feat: Natural instead of Ints for nonnegativity

This commit is contained in:
vegowotenks 2025-06-27 16:20:39 +02:00
parent 2fc0d46ee9
commit 7705371b6b

View file

@ -1,5 +1,4 @@
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE LambdaCase #-}
module Language.Brainfuck (parse, ParseFailure, render) where
@ -16,10 +15,11 @@ import Data.Vector.Mutable qualified as MutableVector
import Language.Brainfuck.Instruction ( Instruction(..) )
import qualified Data.List as List
import Numeric.Natural (Natural)
data ParseFailure
= UnexpectedClosingBracket Int -- closing bracket position
| UnmatchedOpenBracket Int -- opening bracket position
= UnexpectedClosingBracket Natural -- closing bracket position
| UnmatchedOpenBracket Natural -- opening bracket position
deriving stock (Show, Eq)
-- | Convert a Text to a list of instructions, discard all comments.
@ -36,14 +36,14 @@ parse text = runST $ do
Right (instructions, rest) -> case rest of
Text.Empty -> Right instructions
_ -> Left (UnexpectedClosingBracket $ Text.length text - Text.length rest)
_ -> Left (UnexpectedClosingBracket . fromIntegral $ Text.length text - Text.length rest)
Left failure -> Left failure
where
go :: Text -> MVector s Instruction -> Int -> ST s (Either ParseFailure (Vector Instruction, Text))
go (Text.Empty ) instructions index = do
go Text.Empty instructions index = do
let populatedSlice = MutableVector.take index instructions
frozen <- Vector.force <$!> Vector.freeze populatedSlice
pure . Right $ (frozen, Text.empty)
@ -69,7 +69,7 @@ parse text = runST $ do
innerResult <- go cs innerVector 0
case innerResult of
Right (body, ']' Text.:< rest) -> recognizeInstruction (Loop body) rest
Right _ -> pure $ Left (UnmatchedOpenBracket $ Text.length text - Text.length t)
Right _ -> pure $ Left (UnmatchedOpenBracket . fromIntegral $ Text.length text - Text.length t)
_ -> pure innerResult
_ -> go cs instructions index