{-#LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances #-} module Text.Parcom.Stream where class Stream s t | s -> t where peek :: s -> t atEnd :: s -> Bool consume :: s -> s pop :: s -> (t, s) consume = snd . pop pop s = (peek s, consume s) instance Stream [a] a where peek = head atEnd = null consume = tail class Token t where isLineDelimiter :: t -> Bool instance Token Char where isLineDelimiter '\n' = True isLineDelimiter _ = False class Listish s t | s -> t where toList :: s -> [t] fromList :: [t] -> s instance Listish [a] a where toList = id fromList = id class Textish s where peekChar :: s -> (Maybe Char, Int) instance Textish [Char] where peekChar [] = (Nothing, 0) peekChar (c:[]) = (Just c, 1)