Skip to content

Instantly share code, notes, and snippets.

@ChristopherKing42
Last active February 26, 2016 20:21
Show Gist options
  • Save ChristopherKing42/cb30809332ccb9d7a6bd to your computer and use it in GitHub Desktop.
Save ChristopherKing42/cb30809332ccb9d7a6bd to your computer and use it in GitHub Desktop.
{-# LANGUAGE Rank2Types #-}
import Control.Applicative (Alternative(..))
import Data.Foldable (asum, traverse_)
newtype Parser a = Parser {run :: forall f. Alternative f => (Char -> f ()) -> f a}
instance Functor Parser where
fmap f (Parser cont) = Parser $ \char -> f <$> cont char
instance Applicative Parser where
pure a = Parser $ \char -> pure a
(Parser contf) <*> (Parser cont) = Parser $ \char -> (contf char) <*> (cont char)
instance Alternative Parser where
empty = Parser $ \char -> empty
(Parser cont) <|> (Parser cont') = Parser $ \char -> (cont char) <|> (cont' char)
some (Parser cont) = Parser $ \char -> some $ cont char
many (Parser cont) = Parser $ \char -> many $ cont char
-- Parser is actually isomorphic to regular expressions, because of `some` and `many`.
item :: Parser Char
item = Parser $ \char -> asum $ map (\c -> c <$ char c) ['A'..'z']
-- If we used `newtype Parser a = Parser {run :: forall f. Alternative f => f Char -> f a}` instead, then we could do `item = Parser id` instead
digit :: Parser Int
digit = Parser $ \char -> asum $ map (\c -> c <$ char (head $ show c)) [0..9]
-- If we used `newtype Parser a = Parser {run :: forall f. Monad f => f Char -> f a}` instead, then we could do `digit = mfilter isDigit item` instead
string :: String -> Parser ()
string s = Parser $ \char -> traverse_ char s
-- Our type can be converted to your type like so:
-- convert :: Parser a -> YourParser a
-- convert p = run p youritem
-- It can also be converted to Parsec efficiently
-- convert :: Parser a -> Parsec a
-- convert p = run p anyChar
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment