[Haskell-beginners] combining a trifecta parser with FreshMT from unbound

Andreas Reuleaux reuleaux at web.de
Mon Jul 28 23:26:17 UTC 2014


I can relatively easily combine a trifecta parser with some state:

  -- imports, language pragmas omitted here

  newtype InnerParser a = InnerParser { runInnerParser :: Parser a }
                        deriving (Functor
                                 , Monad
                                 , Applicative
                                 , Alternative
                                 , Parsing
                                 , CharParsing
                                 , MonadPlus
                                 )


  data PiState = PiState {
     foobar :: Integer
     -- ...some more stuff...
    }



  type PiParser = StateT PiState InnerParser


  instance TokenParsing PiParser where
    someSpace = buildSomeSpaceParser (skipSome (satisfy isSpace))
                $ commentStart .~ "{-"
                $ commentEnd .~ "-}"
                $ commentLine .~ "--"
                $ commentNesting .~ True
                $ emptyCommentStyle


  idStyle = styleStart .~ letter
            $ styleLetter .~ (alphaNum <|> oneOf "_'")
            $ styleReserved .~  HS.fromList
            ["refl"
            ,"ind"
            ,"Type"
            -- ...
            ]
            $ emptyIdents


  identifier :: PiParser String
  identifier = token
               $ ident
               $ idStyle


  -- etc.
  

This is the approach taken in Idris e.g. and it works, as I understand,
because the trifecta/parsers type classes involved (CharParsing etc) are "already
prepared" for attaching a StateT monad transformer: there are instances
defined for all the usual transformers: StateT, ReaderT, RWST etc.

I can easily add more convenient type classes, having them derived for
my InnerParser: LookAheadParsing, DeltaParsing etc.

Now when I want to use FreshMT from the unbound package instead of
StateT, things get much more complicated.

I don't really care at this point if with a type synonym

  type PiParser = FreshMT InnerParser

or as a newtype wrapper (deriving as much as I can automatically)

  newtype PiParser a = P {
    runP :: FreshMT InnerParser a
    } deriving (Monad, Functor, Applicative)

Anyway, I need to provide all these instances by hand (CharParsing,
Alternative etc), am still
struggling with the details (and might have more questions in this
regard), even though FreshMT really is just defined in terms of StateT

  http://hackage.haskell.org/package/unbound-0.4.3.1/docs/src/Unbound-LocallyNameless-Fresh.html#FreshMT

So I wonder, if there is an easier way to approach this, have some more
instances derived automatically ?

(Basically I just want to get Stephanie Weirichs pi-forall language
working with trifecta instead of parsec, cf. this years' OPLSS)

I can provide complete running code (with all the imports etc) if
necessary.

Thanks.

-Andreas


More information about the Beginners mailing list