Skip to content

Instantly share code, notes, and snippets.

@jg
Last active August 29, 2015 14:03
Show Gist options
  • Save jg/33889e77ef25c4c947d4 to your computer and use it in GitHub Desktop.
Save jg/33889e77ef25c4c947d4 to your computer and use it in GitHub Desktop.
Applicative Ignore
module AParser where
import Control.Applicative
import Data.Char
import Prelude as P
newtype Parser a = Parser { runParser :: String -> Maybe (a, String) }
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
posInt :: Parser Integer
posInt = Parser f
where
f xs
| null ns = Nothing
| otherwise = Just (read ns, rest)
where (ns, rest) = span isDigit xs
instance Applicative Parser where
pure a = Parser (\s -> Just (a,s))
p1 <*> p2 = Parser $ (\s -> do
(f, rest1) <- runParser p1 s
(v, rest2) <- runParser p2 rest1
return $ (f v, rest2))
ignore :: Parser a -> Parser ()
ignore = (pure (const ()) <*>)
intOrUppercase :: Parser ()
intOrUppercase = ignore posInt <|> ignore (satisfy isUpper)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment