Skip to content
Snippets Groups Projects

Compare revisions

Changes are shown as if the source revision was being merged into the target revision. Learn more about comparing revisions.

Source

Select target project
No results found

Target

Select target project
No results found
Show changes
Commits on Source (7)
......@@ -5,7 +5,7 @@
#if __GLASGOW_HASKELL__ >= 710 && __GLASGOW_HASKELL__ < 802
{-# LANGUAGE AutoDeriveTypeable #-}
#endif
#if __GLASGOW_HASKELL__ >= 808
#if __GLASGOW_HASKELL__ >= 806
{-# LANGUAGE QuantifiedConstraints #-}
#endif
-----------------------------------------------------------------------------
......@@ -58,14 +58,29 @@ module Control.Monad.Trans.Class (
--
-- * @'lift' (m >>= f) = 'lift' m >>= ('lift' . f)@
--
-- Since 0.6.0.0 and for GHC 8.8 and later, the requirement that @t m@
-- Since 0.6.0.0 and for GHC 8.6 and later, the requirement that @t m@
-- be a 'Monad' is enforced by the implication constraint
-- @forall m. 'Monad' m => 'Monad' (t m)@ enabled by the
-- @QuantifiedConstraints@ extension.
#if __GLASGOW_HASKELL__ >= 808
--
-- === __Ambiguity error with GHC 9.0 to 9.2.2__
-- These versions of GHC have a bug
-- (<https://gitlab.haskell.org/ghc/ghc/-/issues/20582>)
-- which causes constraints like
--
-- @
-- (MonadTrans t, forall m. Monad m => Monad (t m)) => ...
-- @
--
-- to be reported as ambiguous. For transformers 0.6 and later, this can
-- be fixed by removing the second constraint, which is implied by the first.
#if __GLASGOW_HASKELL__ >= 806
class (forall m. Monad m => Monad (t m)) => MonadTrans t where
#else
-- prior to GHC 8.8 (base-4.13), the Monad class included fail
-- Prior to GHC 8.8 (base-4.13), the Monad class included fail.
-- GHC 8.6 (base-4.12) has MonadFailDesugaring on by default, so there
-- is no need for users defining monad transformers to define fail in
-- the Monad instance of the transformed monad.
class MonadTrans t where
#endif
-- | Lift a computation from the argument monad to the constructed monad.
......@@ -108,16 +123,23 @@ specialized lifting combinators, called @lift@/Op/
{- $strict
A monad is said to be /strict/ if its '>>=' operation is strict in its first
argument. The base monads 'Maybe', @[]@ and 'IO' are strict:
A monad is said to be /strict/ if its '>>=' operation (and therefore also
'>>') is strict in its first argument. The base monads 'Maybe', @[]@
and 'IO' are strict:
>>> undefined >> return 2 :: Maybe Integer
>>> undefined >> Just 2
*** Exception: Prelude.undefined
>>> undefined >> [2]
*** Exception: Prelude.undefined
>>> undefined >> print 2
*** Exception: Prelude.undefined
However the monad 'Data.Functor.Identity.Identity' is not:
However the monads 'Data.Functor.Identity.Identity' and @(->) a@ are not:
>>> runIdentity (undefined >> return 2)
2
>>> undefined >> Identity 2
Identity 2
>>> (undefined >> (+1)) 5
6
In a strict monad you know when each action is executed, but the monad
is not necessarily strict in the return value, or in other components
......
......@@ -291,6 +291,10 @@ modify f = state $ \ s -> ((), f s)
-- new state.
--
-- * @'modify'' f = 'get' >>= (('$!') 'put' . f)@
--
-- Note that this is only strict in the top level of the state.
-- Lazy components of the state will not be evaluated unless @f@
-- evaluates them.
modify' :: (Monad m) => (s -> s) -> StateT s m ()
modify' f = do
s <- get
......
-*-change-log-*-
0.6.0.6 Ross Paterson <R.Paterson@city.ac.uk> Jan 2023
* Fix for GHC 8.6
0.6.0.5 Ross Paterson <R.Paterson@city.ac.uk> Jan 2023
* Revert to allowing MonadTrans constraint with GHC >= 8.6
0.6.0.4 Ross Paterson <R.Paterson@city.ac.uk> Feb 2022
* Restrict deriving (Generic) to GHC >= 7.4
......
name: transformers
version: 0.6.0.4
version: 0.6.0.6
license: BSD3
license-file: LICENSE
author: Andy Gill, Ross Paterson
......