Skip to content

Commit

Permalink
Don't use polysemy-plugin, remove IdempotentLoweringSpec (#66)
Browse files Browse the repository at this point in the history
  • Loading branch information
KingoftheHomeless authored Sep 28, 2020
1 parent 57c6012 commit ac99fdc
Show file tree
Hide file tree
Showing 16 changed files with 69 additions and 95 deletions.
13 changes: 7 additions & 6 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -21,25 +21,23 @@ description: Please see the README on GitHub at <https://github.com/isov

dependencies:
- base >= 4.9 && < 5
- constraints >= 0.10.1 && < 0.12
- constraints >= 0.10.1 && < 0.13
- containers >= 0.5 && < 0.7
- contravariant < 2
- exceptions >= 0.10.0 && < 0.11
- mtl >= 2.0.1.0 && < 3.0.0.0
- polysemy >= 1.2.1.0
- polysemy-plugin >= 0.2
- random >= 1.1 && <1.2
- random >= 1.1 && < 1.3
- reflection >= 2.1.4 && < 3.0.0
- transformers >= 0.5.2.0 && < 0.6
- text >= 1.1.0 && < 1.3
- ghc-prim >= 0.5.2 && < 0.6
- ghc-prim >= 0.5.2 && < 0.7
- async >= 2.2 && < 3
- streaming
- streaming >= 0.2 && < 0.3
- compact >= 0.1.0.1


ghc-options:
- -fplugin=Polysemy.Plugin
- -Wall

# # Enable these when building haddock
Expand Down Expand Up @@ -72,9 +70,12 @@ tests:
- -threaded
- -rtsopts
- -with-rtsopts=-N
- -fplugin=Polysemy.Plugin
build-tools:
- hspec-discover >= 2.0
dependencies:
- polysemy >= 1.2.0.0
- polysemy-plugin >= 0.2
- exceptions >= 0.10.0 && < 0.11
- polysemy-zoo
- hspec >= 2.6.0 && < 3
26 changes: 12 additions & 14 deletions polysemy-zoo.cabal
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
cabal-version: 1.12

-- This file has been generated from package.yaml by hpack version 0.31.2.
-- This file has been generated from package.yaml by hpack version 0.33.0.
--
-- see: https://github.com/sol/hpack
--
-- hash: 3ca3f0fd7140b4210529e77e057687ebd67bb4477155611458e964afa5cdc192
-- hash: 10effff79a5ce4ecbb0f9ab6f98d553ff063aebf33c62472e65323daa15daca2

