mirror of
https://github.com/haskell-effectful/effectful.git
synced 2024-11-23 14:36:11 +03:00
Fix haddock references
This commit is contained in:
parent
e190279e5f
commit
23d96a4633
@ -12,7 +12,7 @@ import Effectful.Internal.Monad
|
||||
import qualified Effectful.Reader as R
|
||||
|
||||
-- | Compatiblity layer for a transition period from MTL-style effect handling
|
||||
-- to 'Effective.Eff'.
|
||||
-- to 'Effectful.Eff'.
|
||||
class Monad m => MonadReader r m where
|
||||
{-# MINIMAL (ask | reader), local #-}
|
||||
ask :: m r
|
||||
|
@ -8,7 +8,7 @@ import Effectful.Internal.Monad
|
||||
import qualified Effectful.State.Dynamic as S
|
||||
|
||||
-- | Compatiblity layer for a transition period from MTL-style effect handling
|
||||
-- to 'Effective.Eff'.
|
||||
-- to 'Effectful.Eff'.
|
||||
class Monad m => MonadState s m where
|
||||
{-# MINIMAL state | get, put #-}
|
||||
|
||||
|
@ -9,7 +9,7 @@ import Effectful.Internal.Monad
|
||||
import qualified Effectful.Writer as W
|
||||
|
||||
-- | Compatiblity layer for a transition period from MTL-style effect handling
|
||||
-- to 'Effective.Eff'.
|
||||
-- to 'Effectful.Eff'.
|
||||
class Monad m => MonadWriter w m where
|
||||
{-# MINIMAL (writer | tell), listen #-}
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# OPTIONS_HADDOCK not-home #-}
|
||||
-- | The enviroment for 'Effective.Internal.Monad.Eff'.
|
||||
-- | The enviroment for 'Effectful.Internal.Monad.Eff'.
|
||||
--
|
||||
-- This module is intended for internal use only, and may change without warning
|
||||
-- in subsequent releases.
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
{-# OPTIONS_HADDOCK not-home #-}
|
||||
-- | Type-safe indexing for 'Effective.Internal.Monad.Env'.
|
||||
-- | Type-safe indexing for 'Effectful.Internal.Monad.Env'.
|
||||
--
|
||||
-- This module is intended for internal use only, and may change without warning
|
||||
-- in subsequent releases.
|
||||
@ -30,6 +30,6 @@ instance {-# OVERLAPPING #-} e :> (e : es) where
|
||||
instance e :> es => e :> (x : es) where
|
||||
ixOf = 1 + ixOf @e @es
|
||||
|
||||
-- | Get position of @e@ in the 'Effective.Internal.Env.Env'.
|
||||
-- | Get position of @e@ in the 'Effectful.Internal.Env.Env'.
|
||||
ixEnv :: forall e es. e :> es => Int -> Int
|
||||
ixEnv n = n - ixOf @e @es - 1
|
||||
|
@ -6,8 +6,8 @@
|
||||
--
|
||||
-- - not suitable for sharing between multiple threads.
|
||||
--
|
||||
-- If you plan to do the latter, have a look at "Effective.State.MVar" or
|
||||
-- "Effective.State.Dynamic".
|
||||
-- If you plan to do the latter, have a look at "Effectful.State.MVar" or
|
||||
-- "Effectful.State.Dynamic".
|
||||
--
|
||||
module Effectful.State
|
||||
( State
|
||||
|
@ -1,7 +1,7 @@
|
||||
-- | The 'State' as an effect with dynamic dispatch.
|
||||
--
|
||||
-- It's not clear in which situation it's beneficial to use this instead of
|
||||
-- "Effective.State" or "Effective.State.MVar" as you either:
|
||||
-- "Effectful.State" or "Effectful.State.MVar" as you either:
|
||||
--
|
||||
-- - Share state between threads and need the synchonized version.
|
||||
--
|
||||
|
@ -2,7 +2,7 @@
|
||||
--
|
||||
-- Represented as an MVar underneath, therefore:
|
||||
--
|
||||
-- - slower than "Effective.State"
|
||||
-- - slower than "Effectful.State"
|
||||
--
|
||||
-- - suitable for sharing between multiple threads.
|
||||
--
|
||||
|
Loading…
Reference in New Issue
Block a user