Clean up haddock warnings

This commit is contained in:
Sandy Maguire 2019-04-20 13:55:49 -04:00
parent 187c6e8152
commit d886b32fe4
6 changed files with 12 additions and 12 deletions

View File

@ -26,7 +26,7 @@ module Polysemy
-- ReadLine :: Console m String
-- @
--
-- Notice that the 'a' parameter gets instataniated at the /desired return
-- Notice that the @a@ parameter gets instataniated at the /desired return
-- type/ of the actions. Writing a line returns a '()', but reading one
-- returns 'String'.
--

View File

@ -36,8 +36,8 @@ swap ~(a, b) = (b, a)
------------------------------------------------------------------------------
-- | The simplest way to produce an effect handler. Interprets an effect 'e' by
-- transforming it into other effects inside of 'r'.
-- | The simplest way to produce an effect handler. Interprets an effect @e@ by
-- transforming it into other effects inside of @r@.
interpret
:: FirstOrder e "interpret"
=> ( x m. e m x -> Sem r x)
@ -51,7 +51,7 @@ interpret f = interpretH $ \(e :: e m x) -> liftT @m $ f e
------------------------------------------------------------------------------
-- | Like 'interpret', but for higher-order effects (ie. those which make use of
-- the 'm' parameter.)
-- the @m@ parameter.)
--
-- See the notes on 'Tactical' for how to use this function.
interpretH

View File

@ -16,10 +16,10 @@ module Polysemy.Internal.Lift where
-- @
--
-- That being said, you lose out on a significant amount of the benefits of
-- 'Polysemy.Sem' by using 'sendM' directly in application code; doing so
-- will tie your application code directly to the underlying monad, and prevent
-- you from interpreting it differently. For best results, only use 'Lift' in
-- your effect interpreters.
-- 'Polysemy.Sem' by using 'Polysemy.sendM' directly in application code; doing
-- so will tie your application code directly to the underlying monad, and
-- prevent you from interpreting it differently. For best results, only use
-- 'Lift' in your effect interpreters.
--
-- Consider using 'Polysemy.Trace.trace' and 'Polysemy.Trace.runTraceIO' as
-- a substitute for using 'putStrLn' directly.

View File

@ -122,7 +122,7 @@ bindT
-- your effect.
--
-- Continuations lifted via 'bindT' will run in the same environment
-- which produced the 'a'.
-- which produced the @a@.
-> Sem (WithTactics e f m r)
(f a -> Sem (e ': r) (f b))
bindT f = send $ HoistInterpretation f

View File

@ -98,8 +98,8 @@ instance Effect (Union r) where
------------------------------------------------------------------------------
-- | A proof that the effect 'e' is available somewhere inside of the effect
-- stack 'r'.
-- | A proof that the effect @e@ is available somewhere inside of the effect
-- stack @r@.
type Member e r = Member' e r
type Member' e r =

View File

@ -41,7 +41,7 @@ runFoldMapOutput f = runState mempty . reinterpret \case
------------------------------------------------------------------------------
-- | Run an 'Ouput' effect by ignoring it.
-- | Run an 'Output' effect by ignoring it.
runIgnoringOutput :: Sem (Output o ': r) a -> Sem r a
runIgnoringOutput = interpret \case
Output _ -> pure ()