Repository : ssh://darcs.haskell.org//srv/darcs/packages/template-haskell

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/907cb365b98ff832aa9412c53610bf1815b2e9e7

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

commit 907cb365b98ff832aa9412c53610bf1815b2e9e7
Author: Simon Peyton Jones <[email protected]>
Date:   Fri Jul 29 13:04:04 2011 +0100

    Make Q an instance of Applicative
    
    Thanks to Bas van Dijk for proposing this.
    
    In the end I replaced Functor by Applicative in the
    superclasses of Quasi, thus:
      class (Monad m, Applicative m) => Quasi m where
    because Functor is a superclass of Applicative.

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

 Language/Haskell/TH/Syntax.hs |    7 ++++++-
 1 files changed, 6 insertions(+), 1 deletions(-)

diff --git a/Language/Haskell/TH/Syntax.hs b/Language/Haskell/TH/Syntax.hs
index c777b89..18f6029 100644
--- a/Language/Haskell/TH/Syntax.hs
+++ b/Language/Haskell/TH/Syntax.hs
@@ -58,6 +58,7 @@ import GHC.Base               ( Int(..), Int#, (<#), (==#) )
 import Language.Haskell.TH.Syntax.Internals
 import Data.Data (Data(..), Typeable, mkConstr, mkDataType, constrIndex)
 import qualified Data.Data as Data
+import Control.Applicative( Applicative(..) )
 import Data.IORef
 import System.IO.Unsafe        ( unsafePerformIO )
 import Control.Monad (liftM)
@@ -70,7 +71,7 @@ import Data.Char        ( isAlpha )
 --
 -----------------------------------------------------
 
-class (Monad m, Functor m) => Quasi m where
+class (Monad m, Applicative m) => Quasi m where
   qNewName :: String -> m Name
        -- ^ Fresh names
 
@@ -149,6 +150,10 @@ instance Monad Q where
 instance Functor Q where
   fmap f (Q x) = Q (fmap f x)
 
+instance Applicative Q where 
+  pure x = Q (pure x) 
+  Q f <*> Q x = Q (f <*> x) 
+
 ----------------------------------------------------
 -- Packaged versions for the programmer, hiding the Quasi-ness
 newName :: String -> Q Name



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to