monad comprehensions: Group and Zip monad
authorNils Schweinsberg <mail@n-sch.de>
Fri, 29 Apr 2011 16:16:56 +0000 (18:16 +0200)
committerSimon Peyton Jones <simonpj@microsoft.com>
Sat, 30 Apr 2011 13:16:23 +0000 (14:16 +0100)
ticket #4370

Control/Monad/Group.hs [new file with mode: 0644]
Control/Monad/Zip.hs [new file with mode: 0644]
base.cabal

diff --git a/Control/Monad/Group.hs b/Control/Monad/Group.hs
new file mode 100644 (file)
index 0000000..baab7da
--- /dev/null
@@ -0,0 +1,33 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Control.Monad.Group
+-- Copyright   :  (c) Nils Schweinsberg 2011,
+--                (c) University Tuebingen 2011
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
+-- Maintainer  :  libraries@haskell.org
+-- 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/Control/Monad/Zip.hs b/Control/Monad/Zip.hs
new file mode 100644 (file)
index 0000000..d6475b8
--- /dev/null
@@ -0,0 +1,46 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Control.Monad.Zip
+-- Copyright   :  (c) Nils Schweinsberg 2011,
+--                (c) University Tuebingen 2011
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
+-- Maintainer  :  libraries@haskell.org
+-- Stability   :  experimental
+-- Portability :  portable
+--
+-- Monadic zipping (used for monad comprehensions)
+--
+-----------------------------------------------------------------------------
+
+module Control.Monad.Zip where
+
+import Prelude
+import Control.Monad (liftM)
+
+-- | `MonadZip` type class. Minimal definition: `mzip` or `mzipWith`
+--
+-- Instances should satisfy the laws:
+--
+-- * Naturality :
+--
+--   > liftM (f *** g) (mzip ma mb) = mzip (liftM f ma) (liftM g mb)
+--
+-- * Information Preservation:
+--
+--   > liftM (const ()) ma = liftM (const ()) mb
+--   > ==>
+--   > munzip (mzip ma mb) = (ma, mb)
+--
+class Monad m => MonadZip m where
+
+    mzip :: m a -> m b -> m (a,b)
+    mzip = mzipWith (,)
+
+    mzipWith :: (a -> b -> c) -> m a -> m b -> m c
+    mzipWith f ma mb = liftM (uncurry f) (mzip ma mb)
+
+instance MonadZip [] where
+    mzip = zip
+
+munzip :: MonadZip m => m (a,b) -> (m a, m b)
+munzip mab = (liftM fst mab, liftM snd mab)
index b4a6ee7..5478cc3 100644 (file)
@@ -121,6 +121,8 @@ Library {
         Control.Monad.ST
         Control.Monad.ST.Lazy
         Control.Monad.ST.Strict
+        Control.Monad.Group
+        Control.Monad.Zip
         Data.Bits,
         Data.Bool,
         Data.Char,