Skip to content
Snippets Groups Projects
Commit 581cbc28 authored by Erik de Castro Lopo's avatar Erik de Castro Lopo Committed by Marge Bot
Browse files

Add MonadFail instance for ParserM

parent 71aca77c
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
module ParserM (
-- Parser Monad
ParserM(..), AlexInput, run_parser,
......@@ -18,7 +19,13 @@ module ParserM (
) where
import Control.Applicative
#if __GLASGOW_HASKELL__ >= 806
import Prelude hiding (fail)
import Control.Monad.Fail (MonadFail (..))
#else
import Prelude
#endif
import Control.Monad (ap, liftM)
import Data.Word (Word8)
......@@ -42,6 +49,10 @@ instance Monad ParserM where
Left err ->
Left err
return a = ParserM $ \i s -> Right (i, s, a)
#if __GLASGOW_HASKELL__ >= 806
instance MonadFail ParserM where
#endif
fail err = ParserM $ \_ _ -> Left err
run_parser :: ParserM a -> (String -> Either String a)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment