Skip to content

Instantly share code, notes, and snippets.

@scott-fleischman
Created August 26, 2014 03:33
Show Gist options
  • Select an option

  • Save scott-fleischman/f150b03e9655f6ff9cbf to your computer and use it in GitHub Desktop.

Select an option

Save scott-fleischman/f150b03e9655f6ff9cbf to your computer and use it in GitHub Desktop.
-- http://www.seas.upenn.edu/~cis194/hw/10-applicative.pdf
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TupleSections #-}
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)
instance Functor Parser where
fmap :: (a -> b) -> Parser a -> Parser b
fmap f p = Parser $ fmap (first f) . runParser p
instance Applicative Parser where
pure :: a -> Parser a
pure x = Parser $ fmap (x,) . Just
(<*>) :: Parser (a -> b) -> Parser a -> Parser b
p1 <*> p2 = Parser $ \s -> case runParser p1 s of
Nothing -> Nothing
Just (p1f, p1s) -> runParser (fmap p1f p2) p1s
abParser :: Parser (Char, Char)
abParser = (,) <$> char 'a' <*> char 'b'
abParser_ :: Parser ()
abParser_ = (\a b -> ()) <$> char 'a' <*> char 'b'
intPair :: Parser (Integer, Integer)
intPair = (,) <$> posInt <*> (char ' ' *> posInt)
instance Alternative Parser where
empty :: Parser a
empty = Parser (const Nothing)
(<|>) :: Parser a -> Parser a -> Parser a
(<|>) a b = Parser $ \s -> runParser a s <|> runParser b s
omit :: Parser a -> Parser ()
omit x = fmap (\a -> ()) x
intOrUppercase :: Parser ()
intOrUppercase = omit posInt <|> omit (satisfy isUpper)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment