Skip to content

Commit 9c1dd44

Browse files
committed
Value: tiny refactor
1 parent 6a15a08 commit 9c1dd44

File tree

1 file changed

+23
-15
lines changed

1 file changed

+23
-15
lines changed

src/Nix/Value.hs

Lines changed: 23 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@
1818

1919
module Nix.Value where
2020

21+
import Data.Bool ( bool )
2122
import Control.Comonad ( Comonad, extract )
2223
import Control.Exception ( Exception )
2324
import Control.Monad ( (<=<) )
@@ -83,14 +84,17 @@ instance Foldable (NValueF p m) where
8384
NVBuiltinF _ _ -> mempty
8485

8586
instance Show r => Show (NValueF p m r) where
86-
showsPrec = flip go where
87-
go (NVConstantF atom ) = showsCon1 "NVConstant" atom
88-
go (NVStrF ns ) = showsCon1 "NVStr" (stringIgnoreContext ns)
89-
go (NVListF lst ) = showsCon1 "NVList" lst
90-
go (NVSetF attrs _) = showsCon1 "NVSet" attrs
91-
go (NVClosureF p _) = showsCon1 "NVClosure" p
92-
go (NVPathF p ) = showsCon1 "NVPath" p
93-
go (NVBuiltinF name _ ) = showsCon1 "NVBuiltin" name
87+
showsPrec = flip go
88+
where
89+
go :: NValueF p m r -> Int -> String -> String
90+
go = \case
91+
(NVConstantF atom ) -> showsCon1 "NVConstant" atom
92+
(NVStrF ns ) -> showsCon1 "NVStr" (stringIgnoreContext ns)
93+
(NVListF lst ) -> showsCon1 "NVList" lst
94+
(NVSetF attrs _ ) -> showsCon1 "NVSet" attrs
95+
(NVClosureF params _ ) -> showsCon1 "NVClosure" params
96+
(NVPathF path ) -> showsCon1 "NVPath" path
97+
(NVBuiltinF name _ ) -> showsCon1 "NVBuiltin" name
9498

9599
showsCon1 :: Show a => String -> a -> Int -> String -> String
96100
showsCon1 con a d =
@@ -208,7 +212,7 @@ hoistNValue'
208212
-> NValue' t f m a
209213
-> NValue' t f n a
210214
hoistNValue' run lft (NValue v) =
211-
NValue (fmap (lmapNValueF (hoistNValue lft run) . hoistNValueF lft) v)
215+
NValue $ lmapNValueF (hoistNValue lft run) . hoistNValueF lft <$> v
212216

213217
liftNValue'
214218
:: (MonadTrans u, Monad m, Functor (u m), Functor f)
@@ -219,10 +223,10 @@ liftNValue' run = hoistNValue' run lift
219223

220224
unliftNValue'
221225
:: (MonadTrans u, Monad m, Functor (u m), Functor f)
222-
=> (forall x . u m x -> m x)
226+
=> (forall x . u m x -> m x) -- aka "run"
223227
-> NValue' t f (u m) a
224228
-> NValue' t f m a
225-
unliftNValue' run = hoistNValue' lift run
229+
unliftNValue' = hoistNValue' lift
226230

227231
iterNValue'
228232
:: forall t f m a r
@@ -261,10 +265,10 @@ liftNValue run = hoistNValue run lift
261265

262266
unliftNValue
263267
:: (MonadTrans u, Monad m, Functor (u m), Functor f)
264-
=> (forall x . u m x -> m x)
268+
=> (forall x . u m x -> m x) -- aka "run"
265269
-> NValue t f (u m)
266270
-> NValue t f m
267-
unliftNValue run = hoistNValue lift run
271+
unliftNValue = hoistNValue lift
268272

269273
iterNValue
270274
:: forall t f m r
@@ -406,8 +410,12 @@ valueType = \case
406410
NFloat _ -> TFloat
407411
NBool _ -> TBool
408412
NNull -> TNull
409-
NVStrF ns | stringHasContext ns -> TString HasContext
410-
| otherwise -> TString NoContext
413+
NVStrF ns ->
414+
TString $
415+
bool
416+
NoContext
417+
HasContext
418+
$ stringHasContext ns
411419
NVListF{} -> TList
412420
NVSetF{} -> TSet
413421
NVClosureF{} -> TClosure

0 commit comments

Comments
 (0)