Skip to content

Commit

Permalink
Add util 'modifyM' function for state-monad.
Browse files Browse the repository at this point in the history
  • Loading branch information
KtorZ committed Oct 11, 2021
1 parent 79c0c2f commit f74271f
Showing 1 changed file with 12 additions and 0 deletions.
12 changes: 12 additions & 0 deletions lib/core/src/Cardano/Wallet/Util.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}

-- |
Expand All @@ -22,6 +23,9 @@ module Cardano.Wallet.Util
-- * String formatting
, ShowFmt (..)

-- * StateT
, modifyM

-- * HTTP(S) URIs
, uriToText
, parseURI
Expand All @@ -37,8 +41,12 @@ import Control.Exception
( ErrorCall, displayException )
import Control.Monad.IO.Unlift
( MonadUnliftIO )
import Control.Monad.Trans.Class
( lift )
import Control.Monad.Trans.Except
( runExceptT, throwE )
import Control.Monad.Trans.State.Strict
( StateT, get, put )
import Data.Foldable
( asum )
import Data.Functor.Identity
Expand Down Expand Up @@ -76,6 +84,10 @@ isInternalErrorMsg msg = "INTERNAL ERROR" `isPrefixOf` msg
tina :: HasCallStack => Builder -> [Maybe a] -> a
tina msg = fromMaybe (internalError msg) . asum

-- | Effectfully modify the state of a state-monad transformer stack.
modifyM :: forall m s. (Monad m) => (s -> m s) -> StateT s m ()
modifyM fn = get >>= lift . fn >>= put

-- | Checks whether or not an invariant holds, by applying the given predicate
-- to the given value.
--
Expand Down

0 comments on commit f74271f

Please sign in to comment.