Release polysemy-1.0.0.0

This commit is contained in:
Sandy Maguire 2019-07-24 10:45:42 -04:00
parent d803c81054
commit f2ca91d57d
15 changed files with 95 additions and 33 deletions

View File

@ -1,5 +1,46 @@
# Changelog for polysemy
## 1.0.0.0 (2019-07-24)
### Breaking Changes
- Renamed `Lift` to `Embed` (thanks to @googleson78)
- Renamed `runAsyncInIO` to `lowerAsync`
- Renamed `runAsync` to `asyncToIO`
- Renamed `runBatchOutput` to `runOutputBatched`
- Renamed `runConstInput` to `runInputConst`
- Renamed `runEmbed` to `runEmbedded` (thanks to @googleson78)
- Renamed `runEmbedded` to `lowerEmbedded`
- Renamed `runErrorAsAnother` to `mapError`
- Renamed `runErrorInIO` to `lowerError`
- Renamed `runFoldMapOutput` to `runOutputMonoid`
- Renamed `runIO` to `embedToMonadIO`
- Renamed `runIgnoringOutput` to `ignoreOutput`
- Renamed `runIgnoringTrace` to `ignoreTrace`
- Renamed `runInputAsReader` to `inputToReader`
- Renamed `runListInput` to `runInputList`
- Renamed `runMonadicInput` to `runInputSem`
- Renamed `runOutputAsList` to `runOutputList`
- Renamed `runOutputAsTrace` to `outputToTrace`
- Renamed `runOutputAsWriter` to `outputToWriter`
- Renamed `runResourceBase` to `resourceToIO`
- Renamed `runResourceInIO` to `lowerResource`
- Renamed `runStateInIORef` to `runStateIORef`
- Renamed `runTraceAsList` to `runTraceList`
- Renamed `runTraceAsOutput` to `traceToOutput`
- Renamed `runTraceIO` to `traceToIO`
- Renamed `sendM` to `embed` (thanks to @googleson78)
- The `NonDet` effect will no longer perform effects in untaken branches (thanks to @KingoftheHomeless)
### Other Changes
- Added `evalState` and `evalLazyState`
- Added `runNonDetMaybe` (thanks to @KingoftheHomeless)
- Added `nonDetToMaybe` (thanks to @KingoftheHomeless)
- Haddock documentation for smart constructors generated via `makeSem` will no
longer have weird variable names (thanks to @TheMatten)
## 0.7.0.0 (2019-07-08)
### Breaking Changes

View File

@ -1,5 +1,5 @@
name: polysemy
version: 0.7.0.0
version: 1.0.0.0
github: "isovector/polysemy"
license: BSD3
author: "Sandy Maguire"

View File

@ -4,10 +4,10 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 168b7f25b456d0a92b6c245a91e1acc9c81ef40eaa2893f2eb6a238abd74f7f9
-- hash: f543f8ca2c4f661f0b6702fb6ec6d7db075660d19bf550e50a04e64c56826913
name: polysemy
version: 0.7.0.0
version: 1.0.0.0
synopsis: Higher-order, low-boilerplate, zero-cost free monads.
description: Please see the README on GitHub at <https://github.com/isovector/polysemy#readme>
category: Language

View File

