feat: StrictData + Unbounded Integer types

This commit is contained in:
vegowotenks 2025-06-19 21:51:45 +02:00
parent 95f86c8660
commit 9484d097d4

View file

@ -1,12 +1,16 @@
{-# 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
import Data.Word (Word8)
import Language.Brainfuck.Instruction.Compressed (CompressedInstruction)
import Data.Vector (Vector)
import Numeric.Natural (Natural)
import Language.Brainfuck.Instruction.Compressed (CompressedInstruction)
import qualified Data.Vector as Vector
import qualified Language.Brainfuck.Instruction.Compressed as CompressedInstruction
import Numeric.Natural (Natural)
data Operation
= Add
@ -18,7 +22,7 @@ data Interaction
| Write
deriving (Show)
pattern WithOffset :: Int -> ExtendedInstruction -> ExtendedInstruction
pattern WithOffset :: Integer -> ExtendedInstruction -> ExtendedInstruction
pattern WithOffset offset embedded <- AtOffset offset embedded
where
WithOffset offset embedded = mkWithOffset offset embedded
@ -29,7 +33,7 @@ pattern IfNonZero instruction <- WhenNonZero instruction
IfNonZero instruction = mkIfNonZero instruction
data ExtendedInstruction
= AtOffset Int ExtendedInstruction -- invariant, WithOffset may not nest itself
= AtOffset Integer ExtendedInstruction -- invariant, WithOffset may not nest itself
| WhenNonZero ExtendedInstruction -- invariant, IfNonZero may not nest itself
| Modify Operation Word8
| Move Integer
@ -42,7 +46,7 @@ mkIfNonZero = \case
WhenNonZero i -> WhenNonZero i
instruction -> WhenNonZero instruction
mkWithOffset :: Int -> ExtendedInstruction -> ExtendedInstruction
mkWithOffset :: Integer -> ExtendedInstruction -> ExtendedInstruction
mkWithOffset offset = \case
AtOffset offset' i -> AtOffset (offset + offset') i
instruction -> AtOffset offset instruction