diff --git a/src/Language/Brainfuck/Instruction/Extended.hs b/src/Language/Brainfuck/Instruction/Extended.hs index 3b685b6..7ab2a59 100644 --- a/src/Language/Brainfuck/Instruction/Extended.hs +++ b/src/Language/Brainfuck/Instruction/Extended.hs @@ -1,7 +1,11 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE StrictData #-} -module Language.Brainfuck.Instruction.Extended (Operation(..), Interaction(..), ExtendedInstruction(Modify, Move, Interact, Jump), pattern IfNonZero, pattern WithOffset, mkIfNonZero, mkWithOffset, translationSize, parse) where + +-- | Extended instructions are the representation I wish to use for the optimization techniques in these modules. +-- They should be easy to extend, hence I factored the 'Operation' type out of 'Language.Brainfuck.CompressedInstruction.CompressedInstruction'. + +module Language.Brainfuck.Instruction.Extended (ExtendedInstruction(Modify, Move, Interact, Jump), pattern IfNonZero, pattern WithOffset, mkIfNonZero, mkWithOffset, translationSize, parse) where import Data.Word (Word8) @@ -19,16 +23,42 @@ import qualified Language.Brainfuck.Instruction.Compressed as CompressedInstruct import qualified Language.Brainfuck.Instruction.Extended.Operation as Operation import qualified Language.Brainfuck.Instruction.Extended.Interaction as Interaction +-- | This pattern protects the invariant that 'WithOffset'-Instructions may not be nested +-- +-- >>> WithOffset 5 (Interact Interaction.Write) +-- AtOffset 5 (Interact Write) +-- +-- >>> WithOffset 5 (WithOffset (-2) (Modify Operation.Add 5)) +-- AtOffset 3 (Modify Add 5) + pattern WithOffset :: Integer -> ExtendedInstruction -> ExtendedInstruction pattern WithOffset offset embedded <- AtOffset offset embedded where WithOffset offset embedded = mkWithOffset offset embedded +-- | This pattern protects the invariant that 'IfNonZero'-Instructions may not be directly nested +-- +-- >>> IfNonZero (Modify Operation.Add 5) +-- WhenNonZero (Modify Add 5) +-- +-- >>> IfNonZero (IfNonZero (Modify Operation.Subtract 2)) +-- WhenNonZero (Modify Subtract 2) + pattern IfNonZero :: ExtendedInstruction -> ExtendedInstruction pattern IfNonZero instruction <- WhenNonZero instruction where IfNonZero instruction = mkIfNonZero instruction +-- | The extended instruction set is defined by this enum. +-- +-- Note: not all instruction types are exported since some of them hold invariants. +-- +-- You need to additionally consider these pattern exports when matching: +-- +-- [@WithOffset@]: Will merge nested WithOffset instructions +-- +-- [@IfNonZero@]: Will eliminate doubly conditional instructions + data ExtendedInstruction = AtOffset Integer ExtendedInstruction -- invariant, WithOffset may not nest itself | WhenNonZero ExtendedInstruction -- invariant, IfNonZero may not nest itself @@ -38,22 +68,40 @@ data ExtendedInstruction | Jump Integer deriving (Show) +-- | Smart constructor alias for the pattern 'WithOffset' +-- +-- >>> mkIfNonZero $ mkIfNonZero (Interact Interaction.Read) +-- WhenNonZero (Interact Read) + mkIfNonZero :: ExtendedInstruction -> ExtendedInstruction mkIfNonZero = \case WhenNonZero i -> WhenNonZero i instruction -> WhenNonZero instruction +-- | Smart constructor alias for the pattern 'IfNonZero' +-- +-- >>> mkWithOffset 15 $ mkWithOffset (-3) $ Interact Interaction.Read +-- AtOffset 12 (Interact Read) + mkWithOffset :: Integer -> ExtendedInstruction -> ExtendedInstruction mkWithOffset offset = \case AtOffset offset' i -> AtOffset (offset + offset') i instruction -> AtOffset offset instruction --- >>> mkWithOffset 15 $ mkWithOffset (-3) $ Interact Read --- AtOffset 12 (Interact Read) +-- | Parsess the CompressedInstruction program into the ExtendedInstruction form, which e.g. does not contain 'CompressedInstruction.Loop' instructions anymore. +-- +-- >>> :set -XOverloadedLists +-- >>> parse [CompressedInstruction.Add 5] +-- [Modify Add 5] +-- +-- >>> parse [CompressedInstruction.Add 5, CompressedInstruction.Loop [CompressedInstruction.Loop [CompressedInstruction.ReadByte], CompressedInstruction.PutByte]] +-- [Modify Add 5,Jump 4,Jump 1,Interact Read,WhenNonZero (Jump (-2)),Interact Write,WhenNonZero (Jump (-5))] parse :: Vector CompressedInstruction -> Vector ExtendedInstruction parse = Vector.fromList . Vector.foldr prependTranslation [] +-- | This prepends the translation of the instruction to the given list, this was before I learned about List.concatMap being very efficient + prependTranslation :: CompressedInstruction -> [ExtendedInstruction] -> [ExtendedInstruction] prependTranslation instruction rest = let addSingle = (:rest) @@ -71,6 +119,8 @@ prependTranslation instruction rest = let in forwardJump : Vector.foldr prependTranslation (backJump : rest) body +-- | Calculates the required size for a instruction vector of ExtendedInstruction, since they may need more space. + translationSize :: Vector CompressedInstruction -> Natural translationSize = Vector.sum . Vector.map instructionTranslationSize where @@ -87,9 +137,3 @@ translationSize = Vector.sum . Vector.map instructionTranslationSize bodySize = translationSize body in skipLoopSize + repeatLoopSize + bodySize --- >>> :set -XOverloadedLists --- >>> parse [CompressedInstruction.Add 5] --- [Modify Add 5] --- --- >>> parse [CompressedInstruction.Add 5, CompressedInstruction.Loop [CompressedInstruction.Loop [CompressedInstruction.ReadByte], CompressedInstruction.PutByte]] --- [Modify Add 5,Jump 4,Jump 1,Interact Read,WhenNonZero (Jump (-2)),Interact Write,WhenNonZero (Jump (-5))]