@ -39,7 +39,7 @@ makeSem ''Async
-- Notably, this means that 'Polysemy.State.State' effects will be consistent
-- in the presence of 'Async'.
--
-- @since 0.5.0.0
-- @since 1.0.0.0
asyncToIO
:: LastMember (Embed IO) r
=> Sem (Async ': r) a
@ -61,8 +61,7 @@ asyncToIO m = withLowerToIO $ \lower _ -> lower $
------------------------------------------------------------------------------
-- | Run an 'Async' effect via in terms of 'A.async'.
--
--
-- @since 0.5.0.0
-- @since 1.0.0.0
lowerAsync
:: Member (Embed IO) r
=> (forall x. Sem r x -> IO x)

View File

@ -18,7 +18,7 @@ import Polysemy.Embed.Type (Embed (..))
-- | Given a natural transform from @m1@ to @m2@
-- run a @Embed m1@ effect by transforming it into a @Embed m2@ effect.
--
-- TODO(sandy): @since
-- @since 1.0.0.0
runEmbedded
:: forall m1 m2 r a
. Member (Embed m2) r

View File

@ -30,5 +30,7 @@ import Data.Kind
--
-- Consider using 'Polysemy.Trace.trace' and 'Polysemy.Trace.traceToIO' as
-- a substitute for using 'putStrLn' directly.
--
-- @since 1.0.0.0
newtype Embed m (z :: Type -> Type) a where
Embed :: { unEmbed :: m a } -> Embed m z a

View File

@ -96,7 +96,7 @@ runError (Sem m) = Sem $ \k -> E.runExceptT $ m $ \u ->
-- | Transform one 'Error' into another. This function can be used to aggregate
-- multiple errors into a single type.
--
-- @since 0.2.2.0
-- @since 1.0.0.0
mapError
:: forall e1 e2 r a
. Member (Error e2) r
@ -133,6 +133,8 @@ instance (Typeable e) => X.Exception (WrappedExc e)
------------------------------------------------------------------------------
-- | Run an 'Error' effect as an 'IO' 'X.Exception'. This interpretation is
-- significantly faster than 'runError', at the cost of being less flexible.
--
-- @since 1.0.0.0
lowerError
:: ( Typeable e
, Member (Embed IO) r

View File

@ -2,8 +2,8 @@
module Polysemy.IO
( -- * Interpretations
runIO
, runEmbeddedInIO
embedToMonadIO
, lowerEmbedded
) where
import Control.Monad.IO.Class
@ -14,8 +14,6 @@ import Polysemy.Internal.Union
------------------------------------------------------------------------------
-- | __If you trying to run 'Sem' in 'IO', the function you want is 'runM'.__
--
-- The 'MonadIO' class is conceptually an interpretation of 'IO' to some
-- other monad. This function reifies that intuition, by transforming an 'IO'
-- effect into some other 'MonadIO'.
@ -23,27 +21,28 @@ import Polysemy.Internal.Union
-- This function is especially useful when using the 'MonadIO' instance for
-- 'Sem' instance.
--
-- Make sure to type-apply the desired 'MonadIO' instance when using 'runIO'.
-- Make sure to type-apply the desired 'MonadIO' instance when using
-- 'embedToMonadIO'.
--
-- @since 0.1.1.0
-- @since 1.0.0.0
--
-- ==== Example
--
-- @
-- foo :: PandocIO ()
-- foo = 'runM' . 'runIO' @PandocIO $ do
-- foo = 'runM' . 'embedToMonadIO' @PandocIO $ do
-- 'liftIO' $ putStrLn "hello from polysemy"
-- @
--
runIO
embedToMonadIO
:: forall m r a
. ( MonadIO m
, Member (Embed m) r
)
=> Sem (Embed IO ': r) a
-> Sem r a
runIO = runEmbedded $ liftIO @m
{-# INLINE runIO #-}
embedToMonadIO = runEmbedded $ liftIO @m
{-# INLINE embedToMonadIO #-}
------------------------------------------------------------------------------
@ -53,21 +52,21 @@ runIO = runEmbedded $ liftIO @m
--
-- This function creates a thread, and so should be compiled with @-threaded@.
--
-- TODO(sandy): @since
runEmbeddedInIO
-- @since 1.0.0.0
lowerEmbedded
:: ( MonadIO m
, LastMember (Embed IO) r
)
=> (forall x. m x -> IO x) -- ^ The means of running this monad.
-> Sem (Embed m ': r) a
-> Sem r a
runEmbeddedInIO run_m (Sem m) = withLowerToIO $ \lower _ ->
lowerEmbedded run_m (Sem m) = withLowerToIO $ \lower _ ->
run_m $ m $ \u ->
case decomp u of
Left x -> liftIO
. lower
. liftSem
$ hoist (runEmbeddedInIO run_m) x
$ hoist (lowerEmbedded run_m) x
Right (Weaving (Embed wd) s _ y _) ->
fmap y $ fmap (<$ s) wd

View File

@ -279,7 +279,7 @@ instance (Member NonDet r) => MonadFail (Sem r) where
------------------------------------------------------------------------------
-- | This instance will only lift 'IO' actions. If you want to lift into some
-- other 'MonadIO' type, use this instance, and handle it via the
-- 'Polysemy.IO.runIO' interpretation.
-- 'Polysemy.IO.embedToMonadIO' interpretation.
instance (Member (Embed IO) r) => MonadIO (Sem r) where
liftIO = embed
{-# INLINE liftIO #-}
@ -359,7 +359,7 @@ send = liftSem . inj
------------------------------------------------------------------------------
-- | Embed a monadic action @m@ in 'Sem'.
--
-- TODO(sandy): @since
-- @since 1.0.0.0
embed :: Member (Embed m) r => m a -> Sem r a
embed = send . Embed
{-# INLINE embed #-}

View File

@ -31,6 +31,8 @@ makeSem ''Output
------------------------------------------------------------------------------
-- | Run an 'Output' effect by transforming it into a list of its values.
--
-- @since 1.0.0.0
runOutputList
:: forall o r a
. Sem (Output o ': r) a
@ -43,6 +45,8 @@ runOutputList = fmap (first reverse) . runState [] . reinterpret
------------------------------------------------------------------------------
-- | Run an 'Output' effect by transforming it into a monoid.
--
-- @since 1.0.0.0
runOutputMonoid
:: forall o m r a
. Monoid m
@ -58,6 +62,8 @@ runOutputMonoid f = runState mempty . reinterpret
------------------------------------------------------------------------------
-- | Run an 'Output' effect by ignoring it.
--
-- @since 1.0.0.0
ignoreOutput :: Sem (Output o ': r) a -> Sem r a
ignoreOutput = interpret $ \case
Output _ -> pure ()
@ -71,7 +77,7 @@ ignoreOutput = interpret $ \case
-- If @size@ is 0, this interpretation will not emit anything in the resulting
-- 'Output' effect.
--
-- @since 0.1.2.0
-- @since 1.0.0.0
runOutputBatched
:: forall o r a
. Member (Output [o]) r

View File

@ -47,6 +47,8 @@ runReader i = interpretH $ \case
------------------------------------------------------------------------------
-- | Transform an 'Input' effect into a 'Reader' effect.
--
-- @since 1.0.0.0
inputToReader :: Member (Reader i) r => Sem (Input i ': r) a -> Sem r a
inputToReader = interpret $ \case
Input -> ask

View File

@ -76,9 +76,7 @@ onException act end = bracketOnError (pure ()) (const end) (const act)
------------------------------------------------------------------------------
-- | Run a 'Resource' effect via in terms of 'X.bracket'.
--
-- __Note:__ This function used to be called @runResource@ prior to 0.4.0.0.
--
-- @since 0.4.0.0
-- @since 1.0.0.0
lowerResource
:: r a
. Member (Embed IO) r
@ -113,7 +111,7 @@ lowerResource finish = interpretH $ \case
------------------------------------------------------------------------------
-- | Run a 'Resource' effect purely.
--
-- @since 0.4.0.0
-- @since 1.0.0.0
runResource
:: r a
. Sem (Resource ': r) a
@ -165,7 +163,7 @@ runResource = interpretH $ \case
--
-- This function creates a thread, and so should be compiled with @-threaded@.
--
-- @since 0.5.0.0
-- @since 1.0.0.0
resourceToIO
:: forall r a
. LastMember (Embed IO) r
@ -198,3 +196,4 @@ resourceToIO = interpretH $ \case
(\x -> done (mb x) >> finish)
(done . mc)
{-# INLINE resourceToIO #-}

View File

@ -68,6 +68,8 @@ runState = stateful $ \case
------------------------------------------------------------------------------
-- | Run a 'State' effect with local state.
--
-- @since 1.0.0.0
evalState :: s -> Sem (State s ': r) a -> Sem r a
evalState s = fmap snd . runState s
{-# INLINE evalState #-}
@ -83,6 +85,8 @@ runLazyState = lazilyStateful $ \case
------------------------------------------------------------------------------
-- | Run a 'State' effect with local state, lazily.
--
-- @since 1.0.0.0
evalLazyState :: s -> Sem (State s ': r) a -> Sem r a
evalLazyState s = fmap snd . runLazyState s
{-# INLINE evalLazyState #-}
@ -91,7 +95,7 @@ evalLazyState s = fmap snd . runLazyState s
------------------------------------------------------------------------------
-- | Run a 'State' effect by transforming it into operations over an 'IORef'.
--
-- @since 0.1.2.0
-- @since 1.0.0.0
runStateIORef
:: forall s r a
. Member (Embed IO) r

View File

@ -31,6 +31,8 @@ makeSem ''Trace
------------------------------------------------------------------------------
-- | Run a 'Trace' effect by printing the messages to stdout.
--
-- @since 1.0.0.0
traceToIO :: Member (Embed IO) r => Sem (Trace ': r) a -> Sem r a
traceToIO = interpret $ \case
Trace m -> embed $ putStrLn m
@ -39,6 +41,8 @@ traceToIO = interpret $ \case
------------------------------------------------------------------------------
-- | Run a 'Trace' effect by ignoring all of its messages.
--
-- @since 1.0.0.0
ignoreTrace :: Sem (Trace ': r) a -> Sem r a
ignoreTrace = interpret $ \case
Trace _ -> pure ()
@ -47,6 +51,8 @@ ignoreTrace = interpret $ \case
------------------------------------------------------------------------------
-- | Transform a 'Trace' effect into a 'Output' 'String' effect.
--
-- @since 1.0.0.0
traceToOutput
:: Member (Output String) r
=> Sem (Trace ': r) a
@ -59,7 +65,7 @@ traceToOutput = interpret $ \case
------------------------------------------------------------------------------
-- | Get the result of a 'Trace' effect as a list of 'String's.
--
-- @since 0.5.0.0
-- @since 1.0.0.0
runTraceList
:: Sem (Trace ': r) a
-> Sem r ([String], a)
@ -73,7 +79,7 @@ runTraceList = runOutputList . reinterpret (
------------------------------------------------------------------------------
-- | Transform a 'Trace' effect into a 'Output' 'String' effect.
--
-- @since 0.1.2.0
-- @since 1.0.0.0
outputToTrace
:: ( Show w
, Member Trace r

View File

@ -43,6 +43,8 @@ censor f m = pass (fmap (f ,) m)
------------------------------------------------------------------------------
-- | Transform an 'Output' effect into a 'Writer' effect.
--
-- @since 1.0.0.0
outputToWriter :: Member (Writer o) r => Sem (Output o ': r) a -> Sem r a
outputToWriter = interpret $ \case
Output o -> tell o