Skip to content

Commit

Permalink
inline functions in unliftio-core
Browse files Browse the repository at this point in the history
GHC probably does this already, but I want to be confident that
they'll disappear for `IO`
  • Loading branch information
bitonic committed Oct 4, 2017
1 parent d265bae commit b87da4c
Showing 1 changed file with 7 additions and 0 deletions.
7 changes: 7 additions & 0 deletions unliftio-core/src/Control/Monad/IO/Unlift.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,12 +62,15 @@ class MonadIO m => MonadUnliftIO m where
-- Would be better, but GHC hates us
-- askUnliftIO :: m (forall a. m a -> IO a)
instance MonadUnliftIO IO where
{-# INLINE askUnliftIO #-}
askUnliftIO = return (UnliftIO id)
instance MonadUnliftIO m => MonadUnliftIO (ReaderT r m) where
{-# INLINE askUnliftIO #-}
askUnliftIO = ReaderT $ \r ->
withUnliftIO $ \u ->
return (UnliftIO (unliftIO u . flip runReaderT r))
instance MonadUnliftIO m => MonadUnliftIO (IdentityT m) where
{-# INLINE askUnliftIO #-}
askUnliftIO = IdentityT $
withUnliftIO $ \u ->
return (UnliftIO (unliftIO u . runIdentityT))
Expand All @@ -78,25 +81,29 @@ instance MonadUnliftIO m => MonadUnliftIO (IdentityT m) where
-- convenient.
--
-- @since 0.1.0.0
{-# INLINE askRunIO #-}
askRunInIO :: MonadUnliftIO m => m (m a -> IO a)
askRunInIO = liftM unliftIO askUnliftIO

-- | Convenience function for capturing the monadic context and running
-- an 'IO' action.
--
-- @since 0.1.0.0
{-# INLINE withUnliftIO #-}
withUnliftIO :: MonadUnliftIO m => (UnliftIO m -> IO a) -> m a
withUnliftIO inner = askUnliftIO >>= liftIO . inner

-- | Same as 'withUnliftIO', but uses a monomorphic function like
-- 'askRunInIO'.
--
-- @since 0.1.0.0
{-# INLINE withRunInIO #-}
withRunInIO :: MonadUnliftIO m => ((m a -> IO a) -> IO b) -> m b
withRunInIO inner = askRunInIO >>= liftIO . inner

-- | Convert an action in @m@ to an action in @IO@.
--
-- @since 0.1.0.0
{-# INLINE toIO #-}
toIO :: MonadUnliftIO m => m a -> m (IO a)
toIO m = withRunInIO $ \run -> return $ run m

0 comments on commit b87da4c

Please sign in to comment.