Repository : ssh://darcs.haskell.org//srv/darcs/packages/base On branch : ghc-7.4
http://hackage.haskell.org/trac/ghc/changeset/f98a240c1c302c3d1ad56f764f4d09a03d68fbe4 >--------------------------------------------------------------- commit f98a240c1c302c3d1ad56f764f4d09a03d68fbe4 Author: George Giorgidze <[email protected]> Date: Wed Nov 2 23:46:01 2011 +0100 Removing the MonadGroup class. This is to reflect the removal of the default grouping clause from the SQL-like comprehension notation ; >--------------------------------------------------------------- Control/Monad/Group.hs | 36 ------------------------------------ base.cabal | 1 - 2 files changed, 0 insertions(+), 37 deletions(-) diff --git a/Control/Monad/Group.hs b/Control/Monad/Group.hs deleted file mode 100644 index a3c36a2..0000000 --- a/Control/Monad/Group.hs +++ /dev/null @@ -1,36 +0,0 @@ -{-# LANGUAGE Trustworthy #-} - ------------------------------------------------------------------------------ --- | --- Module : Control.Monad.Group --- Copyright : (c) Nils Schweinsberg 2011, --- (c) University Tuebingen 2011 --- License : BSD-style (see the file libraries/base/LICENSE) --- Maintainer : [email protected] --- Stability : experimental --- Portability : non-portable >--------------------------------------------------------------- --- Monadic grouping (used for monad comprehensions) >--------------------------------------------------------------- ------------------------------------------------------------------------------ - -{-# LANGUAGE CPP, MultiParamTypeClasses, FlexibleInstances #-} - -module Control.Monad.Group where - -import Prelude -#if defined(__GLASGOW_HASKELL__) -import GHC.Exts (groupWith) -#endif - --- | `MonadGroup` type class without restrictions on the type `t` -class Monad m => MonadGroup m t where - mgroupWith :: (a -> t) -> m a -> m (m a) - -#if defined(__GLASGOW_HASKELL__) --- | Grouping instance for lists using the `groupWith` function from the --- "GHC.Exts" library -instance Ord t => MonadGroup [] t where - mgroupWith = groupWith -#endif - diff --git a/base.cabal b/base.cabal index b968b10..7ebd86b 100644 --- a/base.cabal +++ b/base.cabal @@ -131,7 +131,6 @@ Library { Control.Monad.ST.Lazy.Safe, Control.Monad.ST.Lazy.Unsafe, Control.Monad.ST.Strict, - Control.Monad.Group Control.Monad.Zip Data.Bits, Data.Bool, _______________________________________________ Cvs-libraries mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-libraries
