Skip to content

Commit

Permalink
beauty salon
Browse files Browse the repository at this point in the history
  • Loading branch information
HeinrichApfelmus committed Aug 18, 2021
1 parent 3f9513b commit c9d0f28
Show file tree
Hide file tree
Showing 4 changed files with 10 additions and 7 deletions.
2 changes: 2 additions & 0 deletions lib/core/src/Cardano/Wallet/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,8 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

{- HLINT ignore "Use newtype instead of data" -}

module Cardano.Wallet.Api
( -- * API
Api
Expand Down
2 changes: 1 addition & 1 deletion lib/core/src/Cardano/Wallet/Api/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -180,8 +180,8 @@ import Cardano.Wallet.Api
, WalletLock (..)
, dbFactory
, tokenMetadataClient
, workerRegistry
, walletLocks
, workerRegistry
)
import Cardano.Wallet.Api.Server.Tls
( TlsConfiguration (..), requireClientAuth )
Expand Down
3 changes: 3 additions & 0 deletions lib/core/src/Control/Concurrent/Concierge.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}

{- HLINT ignore "Use newtype instead of data" -}

-- |
-- Copyright: © 2021 IOHK
-- License: Apache-2.0
Expand Down
10 changes: 4 additions & 6 deletions lib/core/test/unit/Control/Concurrent/ConciergeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,9 +22,7 @@ import Control.Monad.Trans.Except
import Test.Hspec
( Spec, describe, it, parallel )
import Test.QuickCheck
( Property
, (===)
)
( Property, (===) )

spec :: Spec
spec = do
Expand Down Expand Up @@ -55,7 +53,7 @@ unit_atomic =

test :: (forall a. IOSim s a -> IOSim s a) -> IOSim s ()
test atomically = do
_ <- forkIO $ atomically $ (delay 1 >> action "B")
_ <- forkIO $ atomically (delay 1 >> action "B")
atomically $ action "A"
delay 4

Expand All @@ -68,14 +66,14 @@ unit_atomic =
-- | Check that using 'throwE' in the 'ExceptE' monad releases the lock
unit_exceptT_release_lock :: Property
unit_exceptT_release_lock =
["A"] === (selectTraceEventsSay $ runSimTrace $ runExceptT test)
["A"] === selectTraceEventsSay (runSimTrace $ runExceptT test)
where
liftE :: IOSim s a -> ExceptT String (IOSim s) a
liftE = lift

test :: ExceptT String (IOSim s) ()
test = do
concierge <- liftE $ newConcierge
concierge <- liftE newConcierge
let atomically = atomicallyWithLifted liftE concierge ()
_ <- tryE $ atomically $ throwE "X"
atomically $ liftE $ say "A"
Expand Down

0 comments on commit c9d0f28

Please sign in to comment.