2019-06-12 16:36:08 +03:00
|
|
|
module BracketSpec where
|
|
|
|
|
|
|
|
import Polysemy
|
|
|
|
import Polysemy.Error
|
|
|
|
import Polysemy.Output
|
|
|
|
import Polysemy.Resource
|
|
|
|
import Polysemy.State
|
|
|
|
import Polysemy.Trace
|
|
|
|
import Test.Hspec
|
|
|
|
|
|
|
|
|
|
|
|
runTest
|
2019-06-26 07:08:55 +03:00
|
|
|
:: Sem '[Error (), Resource, State [Char], Trace] a
|
2019-06-12 16:36:08 +03:00
|
|
|
-> ([String], ([Char], Either () a))
|
|
|
|
runTest = run
|
2019-06-26 07:08:55 +03:00
|
|
|
. runTraceAsList
|
2019-06-12 16:36:08 +03:00
|
|
|
. runState ""
|
|
|
|
. runResource
|
|
|
|
. runError @()
|
|
|
|
|
2019-06-26 07:08:55 +03:00
|
|
|
runTest2
|
2019-07-11 18:02:26 +03:00
|
|
|
:: Sem '[Error (), Resource, State [Char], Trace, Embed IO] a
|
2019-06-26 07:08:55 +03:00
|
|
|
-> IO ([String], ([Char], Either () a))
|
|
|
|
runTest2 = runM
|
|
|
|
. runTraceAsList
|
|
|
|
. runState ""
|
|
|
|
. runResourceBase
|
|
|
|
. runError @()
|
|
|
|
|
2019-06-12 16:36:08 +03:00
|
|
|
|
|
|
|
spec :: Spec
|
2019-06-16 03:04:11 +03:00
|
|
|
spec = parallel $ do
|
2019-06-12 16:36:08 +03:00
|
|
|
describe "pure bracket" $ do
|
|
|
|
it "persist state and call the finalizer" $ do
|
|
|
|
let (ts, (s, e)) = runTest $ do
|
|
|
|
bracket
|
|
|
|
(put "allocated" >> pure ())
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "finalized"
|
|
|
|
)
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "starting block"
|
|
|
|
_ <- throw ()
|
|
|
|
put "don't get here"
|
|
|
|
)
|
|
|
|
ts `shouldContain` ["allocated"]
|
|
|
|
ts `shouldContain` ["starting block"]
|
|
|
|
s `shouldBe` "finalized"
|
|
|
|
e `shouldBe` Left ()
|
|
|
|
|
|
|
|
describe "pure bracketOnError" $ do
|
|
|
|
it "persist state and call the finalizer if there was an error" $ do
|
|
|
|
let (ts, (s, e)) = runTest $ do
|
|
|
|
bracketOnError
|
|
|
|
(put "allocated" >> pure ())
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "finalized"
|
|
|
|
)
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "starting block"
|
|
|
|
_ <- throw ()
|
|
|
|
put "don't get here"
|
|
|
|
)
|
|
|
|
ts `shouldContain` ["allocated"]
|
|
|
|
ts `shouldContain` ["starting block"]
|
|
|
|
s `shouldBe` "finalized"
|
|
|
|
e `shouldBe` Left ()
|
|
|
|
|
|
|
|
it "should not call the finalizer if there no error" $ do
|
|
|
|
let (ts, (s, e)) = runTest $ do
|
|
|
|
bracketOnError
|
|
|
|
(put "allocated" >> pure ())
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "finalized"
|
|
|
|
)
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "starting block"
|
|
|
|
put "don't get here"
|
|
|
|
)
|
|
|
|
ts `shouldContain` ["allocated"]
|
|
|
|
ts `shouldNotContain` ["starting block"]
|
|
|
|
s `shouldBe` "don't get here"
|
|
|
|
e `shouldBe` Right ()
|
|
|
|
|
2019-06-26 07:08:55 +03:00
|
|
|
|
|
|
|
describe "io dispatched bracket" $ do
|
|
|
|
it "persist state and call the finalizer" $ do
|
|
|
|
(ts, (s, e)) <- runTest2 $ do
|
|
|
|
bracket
|
|
|
|
(put "allocated" >> pure ())
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "finalized"
|
|
|
|
)
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "starting block"
|
|
|
|
_ <- throw ()
|
|
|
|
put "don't get here"
|
|
|
|
)
|
|
|
|
ts `shouldContain` ["allocated"]
|
|
|
|
ts `shouldContain` ["starting block"]
|
|
|
|
s `shouldBe` "finalized"
|
|
|
|
e `shouldBe` Left ()
|
|
|
|
|
|
|
|
it "should not lock when done recursively" $ do
|
|
|
|
(ts, (s, e)) <- runTest2 $ do
|
|
|
|
bracket
|
|
|
|
(put "hello 1")
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
put "finished"
|
|
|
|
)
|
|
|
|
(\() -> do
|
|
|
|
get >>= trace
|
|
|
|
bracket (put "hello 2")
|
|
|
|
(const $ do
|
|
|
|
get >>= trace
|
|
|
|
put "goodbye 2"
|
|
|
|
)
|
|
|
|
(const $ do
|
|
|
|
get >>= trace
|
|
|
|
put "RUNNING"
|
|
|
|
throw ()
|
|
|
|
)
|
|
|
|
-- This doesn't run due to the thrown error above
|
|
|
|
get >>= trace
|
|
|
|
put "goodbye 1"
|
|
|
|
)
|
|
|
|
ts `shouldContain` [ "hello 1"
|
|
|
|
, "hello 2"
|
|
|
|
, "RUNNING"
|
|
|
|
, "goodbye 2"
|
|
|
|
]
|
|
|
|
s `shouldBe` "finished"
|
|
|
|
e `shouldBe` Left ()
|
|
|
|
|