Skip to content

Instantly share code, notes, and snippets.

@gallais
Last active March 1, 2017 00:43
Show Gist options
  • Save gallais/f31d2a655e4c553c096c13150125a0f9 to your computer and use it in GitHub Desktop.
Save gallais/f31d2a655e4c553c096c13150125a0f9 to your computer and use it in GitHub Desktop.
Trying to see what Ptival's Modular Parser would look like for mutually defined types of expressions
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
module ModularParser3 where
import Data.Function
import Data.Attoparsec.ByteString
import Data.Attoparsec.Combinator
import Data.Attoparsec.ByteString.Char8
import Control.Monad (ap)
newtype All (p :: a -> *) (as :: [a]) = All { getAll :: forall a. In a as -> p a }
data In (x :: a) (xs :: [a]) where
Here :: In x (x ': xs)
There :: In x xs -> In x (y ': xs)
newtype MParser as a = MParser {
runMParser :: All Parser as -- "self"-precedence parsers
-> All Parser as -- "next"-precedence parsers
-> Parser a }
newtype LParser as a = Parsers { getLParser :: [MParser as a] }
choiceOrNextP :: forall as. All (LParser as) as -> All Parser as -> All Parser as
choiceOrNextP ps nextPs =
fix $ \ selfPs -> All $ \ idx ->
choice $ fmap (\ p -> runMParser p selfPs nextPs) (getLParser $ getAll ps idx) ++ [getAll nextPs idx]
instance Functor (MParser as) where
fmap f mp = MParser $ \ selfP nextP ->
fmap f (runMParser mp selfP nextP)
instance Applicative (MParser as) where
pure = return
(<*>) = ap
instance Monad (MParser as) where
return a = MParser $ \ _ _ -> return a
ma >>= f = MParser $ \ selfP nextP ->
runMParser ma selfP nextP >>= \ a ->
runMParser (f a) selfP nextP
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment