[commit: ghc] master: Move Control.Monad.IO.Class to base from transformers (fff0254)
git at git.haskell.org
git at git.haskell.org
Sat Oct 17 14:49:07 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/fff02548d237655dea39f108364d7ebe6d0e122d/ghc
>---------------------------------------------------------------
commit fff02548d237655dea39f108364d7ebe6d0e122d
Author: RyanGlScott <ryan.gl.scott at gmail.com>
Date: Sat Oct 17 16:43:22 2015 +0200
Move Control.Monad.IO.Class to base from transformers
See Trac #10773
Remove Control.Monad.IO.Class from `transformers`. Updates
`transformers` submodule.
See Trac #10773
Test Plan: ./validate
Reviewers: ekmett, hvr, bgamari, austin
Reviewed By: hvr, bgamari, austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1147
GHC Trac Issues: #10773
>---------------------------------------------------------------
fff02548d237655dea39f108364d7ebe6d0e122d
libraries/base/Control/Monad/IO/Class.hs | 36 ++++++++++++++++++++++++++++++++
libraries/base/base.cabal | 1 +
libraries/base/changelog.md | 3 +++
libraries/transformers | 2 +-
4 files changed, 41 insertions(+), 1 deletion(-)
diff --git a/libraries/base/Control/Monad/IO/Class.hs b/libraries/base/Control/Monad/IO/Class.hs
new file mode 100644
index 0000000..b2c419c
--- /dev/null
+++ b/libraries/base/Control/Monad/IO/Class.hs
@@ -0,0 +1,36 @@
+{-# LANGUAGE Safe #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : Control.Monad.IO.Class
+-- Copyright : (c) Andy Gill 2001,
+-- (c) Oregon Graduate Institute of Science and Technology, 2001
+-- License : BSD-style (see the file LICENSE)
+--
+-- Maintainer : R.Paterson at city.ac.uk
+-- Stability : experimental
+-- Portability : portable
+--
+-- Class of monads based on @IO at .
+-----------------------------------------------------------------------------
+
+module Control.Monad.IO.Class (
+ MonadIO(..)
+ ) where
+
+-- | Monads in which 'IO' computations may be embedded.
+-- Any monad built by applying a sequence of monad transformers to the
+-- 'IO' monad will be an instance of this class.
+--
+-- Instances should satisfy the following laws, which state that 'liftIO'
+-- is a transformer of monads:
+--
+-- * @'liftIO' . 'return' = 'return'@
+--
+-- * @'liftIO' (m >>= f) = 'liftIO' m >>= ('liftIO' . f)@
+
+class (Monad m) => MonadIO m where
+ -- | Lift a computation from the 'IO' monad.
+ liftIO :: IO a -> m a
+
+instance MonadIO IO where
+ liftIO = id
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 326f457..7a0ef98 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -115,6 +115,7 @@ Library
Control.Monad
Control.Monad.Fix
Control.Monad.Instances
+ Control.Monad.IO.Class
Control.Monad.ST
Control.Monad.ST.Lazy
Control.Monad.ST.Lazy.Safe
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 34493ac..ff03562 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -56,6 +56,9 @@
* Made `PatternMatchFail`, `RecSelError`, `RecConError`, `RecUpdError`,
`NoMethodError`, and `AssertionFailed` newtypes (#10738)
+ * New module `Control.Monad.IO.Class` (previously provided by `transformers`
+ package). (#10773)
+
* The `Generic` instance for `Proxy` is now poly-kinded (#10775)
* add `Data.List.NonEmpty` and `Data.Semigroup` (to become
diff --git a/libraries/transformers b/libraries/transformers
index 078c7da..0c7207e 160000
--- a/libraries/transformers
+++ b/libraries/transformers
@@ -1 +1 @@
-Subproject commit 078c7daf36ea1fa1ecb63b04dbe667a443e13044
+Subproject commit 0c7207e9702afb5344cc33892eb6da9126a85cf3
More information about the ghc-commits
mailing list