Skip to content

Instantly share code, notes, and snippets.

@bananabrick
Last active June 28, 2020 00:17
Show Gist options
  • Save bananabrick/d7e9e720843d3172d04b0412f393bf7c to your computer and use it in GitHub Desktop.
Save bananabrick/d7e9e720843d3172d04b0412f393bf7c to your computer and use it in GitHub Desktop.
{- CIS 194 HW 10
due Monday, 1 April
-}
module AParser where
import Control.Applicative
import Data.Char
-- A parser for a value of type a is a function which takes a String
-- represnting the input to be parsed, and succeeds or fails; if it
-- succeeds, it returns the parsed value along with the remainder of
-- the input.
newtype Parser a = Parser { runParser :: String -> Maybe (a, String) }
-- For example, 'satisfy' takes a predicate on Char, and constructs a
-- parser which succeeds only if it sees a Char that satisfies the
-- predicate (which it then returns). If it encounters a Char that
-- does not satisfy the predicate (or an empty input), it fails.
satisfy :: (Char -> Bool) -> Parser Char
satisfy p = Parser f
where
f [] = Nothing -- fail on the empty input
f (x:xs) -- check if x satisfies the predicate
-- if so, return x along with the remainder
-- of the input (that is, xs)
| p x = Just (x, xs)
| otherwise = Nothing -- otherwise, fail
-- Using satisfy, we can define the parser 'char c' which expects to
-- see exactly the character c, and fails otherwise.
char :: Char -> Parser Char
char c = satisfy (== c)
{- For example:
*Parser> runParser (satisfy isUpper) "ABC"
Just ('A',"BC")
*Parser> runParser (satisfy isUpper) "abc"
Nothing
*Parser> runParser (char 'x') "xyz"
Just ('x',"yz")
-}
-- For convenience, we've also provided a parser for positive
-- integers.
posInt :: Parser Integer
posInt = Parser f
where
f xs
| null ns = Nothing
| otherwise = Just (read ns, rest)
where (ns, rest) = span isDigit xs
------------------------------------------------------------
-- Your code goes below here
------------------------------------------------------------
first :: (a -> b) -> (a, c) -> (b, c)
first f (a, c) = (f a, c)
-- Parser a = String -> Maybe (a, String)
-- Parser b = String -> Maybe (b, String)
-- fmap :: (a -> b) -> f a -> f b
-- <*> :: f (a -> b) -> f a -> f b
instance Functor Parser where
fmap m (Parser fa) = Parser {runParser = fmap (first m) . fa}
-- (((b -> c), String) -> Maybe (c, String)) -> Maybe (c, String)
applySecond ::
Parser b ->
(b -> c, String) ->
Maybe (c, String)
applySecond parserB (bToC, toParse) = first bToC <$> runParser parserB toParse
-- Maybe (b, String)
instance Applicative Parser where
-- Don't consume input
pure v = Parser {runParser = \s -> Just (v, s)}
-- f (a -> b) -> f a -> f b
-- Maybe ((b -> c), String), String -> Maybe (b, String)
(Parser ffa) <*> parserB = Parser {runParser = \s -> ffa s >>= applySecond parserB}
-- (a -> b -> c) -> (String -> Maybe (a, String))
-- -> (String -> Maybe (b, String)) -> (String -> Maybe (c, String))
-- (String -> Maybe ((b -> c), String)) -> (String -> Maybe (b, String))
-- (String -> Maybe (c, String))
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment