[commit: packages/haskeline] ghc-head: Add missing Functor/Applicative instances (694af53)

git at git.haskell.org git at git.haskell.org
Wed Jan 15 08:27:45 UTC 2014


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

On branch  : ghc-head
Link       : http://git.haskell.org/packages/haskeline.git/commitdiff/694af532d741511b5e4e8c0453582052ae22d514

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

commit 694af532d741511b5e4e8c0453582052ae22d514
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Nov 2 20:00:15 2013 +0100

    Add missing Functor/Applicative instances
    
    This is needed to silence GHC 7.8's AMP warnings, see also
    
     http://www.haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal#Missing_superclasses
    
    for more information.
    
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


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

694af532d741511b5e4e8c0453582052ae22d514
 System/Console/Haskeline/Backend/DumbTerm.hs |    3 ++-
 System/Console/Haskeline/Backend/Terminfo.hs |    3 ++-
 System/Console/Haskeline/Command.hs          |   10 +++++++++-
 System/Console/Haskeline/Monads.hs           |   10 +++++++++-
 4 files changed, 22 insertions(+), 4 deletions(-)

diff --git a/System/Console/Haskeline/Backend/DumbTerm.hs b/System/Console/Haskeline/Backend/DumbTerm.hs
index b035d65..047b3cf 100644
--- a/System/Console/Haskeline/Backend/DumbTerm.hs
+++ b/System/Console/Haskeline/Backend/DumbTerm.hs
@@ -8,6 +8,7 @@ import System.Console.Haskeline.LineState
 import System.Console.Haskeline.Monads as Monads
 
 import System.IO
+import Control.Applicative(Applicative)
 import Control.Monad(liftM)
 
 -- TODO: 
@@ -21,7 +22,7 @@ initWindow :: Window
 initWindow = Window {pos=0}
 
 newtype DumbTerm m a = DumbTerm {unDumbTerm :: StateT Window (PosixT m) a}
-                deriving (Monad, MonadIO, MonadException,
+                deriving (Functor, Applicative, Monad, MonadIO, MonadException,
                           MonadState Window,
                           MonadReader Handles, MonadReader Encoder)
 
diff --git a/System/Console/Haskeline/Backend/Terminfo.hs b/System/Console/Haskeline/Backend/Terminfo.hs
index 18f1150..95917df 100644
--- a/System/Console/Haskeline/Backend/Terminfo.hs
+++ b/System/Console/Haskeline/Backend/Terminfo.hs
@@ -5,6 +5,7 @@ module System.Console.Haskeline.Backend.Terminfo(
                              where
 
 import System.Console.Terminfo
+import Control.Applicative
 import Control.Monad
 import Data.List(foldl')
 import System.IO
@@ -103,7 +104,7 @@ newtype Draw m a = Draw {unDraw :: (ReaderT Actions
                                     (StateT TermRows
                                     (StateT TermPos
                                     (PosixT m))))) a}
-    deriving (Monad, MonadIO, MonadException,
+    deriving (Functor, Applicative, Monad, MonadIO, MonadException,
               MonadReader Actions, MonadReader Terminal, MonadState TermPos,
               MonadState TermRows,
               MonadReader Handles, MonadReader Encoder)
diff --git a/System/Console/Haskeline/Command.hs b/System/Console/Haskeline/Command.hs
index d900e8f..986fd42 100644
--- a/System/Console/Haskeline/Command.hs
+++ b/System/Console/Haskeline/Command.hs
@@ -29,7 +29,8 @@ module System.Console.Haskeline.Command(
                         ) where
 
 import Data.Char(isPrint)
-import Control.Monad(mplus, liftM)
+import Control.Applicative(Applicative(..))
+import Control.Monad(ap, mplus, liftM)
 import Control.Monad.Trans.Class
 import System.Console.Haskeline.LineState
 import System.Console.Haskeline.Key
@@ -61,6 +62,13 @@ data CmdM m a   = GetKey (KeyMap (CmdM m a))
 
 type Command m s t = s -> CmdM m t
 
+instance Monad m => Functor (CmdM m) where
+    fmap = liftM
+
+instance Monad m => Applicative (CmdM m) where
+    pure  = return
+    (<*>) = ap
+
 instance Monad m => Monad (CmdM m) where
     return = Result
 
diff --git a/System/Console/Haskeline/Monads.hs b/System/Console/Haskeline/Monads.hs
index 86a9c26..0433971 100644
--- a/System/Console/Haskeline/Monads.hs
+++ b/System/Console/Haskeline/Monads.hs
@@ -19,7 +19,8 @@ module System.Console.Haskeline.Monads(
                 orElse
                 ) where
 
-import Control.Monad (liftM)
+import Control.Applicative (Applicative(..))
+import Control.Monad (ap, liftM)
 import Control.Monad.IO.Class (MonadIO(..))
 import Control.Monad.Trans.Class (MonadTrans(..))
 import Control.Monad.Trans.Maybe (MaybeT(..))
@@ -70,6 +71,13 @@ runReaderT' = flip runReaderT
 newtype StateT s m a = StateT { getStateTFunc 
                                     :: forall r . s -> m ((a -> s -> r) -> r)}
 
+instance Monad m => Functor (StateT s m) where
+    fmap  = liftM
+
+instance Monad m => Applicative (StateT s m) where
+    pure  = return
+    (<*>) = ap
+
 instance Monad m => Monad (StateT s m) where
     return x = StateT $ \s -> return $ \f -> f x s
     StateT f >>= g = StateT $ \s -> do



More information about the ghc-commits mailing list