doc[extended]: examples and exports
This commit is contained in:
parent
9dfbb4fb1e
commit
b44e238907
1 changed files with 53 additions and 9 deletions
|
@ -1,7 +1,11 @@
|
||||||
{-# LANGUAGE LambdaCase #-}
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
{-# LANGUAGE PatternSynonyms #-}
|
||||||
{-# LANGUAGE StrictData #-}
|
{-# 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)
|
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.Operation as Operation
|
||||||
import qualified Language.Brainfuck.Instruction.Extended.Interaction as Interaction
|
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 :: Integer -> ExtendedInstruction -> ExtendedInstruction
|
||||||
pattern WithOffset offset embedded <- AtOffset offset embedded
|
pattern WithOffset offset embedded <- AtOffset offset embedded
|
||||||
where
|
where
|
||||||
WithOffset offset embedded = mkWithOffset offset embedded
|
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 :: ExtendedInstruction -> ExtendedInstruction
|
||||||
pattern IfNonZero instruction <- WhenNonZero instruction
|
pattern IfNonZero instruction <- WhenNonZero instruction
|
||||||
where
|
where
|
||||||
IfNonZero instruction = mkIfNonZero instruction
|
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
|
data ExtendedInstruction
|
||||||
= AtOffset Integer ExtendedInstruction -- invariant, WithOffset may not nest itself
|
= AtOffset Integer ExtendedInstruction -- invariant, WithOffset may not nest itself
|
||||||
| WhenNonZero ExtendedInstruction -- invariant, IfNonZero may not nest itself
|
| WhenNonZero ExtendedInstruction -- invariant, IfNonZero may not nest itself
|
||||||
|
@ -38,22 +68,40 @@ data ExtendedInstruction
|
||||||
| Jump Integer
|
| Jump Integer
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
|
-- | Smart constructor alias for the pattern 'WithOffset'
|
||||||
|
--
|
||||||
|
-- >>> mkIfNonZero $ mkIfNonZero (Interact Interaction.Read)
|
||||||
|
-- WhenNonZero (Interact Read)
|
||||||
|
|
||||||
mkIfNonZero :: ExtendedInstruction -> ExtendedInstruction
|
mkIfNonZero :: ExtendedInstruction -> ExtendedInstruction
|
||||||
mkIfNonZero = \case
|
mkIfNonZero = \case
|
||||||
WhenNonZero i -> WhenNonZero i
|
WhenNonZero i -> WhenNonZero i
|
||||||
instruction -> WhenNonZero instruction
|
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 :: Integer -> ExtendedInstruction -> ExtendedInstruction
|
||||||
mkWithOffset offset = \case
|
mkWithOffset offset = \case
|
||||||
AtOffset offset' i -> AtOffset (offset + offset') i
|
AtOffset offset' i -> AtOffset (offset + offset') i
|
||||||
instruction -> AtOffset offset instruction
|
instruction -> AtOffset offset instruction
|
||||||
|
|
||||||
-- >>> mkWithOffset 15 $ mkWithOffset (-3) $ Interact Read
|
-- | Parsess the CompressedInstruction program into the ExtendedInstruction form, which e.g. does not contain 'CompressedInstruction.Loop' instructions anymore.
|
||||||
-- AtOffset 12 (Interact Read)
|
--
|
||||||
|
-- >>> :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 CompressedInstruction -> Vector ExtendedInstruction
|
||||||
parse = Vector.fromList . Vector.foldr prependTranslation []
|
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 :: CompressedInstruction -> [ExtendedInstruction] -> [ExtendedInstruction]
|
||||||
prependTranslation instruction rest = let
|
prependTranslation instruction rest = let
|
||||||
addSingle = (:rest)
|
addSingle = (:rest)
|
||||||
|
@ -71,6 +119,8 @@ prependTranslation instruction rest = let
|
||||||
|
|
||||||
in forwardJump : Vector.foldr prependTranslation (backJump : rest) body
|
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 CompressedInstruction -> Natural
|
||||||
translationSize = Vector.sum . Vector.map instructionTranslationSize
|
translationSize = Vector.sum . Vector.map instructionTranslationSize
|
||||||
where
|
where
|
||||||
|
@ -87,9 +137,3 @@ translationSize = Vector.sum . Vector.map instructionTranslationSize
|
||||||
bodySize = translationSize body
|
bodySize = translationSize body
|
||||||
in skipLoopSize + repeatLoopSize + bodySize
|
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))]
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue