doc[haddock]: examples and comments

This commit is contained in:
vegowotenks 2025-06-29 13:38:36 +02:00
parent bfa071fb6b
commit 0411e8af19
2 changed files with 40 additions and 15 deletions

View file

@ -1,7 +1,10 @@
{-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
module Language.Brainfuck (parse, ParseFailure, render) where
-- | This module allows you to parse and manipulate brainfuck programs. Currently there are no re-exports here, you may need to look into submodules to find the operations you need.
module Language.Brainfuck (parse, ParseFailure(..), render) where
import Control.Monad.ST (runST, ST) import Control.Monad.ST (runST, ST)
@ -16,14 +19,32 @@ import Language.Brainfuck.Instruction ( Instruction(..) )
import qualified Data.List as List import qualified Data.List as List
import Numeric.Natural (Natural) import Numeric.Natural (Natural)
-- | Brainfuck has only two types of syntax errors: either too many open brackets or too many closed brackets, this is the failure type.
data ParseFailure data ParseFailure
= UnexpectedClosingBracket Natural -- closing bracket position = UnexpectedClosingBracket Natural
| UnmatchedOpenBracket Natural -- opening bracket position -- ^ closing bracket position
| UnmatchedOpenBracket Natural
-- ^ opening bracket position
deriving stock (Show, Eq) deriving stock (Show, Eq)
-- | Convert a Text to a list of instructions, discard all comments. -- | Convert a Text to a list of instructions, discard all comments.
-- --
-- Recognized instructions are in the string "+-<>,.[]", they are represented as a Enum Type. -- Recognized instructions are in the string "+-<>,.[]", they are represented as a Enum Type.
--
-- ==== __Examples__
--
-- >>> parse $ Text.pack "<<>>,,..<,.>"
-- Right [MoveLeft,MoveLeft,MoveRight,MoveRight,ReadByte,ReadByte,PutByte,PutByte,MoveLeft,ReadByte,PutByte,MoveRight]
--
-- >>> parse $ Text.pack "[-]++<<<[>-[+-+-+]]>+"
-- Right [Loop [Decrement],Increment,Increment,MoveLeft,MoveLeft,MoveLeft,Loop [MoveRight,Decrement,Loop [Increment,Decrement,Increment,Decrement,Increment]],MoveRight,Increment]
--
-- >>> parse $ Text.pack "["
-- Left (UnmatchedOpenBracket 0)
--
-- >>> parse $ Text.pack "[]]"
-- Left (UnexpectedClosingBracket 2)
parse :: Text -> Either ParseFailure (Vector Instruction) parse :: Text -> Either ParseFailure (Vector Instruction)
parse text = runST $ do parse text = runST $ do
@ -75,18 +96,17 @@ parse text = runST $ do
_ -> pure innerResult _ -> pure innerResult
_ -> parseBlock cs instructions index _ -> parseBlock cs instructions index
-- | Render a series of instructions into a program text.
-- >>> parse $ Text.pack "<<>>,,..<,.>" --
-- Right [MoveLeft,MoveLeft,MoveRight,MoveRight,ReadByte,ReadByte,PutByte,PutByte,MoveLeft,ReadByte,PutByte,MoveRight] -- This is not exactly an inverse of 'parse' because parse will discard all comments and may fail with the 'Left' constructor.
--
-- >>> parse $ Text.pack "[-]++<<<[>-[+-+-+]]>+" -- ==== __Examples__
-- Right [Loop [Decrement],Increment,Increment,MoveLeft,MoveLeft,MoveLeft,Loop [MoveRight,Decrement,Loop [Increment,Decrement,Increment,Decrement,Increment]],MoveRight,Increment] --
-- >>> render $ Vector.fromList [Increment,Increment, Loop $ Vector.fromList [Decrement, MoveRight, Increment, MoveLeft]]
-- >>> parse $ Text.pack "[" -- "++[->+<]"
-- Left (UnmatchedOpenBracket 0) --
-- >>> fmap render . parse $ Text.pack "++ [ ->+< ] comment"
-- >>> parse $ Text.pack "[]]" -- Right "++[->+<]"
-- Left (UnexpectedClosingBracket 2)
render :: Vector Instruction -> Text render :: Vector Instruction -> Text
render = Text.concat . List.map renderSingle . Vector.toList render = Text.concat . List.map renderSingle . Vector.toList

View file

@ -1,5 +1,8 @@
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
-- | This is the native brainfuck instruction representation. They can be easily mapped to and from a program text.
module Language.Brainfuck.Instruction (Instruction(..)) where module Language.Brainfuck.Instruction (Instruction(..)) where
import Data.Vector ( Vector ) import Data.Vector ( Vector )
@ -9,6 +12,8 @@ import Test.QuickCheck.Instances.Vector ()
import qualified Test.QuickCheck.Gen as Gen import qualified Test.QuickCheck.Gen as Gen
-- | The native brainfuck instruction. Does not allow comments, they must be discarded whilst parsing.
data Instruction data Instruction
= Increment = Increment
| Decrement | Decrement