aboutsummaryrefslogtreecommitdiff
path: root/ch19
diff options
context:
space:
mode:
authorJan Sucan <jan@jansucan.com>2025-09-06 17:06:43 +0200
committerJan Sucan <jan@jansucan.com>2025-09-06 17:06:43 +0200
commitd73d68b69da59f2895e3340007adf9aa9acadc72 (patch)
tree85a47aaf552cbe37e1f046f3362edcc3dc69f727 /ch19
parent94b3e712bc164422b228671d16b3ecb2a7c90cb9 (diff)
19_b_1: Add solution
Diffstat (limited to 'ch19')
-rw-r--r--ch19/Module_19_b_1.hs73
1 files changed, 73 insertions, 0 deletions
diff --git a/ch19/Module_19_b_1.hs b/ch19/Module_19_b_1.hs
new file mode 100644
index 0000000..eb68a9c
--- /dev/null
+++ b/ch19/Module_19_b_1.hs
@@ -0,0 +1,73 @@
+-- Write a many parser, with type Parser a -> Parser [a]. It should apply a
+-- parser until it fails.
+
+-- Control.Monad.Error is deprecated. Control.Monad.Except should be used
+-- instead. I modified the code from examples here to use it.
+
+
+{-- From examples/examples/ch19/ParseInt.hs and modified --}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
+module Module_19_b_1 where
+
+import Control.Monad.Except
+import Control.Monad
+import Control.Monad.State
+import qualified Data.ByteString.Char8 as B
+
+data ParseError = NumericOverflow
+ | EndOfInput
+ | Chatty String
+ deriving (Eq, Ord, Show)
+
+newtype Parser a = P {
+ runP :: ExceptT ParseError (State B.ByteString) a
+ } deriving (Functor, Applicative, Monad, MonadError ParseError)
+
+liftP :: State B.ByteString a -> Parser a
+liftP m = P (lift m)
+
+satisfy :: (Char -> Bool) -> Parser Char
+satisfy p = do
+ s <- liftP get
+ case B.uncons s of
+ Nothing -> throwError EndOfInput
+ Just (c, s')
+ | p c -> liftP (put s') >> return c
+ | otherwise -> throwError (Chatty "satisfy failed")
+
+runParser :: Parser a -> B.ByteString
+ -> Either ParseError (a, B.ByteString)
+runParser p bs = case runState (runExceptT (runP p)) bs of
+ (Left err, _) -> Left err
+ (Right r, bs) -> Right (r, bs)
+
+optional :: Parser a -> Parser (Maybe a)
+optional p = (Just `liftM` p) `catchError` \_ -> return Nothing
+{-- End of code from examples --}
+
+
+many :: Parser a -> Parser [a]
+many p = ((:) <$> p <*> many p) `catchError` \_ -> return []
+
+
+-- ghci> :l Module_19_b_1.hs
+-- [1 of 1] Compiling Module_19_b_1 ( Module_19_b_1.hs, interpreted )
+-- Ok, one module loaded.
+
+-- ghci> :m +Data.Char
+
+-- ghci> runParser (many (satisfy isDigit)) (B.pack "")
+-- Right ("","")
+
+-- ghci> runParser (many (satisfy isDigit)) (B.pack "abc")
+-- Right ("","abc")
+
+-- ghci> runParser (many (satisfy isDigit)) (B.pack "9abc")
+-- Right ("9","abc")
+
+-- ghci> runParser (many (satisfy isDigit)) (B.pack "987abc")
+-- Right ("987","abc")
+
+-- ghci> runParser (many (satisfy isDigit)) (B.pack "x987abc")
+-- Right ("","x987abc")