Skip to content

Commit

Permalink
io-sim: IOSim's Alternative and MonadPlus instances
Browse files Browse the repository at this point in the history
  • Loading branch information
coot committed Jan 2, 2024
1 parent dd1f489 commit 64cdaf8
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 0 deletions.
2 changes: 2 additions & 0 deletions io-sim/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,8 @@

### Non-breaking changes

* `Alternative` & `MonadPlus` instances for `IOSim`.

## 1.3.1.0

### Non-breaking changes
Expand Down
7 changes: 7 additions & 0 deletions io-sim/src/Control/Monad/IOSim/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

-- Needed for `SimEvent` type.
Expand Down Expand Up @@ -136,6 +137,7 @@ import Control.Monad.IOSimPOR.Types

import qualified System.IO.Error as IO.Error (userError)
import Data.List (intercalate)
import GHC.IO (mkUserError)

{-# ANN module "HLint: ignore Use readTVarIO" #-}
newtype IOSim s a = IOSim { unIOSim :: forall r. (a -> SimA s r) -> SimA s r }
Expand Down Expand Up @@ -287,6 +289,11 @@ instance Fail.MonadFail (IOSim s) where
instance MonadFix (IOSim s) where
mfix f = IOSim $ oneShot $ \k -> Fix f k

instance Alternative (IOSim s) where
empty = throwIO (mkUserError "mzero")
!a <|> b = a `catch` \(_ :: IOError) -> b

instance MonadPlus (IOSim s)

instance Functor (STM s) where
{-# INLINE fmap #-}
Expand Down

0 comments on commit 64cdaf8

Please sign in to comment.