{-# LANGUAGE FlexibleContexts, FunctionalDependencies, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- Copyright 2019, Advise-Me project team. This file is distributed under -- the terms of the Apache License 2.0. For more information, see the files -- "LICENSE.txt" and "NOTICE.txt", which are included in the distribution. ----------------------------------------------------------------------------- -- | -- Maintainer : bastiaan.heeren@ou.nl -- Stability : provisional -- Portability : portable (depends on ghc) -- -- This module defines the parser interface. It consists of three type classes: ParseState, Parse and ParseLog. -- These three type classes expose the parsing primitives necessary to be implemented by any parser. -- Although both ParseState and ParseLog are optional, Parse is not. -- ----------------------------------------------------------------------------- module Recognize.Parsing.Parse where import Control.Applicative (Alternative, (<|>)) import Control.Monad.State import Control.Monad.Identity infixl 3 |> -- | Interface for the basic parsing primitives class (Monad m, Alternative m) => Parse m s | m -> s where (|>) :: m a -> m a -> m a satisfyWith :: (s -> Maybe a) -> m a withInputList :: ([s] -> [a]) -> m a -- input :: m s [s] -- lookAhead :: m s a -> m s a safePeek :: Parse m s => m (Maybe s) safePeek = withInputList $ \xs -> case xs of [] -> [Nothing] hd:_ -> [Just hd] option :: Parse m s => m a -> m (Maybe a) option m = Just <$> m <|> return Nothing satisfy :: Parse m s => (s -> Bool) -> m s satisfy f = satisfyWith (\s -> if f s then Just s else Nothing) guardBy :: (MonadState st m, Alternative m) => (st -> Bool) -> m () guardBy p = gets p >>= guard -- | Interface for monads that are capable of logging. -- class ParseLog m where pLog :: String -> m () instance ParseLog Identity where pLog _ = return () instance ParseLog IO where pLog = putStrLn