-
Notifications
You must be signed in to change notification settings - Fork 73
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
* Add Fail effect * Add inlining to Fail interpreters, make Fail newtype * Hide visibility of Polysemy.Fixpoint.bomb, fix changelog * Revert "Hide visibility of Polysemy.Fixpoint.bomb, fix changelog" This reverts commit 5b043ed. * Move Polysemy.Internal.Fail to Polysemy.Fail.Type. Fixed inconsistency in docs
- Loading branch information
1 parent
e4ad261
commit 26a6d2e
Showing
6 changed files
with
93 additions
and
18 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,55 @@ | ||
{-# LANGUAGE AllowAmbiguousTypes #-} | ||
|
||
module Polysemy.Fail | ||
( -- * Effect | ||
Fail(..) | ||
|
||
-- * Interpretations | ||
, runFail | ||
, failToError | ||
, failToNonDet | ||
, failToEmbed | ||
) where | ||
|
||
import Control.Applicative | ||
import Polysemy | ||
import Polysemy.Fail.Type | ||
import Polysemy.Error | ||
import Polysemy.NonDet | ||
import Control.Monad.Fail as Fail | ||
|
||
------------------------------------------------------------------------------ | ||
-- | Run a 'Fail' effect purely. | ||
runFail :: Sem (Fail ': r) a | ||
-> Sem r (Either String a) | ||
runFail = runError . reinterpret (\(Fail s) -> throw s) | ||
{-# INLINE runFail #-} | ||
|
||
------------------------------------------------------------------------------ | ||
-- | Transform a 'Fail' effect into an @'Error' e@ effect, | ||
-- through providing a function for transforming any failure | ||
-- to an exception. | ||
failToError :: Member (Error e) r | ||
=> (String -> e) | ||
-> Sem (Fail ': r) a | ||
-> Sem r a | ||
failToError f = interpret $ \(Fail s) -> throw (f s) | ||
{-# INLINE failToError #-} | ||
|
||
------------------------------------------------------------------------------ | ||
-- | Transform a 'Fail' effect into a 'NonDet' effect, | ||
-- through mapping any failure to 'empty'. | ||
failToNonDet :: Member NonDet r | ||
=> Sem (Fail ': r) a | ||
-> Sem r a | ||
failToNonDet = interpret $ \(Fail _) -> empty | ||
{-# INLINE failToNonDet #-} | ||
|
||
------------------------------------------------------------------------------ | ||
-- | Run a 'Fail' effect in terms of an underlying 'MonadFail' instance. | ||
failToEmbed :: forall m a r | ||
. (Member (Embed m) r, MonadFail m) | ||
=> Sem (Fail ': r) a | ||
-> Sem r a | ||
failToEmbed = interpret $ \(Fail s) -> embed @m (Fail.fail s) | ||
{-# INLINE failToEmbed #-} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,3 @@ | ||
module Polysemy.Fail.Type where | ||
|
||
newtype Fail m a = Fail String |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,25 @@ | ||
module FailSpec where | ||
|
||
import Polysemy | ||
import Polysemy.Fail | ||
import Polysemy.NonDet | ||
import Test.Hspec | ||
import Control.Applicative | ||
|
||
semFail :: Member Fail r => Maybe Bool -> Sem r Bool | ||
semFail mb = do | ||
Just b <- pure mb | ||
pure b | ||
|
||
runAlt :: Alternative f => Sem '[Fail, NonDet] a -> f a | ||
runAlt = run . runNonDet . failToNonDet | ||
|
||
spec :: Spec | ||
spec = parallel $ do | ||
describe "MonadFail instance with failToNonDet" $ 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] |