doc[compressed]: Haddock coverage 100%

This commit is contained in:
vegowotenks 2025-06-29 13:22:53 +02:00
parent 4aff1a56d6
commit bfa071fb6b

View file

@ -1,5 +1,12 @@
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
-- |
-- Copyright: (c) Luca S. Jaekel
-- License: AGPL3
--
-- Compressed Instructions are useful for brainfuck optimization, since they enable easier pattern-matching on common program patterns.
module Language.Brainfuck.Instruction.Compressed ( CompressedInstruction(..), compress, uncompress ) where
import Data.Bifunctor ( Bifunctor(first) )
@ -17,6 +24,8 @@ import Test.QuickCheck.Gen qualified as Gen
import Language.Brainfuck.Instruction ( Instruction )
import Language.Brainfuck.Instruction qualified as Instruction
-- | Represents a single dense instruction, repeatable instructions have a effect count associated with them. They should not occur next to each other in data structures when they could be merged in any way.
data CompressedInstruction
= Add Word8
| Subtract Word8
@ -29,6 +38,10 @@ data CompressedInstruction
| Loop (Vector CompressedInstruction)
deriving (Show, Eq)
-- >>> fromInteger 300 :: Word8
-- 44
instance Arbitrary CompressedInstruction where
arbitrary :: Gen CompressedInstruction
arbitrary = Gen.oneof
@ -43,6 +56,14 @@ instance Arbitrary CompressedInstruction where
where
resize f x = Gen.sized $ \ s -> Gen.resize (f s) x
-- | Will count reoccuring instructions and associate the count with the repeatable instruction. This should reduce the size of the instruction vector for any useful program.
--
-- >>> compress . Vector.fromList $ replicate 300 Instruction.Increment
-- [Add 44]
--
-- >>> compress . Vector.fromList $ replicate 300 Instruction.MoveRight
-- [MoveRight 300]
compress :: Vector Instruction -> Vector CompressedInstruction
compress instructions = Vector.fromList (go instructions)
where
@ -65,13 +86,13 @@ compress instructions = Vector.fromList (go instructions)
spanLength :: Eq a => a -> Vector a -> (Int, Vector a)
spanLength x xs = first Vector.length $ Vector.span (== x) xs
-- >>> fromInteger 300 :: Word8
-- 44
-- | Uncompress is not necessarily the exact inverse of compress, but it is a brainfuck program semantic-preserving function.
--
-- >>> compress . Vector.fromList $ replicate 300 Instruction.Increment
-- [Add 44]
-- >>> compress . Vector.fromList $ replicate 300 Instruction.MoveRight
-- [MoveRight 300]
--
-- >>> let source = Vector.replicate 300 Instruction.Increment in source == (uncompress . compress) source
-- False
uncompress :: Vector CompressedInstruction -> Vector Instruction
uncompress = Vector.concatMap uncompressSingle
@ -88,7 +109,3 @@ uncompress = Vector.concatMap uncompressSingle
ReadByte -> Vector.singleton Instruction.ReadByte
Loop body -> Vector.singleton $ Instruction.Loop (uncompress body)
-- >>> let source = Vector.replicate 300 Instruction.Increment in source == (uncompress . compress) source
-- False