Skip to content

Commit

Permalink
Added Data.IORef.Lifted
Browse files Browse the repository at this point in the history
  • Loading branch information
liyang committed Aug 15, 2012
1 parent 01c9841 commit 37352e1
Show file tree
Hide file tree
Showing 2 changed files with 90 additions and 0 deletions.
89 changes: 89 additions & 0 deletions Data/IORef/Lifted.hs
@@ -0,0 +1,89 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-}

#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif

{- |
Module : Data.IORef
Copyright : Liyang HU, Bas van Dijk
License : BSD-style
Maintainer : Bas van Dijk <v.dijk.bas@gmail.com>
Stability : experimental
This is a wrapped version of "Data.IORef" with types
generalised from 'IO' to all monads in 'MonadBase'.
-}

module Data.IORef.Lifted
( IORef
, newIORef
, readIORef
, writeIORef
, modifyIORef
, atomicModifyIORef
, mkWeakIORef
) where

--------------------------------------------------------------------------------
-- Imports
--------------------------------------------------------------------------------

-- from base:
import Data.IORef ( IORef )
import qualified Data.IORef as R
import System.IO ( IO )
import System.Mem.Weak ( Weak )

-- from base-unicode-symbols:
import Data.Function.Unicode ( (∘) )

-- from transformers-base:
import Control.Monad.Base ( MonadBase, liftBase )

-- from monad-control:
import Control.Monad.Trans.Control ( MonadBaseControl, liftBaseDiscard )

#include "inlinable.h"

--------------------------------------------------------------------------------
-- * IORefs
--------------------------------------------------------------------------------

-- | Generalized version of 'R.newIORef'.
newIORef MonadBase IO m a m (IORef a)
newIORef = liftBase R.newIORef
{-# INLINABLE newIORef #-}

-- | Generalized version of 'R.readIORef'.
readIORef MonadBase IO m IORef a m a
readIORef = liftBase R.readIORef
{-# INLINABLE readIORef #-}

-- | Generalized version of 'R.writeIORef'.
writeIORef MonadBase IO m IORef a a m ()
writeIORef r = liftBase R.writeIORef r
{-# INLINABLE writeIORef #-}

-- | Generalized version of 'R.modifyIORef'.
modifyIORef MonadBase IO m IORef a (a a) m ()
modifyIORef r = liftBase R.modifyIORef r
{-# INLINABLE modifyIORef #-}

-- | Generalized version of 'R.atomicModifyIORef'.
atomicModifyIORef MonadBase IO m IORef a (a (a, b)) m b
atomicModifyIORef r = liftBase R.atomicModifyIORef r
{-# INLINABLE atomicModifyIORef #-}

-- | Generalized version of 'R.mkWeakIORef'.
--
-- Note any monadic side effects in @m@ of the \"finalizer\" computation
-- are discarded.
mkWeakIORef MonadBaseControl IO m IORef a m () m (Weak (IORef a))
mkWeakIORef = liftBaseDiscard R.mkWeakIORef
{-# INLINABLE mkWeakIORef #-}

1 change: 1 addition & 0 deletions lifted-base.cabal
Expand Up @@ -41,6 +41,7 @@ Library
Control.Concurrent.QSemN.Lifted
Control.Concurrent.SampleVar.Lifted
Control.Concurrent.Lifted
Data.IORef.Lifted
System.Timeout.Lifted

Build-depends: base >= 3 && < 4.7
Expand Down

0 comments on commit 37352e1

Please sign in to comment.