{-| Module : Control.Monad.Parse.Class Description : Rudimentary parsing functionality Copyright : (c) Lackmann Phymetric License : GPL-3 Maintainer : olaf.klinke@phymetric.de Stability : experimental Least common denominator of parsing libraries -} module Control.Monad.Parse.Class where import Control.Applicative import Data.Char (isSpace) import Control.Monad.IO.Class -- | rudimentary parsing functionality. -- Every parsing library provides these. class (Monad p, Alternative p) => MonadParse p where char :: Char -> p Char -- ^ parses given character char c = fmap head (string [c]) string :: String -> p String -- ^ parses given string string "" = return "" string (c:cs) = liftA2 (:) (char c) (string cs) anyOf :: (Char -> Bool) -> p Char -- ^ parses character satisfying the predicate eof :: p () -- ^ the end-of-file parser, fails if not all input is consumed. try :: p a -> p a -- ^ add backtracking to a parser. For parser monads that always backtrack, this is 'id'. {-# MINIMAL (char | string),anyOf,eof,try #-} -- | Parser monads that can also do IO. -- -- @ -- p \`fromFile\` fpath -- @ -- -- should be a parser that opens the file @fpath@, parses the contents using @p@ -- and returns the parse result. class (MonadIO p, MonadParse p) => MonadParseIO p where fromFile :: p a -> FilePath -> p a -- | Parse a non-empty string up to the first un-escaped whitespace, -- removing all backslashes. escapedWhitespace :: MonadParse p => p String escapedWhitespace = do c <- anyOf (not.isSpace) if c == '\\' then do w <- anyOf (const True) fmap (w:) (escapedWhitespace <|> return "") else fmap (c:) (escapedWhitespace <|> return "")