[commit: hsc2hs] master: Fix AMP warnings in HSCParser.hs (9960cac)

git at git.haskell.org git at git.haskell.org
Wed Sep 18 19:12:23 CEST 2013


Repository : ssh://git@git.haskell.org/hsc2hs

On branch  : master
Link       : http://git.haskell.org/hsc2hs.git/commitdiff/9960cac0996585a592b9b53cd19356eb8abb3526

>---------------------------------------------------------------

commit 9960cac0996585a592b9b53cd19356eb8abb3526
Author: Austin Seipp <austin at well-typed.com>
Date:   Wed Sep 18 12:12:07 2013 -0500

    Fix AMP warnings in HSCParser.hs
    
    Signed-off-by: Austin Seipp <austin at well-typed.com>


>---------------------------------------------------------------

9960cac0996585a592b9b53cd19356eb8abb3526
 HSCParser.hs |   15 +++++++++++++--
 1 file changed, 13 insertions(+), 2 deletions(-)

diff --git a/HSCParser.hs b/HSCParser.hs
index 21c1c8a..745037f 100644
--- a/HSCParser.hs
+++ b/HSCParser.hs
@@ -1,6 +1,6 @@
 module HSCParser where
-
-import Control.Monad            ( MonadPlus(..), liftM, liftM2 )
+import Control.Applicative      hiding ( many )
+import Control.Monad            ( MonadPlus(..), liftM, liftM2, ap )
 import Data.Char                ( isAlpha, isAlphaNum, isSpace, isDigit )
 
 ------------------------------------------------------------------------
@@ -21,6 +21,13 @@ updatePos pos@(SourcePos name line) ch = case ch of
     '\n' -> SourcePos name (line + 1)
     _    -> pos
 
+instance Functor Parser where
+    fmap = liftM
+
+instance Applicative Parser where
+    pure  = return
+    (<*>) = ap
+
 instance Monad Parser where
     return a = Parser $ \pos s -> Success pos [] s a
     Parser m >>= k =
@@ -33,6 +40,10 @@ instance Monad Parser where
             Failure pos' msg -> Failure pos' msg
     fail msg = Parser $ \pos _ -> Failure pos msg
 
+instance Alternative Parser where
+    empty = mzero
+    (<|>) = mplus
+
 instance MonadPlus Parser where
     mzero                     = fail "mzero"
     Parser m `mplus` Parser n =




More information about the ghc-commits mailing list