@@ -327,14 +327,9 @@ hasKind
327327 . (MonadNix e t f m , FromValue a m (NValue t f m ))
328328 => NValue t f m
329329 -> m (NValue t f m )
330- hasKind nv =
331- do
332- v <- fromValueMay nv
333-
334- toValue $
335- case v of
336- Just (_ :: a ) -> True
337- _ -> False
330+ hasKind =
331+ inHaskMay
332+ (isJust @ a )
338333
339334
340335absolutePathFromValue :: MonadNix e t f m => NValue t f m -> m FilePath
@@ -445,7 +440,7 @@ hasAttrNix x y =
445440 toValue $ M. member key aset
446441
447442hasContextNix :: MonadNix e t f m => NValue t f m -> m (NValue t f m )
448- hasContextNix = toValue . stringHasContext <=< fromValue
443+ hasContextNix = inHask stringHasContext
449444
450445getAttrNix
451446 :: forall e t f m
@@ -483,7 +478,7 @@ unsafeGetAttrPosNix nvX nvY =
483478-- of the list.
484479lengthNix
485480 :: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m )
486- lengthNix = toValue . (length :: [NValue t f m ] -> Int ) <=< fromValue
481+ lengthNix = inHask (length :: [NValue t f m ] -> Int )
487482
488483addNix
489484 :: MonadNix e t f m
@@ -719,8 +714,10 @@ substringNix start len str =
719714attrNamesNix
720715 :: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m )
721716attrNamesNix =
722- (fmap (coerce :: CoerceDeeperToNValue t f m ) . toValue . fmap (makeNixStringWithoutContext . coerce @ VarName @ Text ) . sort . M. keys)
723- <=< fromValue @ (AttrSet (NValue t f m ))
717+ coersion . inHask @ (AttrSet (NValue t f m ))
718+ (fmap (makeNixStringWithoutContext . coerce) . sort . M. keys)
719+ where
720+ coersion = fmap (coerce :: CoerceDeeperToNValue t f m )
724721
725722attrValuesNix
726723 :: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m )
@@ -740,13 +737,13 @@ mapNix
740737 -> NValue t f m
741738 -> m (NValue t f m )
742739mapNix f =
743- toValue <=<
744- traverse
745- (defer @ ( NValue t f m )
740+ inHaskM @ [ NValue t f m ]
741+ ( traverse
742+ (defer
746743 . withFrame Debug (ErrorCall " While applying f in map:\n " )
747744 . callFunc f
748745 )
749- <=< fromValue @ [ NValue t f m ]
746+ )
750747
751748mapAttrsNix
752749 :: forall e t f m
@@ -780,10 +777,10 @@ filterNix
780777 -> NValue t f m
781778 -> m (NValue t f m )
782779filterNix f =
783- toValue <=<
784- filterM
785- (fromValue <=< callFunc f)
786- <=< fromValue
780+ inHaskM
781+ ( filterM fh)
782+ where
783+ fh = fromValue <=< callFunc f
787784
788785catAttrsNix
789786 :: forall e t f m
@@ -798,7 +795,7 @@ catAttrsNix attrName xs =
798795
799796 nvList . catMaybes <$>
800797 traverse
801- (fmap (M. lookup (coerce @ Text @ VarName n) ) . fromValue <=< demand)
798+ (fmap (M. lookup @ VarName $ coerce n ) . fromValue <=< demand)
802799 l
803800
804801baseNameOfNix :: MonadNix e t f m => NValue t f m -> m (NValue t f m )
@@ -822,7 +819,7 @@ bitAndNix x y =
822819 a <- fromValue @ Integer x
823820 b <- fromValue @ Integer y
824821
825- toValue ( a .&. b)
822+ toValue $ a .&. b
826823
827824bitOrNix
828825 :: forall e t f m
@@ -835,7 +832,7 @@ bitOrNix x y =
835832 a <- fromValue @ Integer x
836833 b <- fromValue @ Integer y
837834
838- toValue ( a .|. b)
835+ toValue $ a .|. b
839836
840837bitXorNix
841838 :: forall e t f m
@@ -848,7 +845,7 @@ bitXorNix x y =
848845 a <- fromValue @ Integer x
849846 b <- fromValue @ Integer y
850847
851- toValue ( a `xor` b)
848+ toValue $ a `xor` b
852849
853850builtinsBuiltinNix
854851 :: forall e t f m
@@ -869,9 +866,8 @@ dirOfNix nvdir =
869866-- jww (2018-04-28): This should only be a string argument, and not coerced?
870867unsafeDiscardStringContextNix
871868 :: MonadNix e t f m => NValue t f m -> m (NValue t f m )
872- unsafeDiscardStringContextNix mnv = do
873- ns <- fromValue mnv
874- toValue $ makeNixStringWithoutContext $ stringIgnoreContext ns
869+ unsafeDiscardStringContextNix =
870+ inHask (makeNixStringWithoutContext . stringIgnoreContext)
875871
876872-- | Evaluate `a` to WHNF to collect its topmost effect.
877873seqNix
@@ -895,15 +891,19 @@ elemNix
895891 => NValue t f m
896892 -> NValue t f m
897893 -> m (NValue t f m )
898- elemNix x = toValue <=< anyMNix ( valueEqM x) <=< fromValue
894+ elemNix x = inHaskM ( anyMNix $ valueEqM x)
899895 where
900896 anyMNix :: Monad m => (a -> m Bool ) -> [a ] -> m Bool
901- anyMNix _ [] = pure False
902- anyMNix p (x : xs) =
903- bool
904- (anyMNix p xs)
905- (pure True )
906- =<< p x
897+ anyMNix p xs =
898+ list
899+ (pure False )
900+ (\ (x : xss) ->
901+ bool
902+ (anyMNix p xss)
903+ (pure True )
904+ =<< p x
905+ )
906+ xs
907907
908908elemAtNix
909909 :: MonadNix e t f m
@@ -1278,19 +1278,15 @@ scopedImportNix asetArg pathArg =
12781278
12791279getEnvNix :: MonadNix e t f m => NValue t f m -> m (NValue t f m )
12801280getEnvNix v =
1281- do
1282- s <- fromStringNoContext =<< fromValue v
1283- mres <- getEnvVar s
1284-
1285- toValue $ makeNixStringWithoutContext $
1286- fromMaybe mempty mres
1281+ (toValue . makeNixStringWithoutContext . fromMaybe mempty ) =<< getEnvVar =<< fromStringNoContext =<< fromValue v
12871282
12881283sortNix
12891284 :: MonadNix e t f m
12901285 => NValue t f m
12911286 -> NValue t f m
12921287 -> m (NValue t f m )
1293- sortNix comp = toValue <=< sortByM (cmp comp) <=< fromValue
1288+ sortNix comp =
1289+ inHaskM (sortByM $ cmp comp)
12941290 where
12951291 cmp f a b =
12961292 do
@@ -1337,10 +1333,11 @@ concatWith
13371333 -> NValue t f m
13381334 -> m (NValue t f m )
13391335concatWith f =
1340- toValue . concat <=<
1341- traverse
1342- (fromValue @ [NValue t f m ] <=< f)
1343- <=< fromValue @ [NValue t f m ]
1336+ toValue .
1337+ concat <=<
1338+ traverse
1339+ (fromValue @ [NValue t f m ] <=< f)
1340+ <=< fromValue @ [NValue t f m ]
13441341
13451342-- | Nix function of Haskell:
13461343-- > concat :: [[a]] -> [a]
0 commit comments