File: Lifted.hs

package info (click to toggle)
haskell-lifted-base 0.2.3.12-6
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 144 kB
  • sloc: haskell: 982; ansic: 3; makefile: 3
file content (108 lines) | stat: -rw-r--r-- 3,195 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
{-# LANGUAGE CPP #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-}

#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#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
#if MIN_VERSION_base(4,6,0)
    , modifyIORef'
#endif
    , atomicModifyIORef
#if MIN_VERSION_base(4,6,0)
    , atomicModifyIORef'
    , atomicWriteIORef
#endif
    , mkWeakIORef
    ) where

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

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

-- 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 #-}

#if MIN_VERSION_base(4,6,0)
-- | 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.atomicWriteIORef'.
atomicWriteIORef :: MonadBase IO m => IORef a -> a -> m ()
atomicWriteIORef r = liftBase . R.atomicWriteIORef r
#endif

-- | 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 #-}