Release polysemy 0.2.1.0

This commit is contained in:
Sandy Maguire 2019-05-27 01:16:14 -04:00
parent aefb1deef0
commit ad42c75fcf
7 changed files with 55 additions and 5 deletions

View File

@ -59,7 +59,7 @@ Or by adding `-fplugin=Polysemy.Plugin` to your package.yaml/.cabal file `ghc-op
<sup><a name="fn1">1</a></sup>: Unfortunately this is not true in GHC 8.6.3, but
will be true as soon as [my patch](https://gitlab.haskell.org/ghc/ghc/merge_requests/668/) lands.
will be true in GHC 8.10.1.
## Examples

View File

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

View File

@ -1,5 +1,11 @@
# Changelog for polysemy-plugin
## 0.2.1.0 (2019-05-27)
- Fixed a bug in the `Alternative` instance for `Sem`, where it would choose the
*last* success instead of the first
- Added `MonadPlus` and `MonadFail` instances for `Sem`
## 0.2.0.0 (2019-05-23)
- Fixed a serious bug where the changes from 0.1.0.1 broke most real-world

View File

@ -4,10 +4,10 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 9a2044113434528f0539fb410b356387676cc468eefb618a666c1246379b43da
-- hash: d24941def9c13073c8c65e68d2cb76cddd1df3fad645148e5dfffa914a749250
name: polysemy
version: 0.2.0.0
version: 0.2.1.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
@ -88,6 +88,7 @@ test-suite polysemy-test
type: exitcode-stdio-1.0
main-is: Main.hs
other-modules:
AlternativeSpec
FusionSpec
HigherOrderSpec
OutputSpec

View File

@ -27,6 +27,8 @@ module Polysemy.Internal
) where
import Control.Applicative
import Control.Monad
import Control.Monad.Fail
import Control.Monad.Fix
import Control.Monad.IO.Class
import Data.Functor.Identity
@ -216,6 +218,13 @@ instance (Member NonDet r) => Alternative (Sem r) where
True -> b
{-# INLINE (<|>) #-}
instance (Member NonDet r) => MonadPlus (Sem r) where
mzero = empty
mplus = (<|>)
instance (Member NonDet r) => MonadFail (Sem r) where
fail = const empty
------------------------------------------------------------------------------
-- | This instance will only lift 'IO' actions. If you want to lift into some

View File

@ -62,6 +62,6 @@ runNonDet (Sem m) = Sem $ \k -> runNonDetC $ m $ \u ->
foldr cons nil z
Right (Yo Empty _ _ _) -> empty
Right (Yo (Choose ek) s _ y) -> do
z <- pure (ek True) <|> pure (ek False)
z <- pure (ek False) <|> pure (ek True)
pure $ y $ z <$ s

34
test/AlternativeSpec.hs Normal file
View File

@ -0,0 +1,34 @@
module AlternativeSpec where
import Polysemy
import Polysemy.NonDet
import Test.Hspec
import Control.Applicative
semFail :: Member NonDet r => Maybe Bool -> Sem r Bool
semFail mb = do
Just b <- pure mb
pure b
runAlt :: Alternative f => Sem '[NonDet] a -> f a
runAlt = run . runNonDet
spec :: Spec
spec = do
describe "Alternative instance" $ do
it "should choose the first branch" $ do
runAlt (pure '1' <|> pure '2') `shouldBe` (Just '1')
it "should failover" $ do
runAlt (empty <|> pure '2') `shouldBe` (Just '2')
runAlt (pure '1' <|> empty) `shouldBe` (Just '1')
describe "MonadFail instance" $ do
it "should call empty via fail" $ do
runAlt (semFail Nothing) `shouldBe` Nothing
runAlt (semFail Nothing) `shouldBe` []
it "should work fine for non-failing patterns" $ do
runAlt (semFail $ Just True) `shouldBe` Just True
runAlt (semFail $ Just False) `shouldBe` [False]