[Haskell-cafe] help w/ improving custom Stream for parsec

Maurizio Vitale mrz.vtl at gmail.com
Tue Apr 7 16:25:12 UTC 2015


I need a custom stream that supports insertion of include files and
expansions of macros.
I also want to be able to give nice error messages (think of clang
macro-expansion backtrace), so I cannot use the standard trick of
concatenating included files and expanded macros to the current input with
setInput/getInput (I think I can't maybe there's a way of keeping a more
complex "position" and since the use in producing an error backtrac is
rare, it migth be worth exploring; if anybody has ideas here, I'm listening)

Assuming I need a more compelx stream, this is what I have (Macro and File
both have a string argument, but it will be more compicated, a list of
expansions for Macro for instance).

Is there a better way for doing this?
What are the performance implications with backtracking? I'll be
benchmarking it, but if people see obvious problems, let me know.

Thanks a lot,
  Maurizio

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}

module Parsing where

import Text.Parsec

type Parser s m = ParsecT s () m

data VStream = File String | Macro String deriving Show

newtype StreamStack = StreamStack [VStream] deriving Show

instance (Monad m) ⇒ Stream VStream m Char where
  uncons ∷ VStream -> m (Maybe (Char, VStream))
  uncons (File (a:as)) = return $ Just (a, File as)
  uncons (File []) = return Nothing
  uncons (Macro (a:as)) = return $ Just (a, File as)
  uncons (Macro []) = return Nothing



instance (Monad m) => Stream StreamStack  m Char where
  uncons (StreamStack []) = return Nothing
  uncons (StreamStack (s:ss)) =
    case uncons s of
     Nothing → uncons $ StreamStack ss
     Just Nothing → uncons $ StreamStack ss
     Just (Just (c, File s')) → return $ Just (c, StreamStack (File s': ss))
     Just (Just (c, Macro s')) → return $ Just (c, StreamStack (Macro
s':ss))
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150407/3e28a995/attachment.html>


More information about the Haskell-Cafe mailing list