name: polysemy-zoo
version: 0.7.0.0
Expand Down Expand Up @@ -64,22 +64,21 @@ library
hs-source-dirs:
src
default-extensions: DataKinds DeriveFunctor FlexibleContexts GADTs LambdaCase PolyKinds RankNTypes ScopedTypeVariables StandaloneDeriving TypeApplications TypeOperators TypeFamilies UnicodeSyntax
ghc-options: -fplugin=Polysemy.Plugin -Wall
ghc-options: -Wall
build-depends:
async >=2.2 && <3
, base >=4.9 && <5
, compact >=0.1.0.1
, constraints >=0.10.1 && <0.12
, constraints >=0.10.1 && <0.13
, containers >=0.5 && <0.7
, contravariant <2
, exceptions >=0.10.0 && <0.11
, ghc-prim >=0.5.2 && <0.6
, ghc-prim >=0.5.2 && <0.7
, mtl >=2.0.1.0 && <3.0.0.0
, polysemy >=1.2.1.0
, polysemy-plugin >=0.2
, random >=1.1 && <1.2
, random >=1.1 && <1.3
, reflection >=2.1.4 && <3.0.0
, streaming
, streaming >=0.2 && <0.3
, text >=1.1.0 && <1.3
, transformers >=0.5.2.0 && <0.6
default-language: Haskell2010
Expand All @@ -93,7 +92,6 @@ test-suite polysemy-zoo-test
ContSpec
FinalSpec
FloodgateSpec
IdempotentLoweringSpec
KVStoreSpec
RevStateSpec
SeveralSpec
Expand All @@ -102,26 +100,26 @@ test-suite polysemy-zoo-test
hs-source-dirs:
test
default-extensions: DataKinds DeriveFunctor FlexibleContexts GADTs LambdaCase PolyKinds RankNTypes ScopedTypeVariables StandaloneDeriving TypeApplications TypeOperators TypeFamilies UnicodeSyntax
ghc-options: -fplugin=Polysemy.Plugin -Wall -threaded -rtsopts -with-rtsopts=-N
ghc-options: -Wall -threaded -rtsopts -with-rtsopts=-N -fplugin=Polysemy.Plugin
build-tool-depends:
hspec-discover:hspec-discover >=2.0
build-depends:
async >=2.2 && <3
, base >=4.9 && <5
, compact >=0.1.0.1
, constraints >=0.10.1 && <0.12
, constraints >=0.10.1 && <0.13
, containers >=0.5 && <0.7
, contravariant <2
, exceptions >=0.10.0 && <0.11
, ghc-prim >=0.5.2 && <0.6
, ghc-prim >=0.5.2 && <0.7
, hspec >=2.6.0 && <3
, mtl >=2.0.1.0 && <3.0.0.0
, polysemy >=1.2.0.0
, polysemy-plugin >=0.2
, polysemy-zoo
, random >=1.1 && <1.2
, random >=1.1 && <1.3
, reflection >=2.1.4 && <3.0.0
, streaming
, streaming >=0.2 && <0.3
, text >=1.1.0 && <1.3
, transformers >=0.5.2.0 && <0.6
default-language: Haskell2010
7 changes: 4 additions & 3 deletions src/Polysemy/Capture.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell, Trustworthy #-}
{-# LANGUAGE AllowAmbiguousTypes, TemplateHaskell, Trustworthy #-}
module Polysemy.Capture
(-- * Effect
Capture(..)
Expand Down Expand Up @@ -92,10 +92,11 @@ delimit' :: forall ref a r
-- which case such failure may be detected by using 'delimit'' together
-- with the provided continuation (the provided continuation
-- is already delimited).
capture :: Member (Capture ref) r
capture :: forall ref r a
. Member (Capture ref) r
=> (forall s. (a -> Sem r s) -> Sem r s)
-> Sem r a
capture cc = reify (\ref -> cc (reflect ref))
capture cc = reify @ref (\ref -> cc (reflect ref))
{-# INLINE capture #-}

-----------------------------------------------------------------------------
Expand Down
6 changes: 4 additions & 2 deletions src/Polysemy/ConstraintAbsorber/MonadCont.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand All @@ -20,13 +21,14 @@ import Polysemy.Cont
--
-- @since 0.3.0.0
absorbCont
:: Member (Cont ref) r
:: forall ref r a
. Member (Cont ref) r
=> (C.MonadCont (Sem r) => Sem r a)
-- ^ A computation that requires an instance of 'C.MonadCont' for
-- 'Sem'. This might be something with type @'C.MonadCont' m => m a@.
-> Sem r a
absorbCont = absorbWithSem @C.MonadCont @Action
(ContDict callCC)
(ContDict (callCC @ref))
(Sub Dict)
{-# INLINEABLE absorbCont #-}

Expand Down
4 changes: 2 additions & 2 deletions src/Polysemy/Cont.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE AllowAmbiguousTypes, Trustworthy #-}
module Polysemy.Cont
(-- * Effect
Cont(..)
Expand Down Expand Up @@ -56,7 +56,7 @@ callCC :: forall ref r a
. Member (Cont ref) r
=> ((forall b. a -> Sem r b) -> Sem r a)
-> Sem r a
callCC cc = subst (\ref -> cc (jump ref)) pure
callCC cc = subst @ref (\ref -> cc (jump ref)) pure
{-# INLINE callCC #-}

-----------------------------------------------------------------------------
Expand Down
4 changes: 2 additions & 2 deletions src/Polysemy/Cont/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ runContViaFreshInC = usingSem $ \u -> ContT $ \c ->
if ref == ref' then
loop (cn' $ unsafeCoerce a')
else
throw x
throw @(uniq, Any) x
loop $ main' $ ViaFreshRef (\a -> (ref, unsafeCoerce a))
Jump ref a -> throw (getBacktrackException ref a)
Left g -> do
Expand Down Expand Up @@ -218,7 +218,7 @@ runContViaFreshInCWeave = usingSem $ \u -> ContT $ \c ->
if ref == ref' then
loop (cn' $ unsafeCoerce a')
else
throw x
throw @(uniq, Any) x
ResAndHandler res h <-
loop $ main' $ ViaFreshRef (\a -> (ref, unsafeCoerce a))
return $ ResAndHandler res
Expand Down
10 changes: 6 additions & 4 deletions src/Polysemy/EndState.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,20 +30,22 @@ makeSem ''EndState
-----------------------------------------------------------------------------
-- | Runs an 'EndState' effect by getting the state after the computation
-- has finished, and providing it recursively back to calls of 'getEndState'.
runEndState :: (Member (State s) r, Member Fixpoint r)
runEndState :: forall s r a
. (Member (State s) r, Member Fixpoint r)
=> Sem (EndState s ': r) a
-> Sem r a
runEndState =
runReaderFixSem get
runReaderFixSem (get @s)
. reinterpret (\GetEndState -> ask)


-----------------------------------------------------------------------------
-- | Like 'runEndState', but for 'AtomicState' rather than 'State'.
runEndAtomicState
:: (Member (AtomicState s) r, Member Fixpoint r)
:: forall s r a
. (Member (AtomicState s) r, Member Fixpoint r)
=> Sem (EndState s ': r) a
-> Sem r a
runEndAtomicState =
runReaderFixSem atomicGet
runReaderFixSem (atomicGet @s)
. reinterpret (\GetEndState -> ask)
23 changes: 14 additions & 9 deletions src/Polysemy/Final/MTL.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
module Polysemy.Final.MTL
(
module Polysemy.Final
Expand Down Expand Up @@ -25,10 +26,11 @@ import Polysemy.Writer hiding (tell, listen, pass)
-- /Beware/: Effects that aren't interpreted in terms of the final
-- monad will have local state semantics in regards to 'Error' effects
-- interpreted this way. See 'Final'.
errorToFinal :: (Member (Final m) r, MonadError e m)
errorToFinal :: forall m e r a
. (Member (Final m) r, MonadError e m)
=> Sem (Error e ': r) a
-> Sem r a
errorToFinal = interpretFinal $ \case
errorToFinal = interpretFinal @m $ \case
Throw e -> pure $ throwError e
Catch m h -> do
m' <- runS m
Expand All @@ -43,10 +45,11 @@ errorToFinal = interpretFinal $ \case
-- /Beware/: Effects that aren't interpreted in terms of the final
-- monad will have local state semantics in regards to 'Reader' effects
-- interpreted this way. See 'Final'.
readerToFinal :: (Member (Final m) r, MonadReader i m)
readerToFinal :: forall m i r a
. (Member (Final m) r, MonadReader i m)
=> Sem (Reader i ': r) a
-> Sem r a
readerToFinal = interpretFinal $ \case
readerToFinal = interpretFinal @m $ \case
Ask -> liftS ask
Local f m -> do
m' <- runS m
Expand All @@ -64,12 +67,13 @@ readerToFinal = interpretFinal $ \case
-- /Beware/: Effects that aren't interpreted in terms of the embedded
-- monad will have local state semantics in regards to 'State' effects
-- interpreted this way. See 'Final'.
stateToEmbed :: (Member (Embed m) r, MonadState s m)
stateToEmbed :: forall m s r a
. (Member (Embed m) r, MonadState s m)
=> Sem (State s ': r) a
-> Sem r a
stateToEmbed = interpret $ \case
Get -> embed get
Put s -> embed (put s)
Get -> embed @m get
Put s -> embed @m (put s)
{-# INLINE stateToEmbed #-}

-----------------------------------------------------------------------------
Expand All @@ -78,10 +82,11 @@ stateToEmbed = interpret $ \case
-- /Beware/: Effects that aren't interpreted in terms of the final
-- monad will have local state semantics in regards to 'Writer' effects
-- interpreted this way. See 'Final'.
writerToFinal :: (Member (Final m) r, MonadWriter o m)
writerToFinal :: forall m o r a
. (Member (Final m) r, MonadWriter o m)
=> Sem (Writer o ': r) a
-> Sem r a
writerToFinal = interpretFinal $ \case
writerToFinal = interpretFinal @m $ \case
Tell s -> liftS (tell s)
Listen m -> do
m' <- runS m
Expand Down
6 changes: 4 additions & 2 deletions src/Polysemy/Final/NonDet.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
module Polysemy.Final.NonDet
(
module Polysemy.NonDet
Expand All @@ -16,10 +17,11 @@ import Polysemy.Final
-- /Beware/: Effects that aren't interpreted in terms of the final
-- monad will have local state semantics in regards to 'NonDet' effects
-- interpreted this way. See 'Final'.
nonDetToFinal :: (Member (Final m) r, Alternative m)
nonDetToFinal :: forall m r a
. (Member (Final m) r, Alternative m)
=> Sem (NonDet ': r) a
-> Sem r a
nonDetToFinal = interpretFinal $ \case
nonDetToFinal = interpretFinal @m $ \case
Empty -> pure empty
Choose left right -> do
left' <- runS left
Expand Down
2 changes: 1 addition & 1 deletion src/Polysemy/Floodgate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ runFloodgate = fmap snd . runState @[Any] [] . reinterpretH
getInitialStateT

Release -> do
ms' <- gets (fmap unsafeCoerce . reverse)
ms' <- gets @[Any] (fmap unsafeCoerce . reverse)
sequence_ ms'
getInitialStateT
)
Expand Down
10 changes: 5 additions & 5 deletions src/Polysemy/KVStore.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE AllowAmbiguousTypes, TemplateHaskell #-}

module Polysemy.KVStore
( -- * Effect
Expand Down Expand Up @@ -40,8 +40,8 @@ writeKV k = updateKV k . Just
{-# INLINE writeKV #-}


deleteKV :: Member (KVStore k v) r => k -> Sem r ()
deleteKV k = updateKV k Nothing
deleteKV :: forall k v r. Member (KVStore k v) r => k -> Sem r ()
deleteKV k = updateKV k (Nothing @v)
{-# INLINE deleteKV #-}


Expand All @@ -64,8 +64,8 @@ lookupOrThrowKV f k =
-- |
--
-- @since 0.3.1.0
existsKV :: Member (KVStore k v) r => k -> Sem r Bool
existsKV = fmap isJust . lookupKV
existsKV :: forall k v r. Member (KVStore k v) r => k -> Sem r Bool
existsKV = fmap isJust . lookupKV @k @v


------------------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion src/Polysemy/Random.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ runRandom q = runState q . reinterpret (\case
-- | Run a 'Random' effect by using the 'IO' random generator.
runRandomIO :: Member (Embed IO) r => Sem (Random ': r) a -> Sem r a
runRandomIO m = do
q <- embed R.newStdGen
q <- embed @IO R.newStdGen
snd <$> runRandom q m
{-# INLINE runRandomIO #-}

7 changes: 4 additions & 3 deletions src/Polysemy/Shift.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE AllowAmbiguousTypes, Trustworthy #-}
module Polysemy.Shift
(
module Polysemy.Cont
Expand Down Expand Up @@ -62,10 +62,11 @@ import Polysemy.Internal.Union
-- It may sometimes become necessary to handle such cases, in
-- which case such failure may be detected by using 'reset\'' together
-- with the provided continuation.
shift :: Member (Shift ref s) r
shift :: forall ref s r a
. Member (Shift ref s) r
=> ((a -> Sem r s) -> Sem r s)
-> Sem r a
shift cc = trap $ \ref -> cc (invoke ref)
shift cc = trap @ref $ \ref -> cc (invoke ref)
{-# INLINE shift #-}

-----------------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion src/Polysemy/Shift/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE AllowAmbiguousTypes, TemplateHaskell #-}
module Polysemy.Shift.Internal where

import Polysemy
Expand Down
4 changes: 2 additions & 2 deletions stack.yaml.lock
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,10 @@

packages:
- completed:
hackage: polysemy-1.2.3.0@sha256:d9cfa7942940c7c6d07d1f26ae70c4f1170f9bd6c331bdbe586e810fafc25f17,5878
hackage: polysemy-1.2.3.0@sha256:2345b6b76adc8f91fc88251129deff584cebcd07e952dd66aa512c69949df537,6097
pantry-tree:
size: 3625
sha256: a54b1b565848944e37a5533bd91e91ecb7cdfa21294ba599c13d015d354c4f39
sha256: 8d327bc0dcb178112b933626a33200e8714712a77eb348271fdfbdd326b03fec
original:
hackage: polysemy-1.2.3.0
snapshots:
Expand Down
Loading

0 comments on commit ac99fdc

Please sign in to comment.