Skip to content

Commit 522e448

Browse files
committed
Fresh: m clean-up
1 parent 1bbf87b commit 522e448

File tree

1 file changed

+21
-9
lines changed

1 file changed

+21
-9
lines changed

src/Nix/Fresh.hs

Lines changed: 21 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,8 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE DeriveFunctor #-}
3-
{-# LANGUAGE FlexibleContexts #-}
43
{-# LANGUAGE FlexibleInstances #-}
54
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
65
{-# LANGUAGE MultiParamTypeClasses #-}
7-
{-# LANGUAGE RankNTypes #-}
86
{-# LANGUAGE TypeFamilies #-}
97
{-# LANGUAGE UndecidableInstances #-}
108

@@ -13,21 +11,35 @@
1311

1412
module Nix.Fresh where
1513

16-
import Control.Applicative
17-
import Control.Monad.Base
18-
import Control.Monad.Catch
14+
import Control.Applicative ( Alternative )
15+
import Control.Monad.Base ( MonadBase(..) )
16+
import Control.Monad.Catch ( MonadCatch
17+
, MonadMask
18+
, MonadThrow
19+
)
1920
import Control.Monad.Except
21+
( MonadFix
22+
, MonadIO
23+
, MonadPlus
24+
, MonadTrans(..)
25+
)
2026
#if !MIN_VERSION_base(4,13,0)
2127
import Control.Monad.Fail
2228
#endif
23-
import Control.Monad.Reader
29+
import Control.Monad.Reader ( ReaderT(..)
30+
, MonadReader(ask)
31+
)
2432
import Control.Monad.Ref
25-
import Control.Monad.ST
26-
import Data.Typeable
33+
( MonadAtomicRef(..)
34+
, MonadRef(writeRef, readRef)
35+
)
36+
import Control.Monad.ST ( ST )
37+
import Data.Typeable ( Typeable )
2738

2839
import Nix.Var
2940
import Nix.Thunk
3041

42+
3143
newtype FreshIdT i m a = FreshIdT { unFreshIdT :: ReaderT (Var m i) m a }
3244
deriving
3345
( Functor
@@ -72,7 +84,7 @@ runFreshIdT i m = runReaderT (unFreshIdT m) i
7284
-- Orphan instance needed by Infer.hs and Lint.hs
7385

7486
-- Since there's no forking, it's automatically atomic.
75-
-- NOTE: MonadAtomicRef (ST s) can be upstreamed to `ref-tf`
87+
-- 2021-02-09: NOTE: Submitted upstream: https://github.com/mainland/ref-tf/pull/4
7688
instance MonadAtomicRef (ST s) where
7789
atomicModifyRef r f = do
7890
v <- readRef r

0 commit comments

Comments
 (0)