@@ -111,15 +111,15 @@ withNixContext mpath action = do
111111 pushScope (M. singleton " __includes" i) $ pushScopes base $ case mpath of
112112 Nothing -> action
113113 Just path -> do
114- traceM $ " Setting __cur_file = " ++ show path
114+ traceM $ " Setting __cur_file = " <> show path
115115 let ref = nvPath path
116116 pushScope (M. singleton " __cur_file" ref) action
117117
118118builtins :: (MonadNix e t f m , Scoped (NValue t f m ) m )
119119 => m (Scopes m (NValue t f m ))
120120builtins = do
121121 ref <- defer $ flip nvSet M. empty <$> buildMap
122- lst <- ([(" builtins" , ref)] ++ ) <$> topLevelBuiltins
122+ lst <- ([(" builtins" , ref)] <> ) <$> topLevelBuiltins
123123 pushScope (M. fromList lst) currentScopes
124124 where
125125 buildMap = M. fromList . fmap mapping <$> builtinsList
@@ -260,7 +260,7 @@ builtinsList = sequence
260260
261261 mkThunk n = defer . withFrame
262262 Info
263- (ErrorCall $ " While calling builtin " ++ Text. unpack n ++ " \n " )
263+ (ErrorCall $ " While calling builtin " <> Text. unpack n <> " \n " )
264264
265265 add0 t n v = wrap t n <$> mkThunk n v
266266 add t n v = wrap t n <$> mkThunk n (builtin (Text. unpack n) v)
@@ -323,17 +323,17 @@ foldNixPath f z = do
323323 dataDir <- maybe getDataDir pure mDataDir
324324 foldrM go z
325325 $ fmap (fromInclude . stringIgnoreContext) dirs
326- ++ case mPath of
326+ <> case mPath of
327327 Nothing -> []
328328 Just str -> uriAwareSplit (Text. pack str)
329- ++ [ fromInclude $ Text. pack $ " nix=" ++ dataDir ++ " /nix/corepkgs" ]
329+ <> [ fromInclude $ Text. pack $ " nix=" <> dataDir <> " /nix/corepkgs" ]
330330 where
331331 fromInclude x | " ://" `Text.isInfixOf` x = (x, PathEntryURI )
332332 | otherwise = (x, PathEntryPath )
333333 go (x, ty) rest = case Text. splitOn " =" x of
334334 [p] -> f (Text. unpack p) Nothing ty rest
335335 [n, p] -> f (Text. unpack p) (Just (Text. unpack n)) ty rest
336- _ -> throwError $ ErrorCall $ " Unexpected entry in NIX_PATH: " ++ show x
336+ _ -> throwError $ ErrorCall $ " Unexpected entry in NIX_PATH: " <> show x
337337
338338nixPath :: MonadNix e t f m => m (NValue t f m )
339339nixPath = fmap nvList $ flip foldNixPath [] $ \ p mn ty rest ->
@@ -371,7 +371,7 @@ attrsetGet :: MonadNix e t f m => Text -> AttrSet (NValue t f m) -> m (NValue t
371371attrsetGet k s = case M. lookup k s of
372372 Just v -> pure v
373373 Nothing ->
374- throwError $ ErrorCall $ " Attribute '" ++ Text. unpack k ++ " ' required"
374+ throwError $ ErrorCall $ " Attribute '" <> Text. unpack k <> " ' required"
375375
376376hasContext :: MonadNix e t f m => NValue t f m -> m (NValue t f m )
377377hasContext = toValue . stringHasContext <=< fromValue
@@ -401,7 +401,7 @@ unsafeGetAttrPos x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of
401401 throwError
402402 $ ErrorCall
403403 $ " Invalid types for builtins.unsafeGetAttrPos: "
404- ++ show (x, y)
404+ <> show (x, y)
405405
406406-- This function is a bit special in that it doesn't care about the contents
407407-- of the list.
@@ -665,7 +665,7 @@ thunkStr s = nvStr (makeNixStringWithoutContext (decodeUtf8 s))
665665substring :: forall e t f m . MonadNix e t f m => Int -> Int -> NixString -> Prim m NixString
666666substring start len str = Prim $
667667 if start < 0
668- then throwError $ ErrorCall $ " builtins.substring: negative start position: " ++ show start
668+ then throwError $ ErrorCall $ " builtins.substring: negative start position: " <> show start
669669 else pure $ modifyNixContents (take . Text. drop start) str
670670 where
671671 -- NOTE: negative values of 'len' are OK, and mean "take everything"
@@ -789,7 +789,7 @@ dirOf x = demand x $ \case
789789 (modifyNixContents (Text. pack . takeDirectory . Text. unpack) ns)
790790 NVPath path -> pure $ nvPath $ takeDirectory path
791791 v ->
792- throwError $ ErrorCall $ " dirOf: expected string or path, got " ++ show v
792+ throwError $ ErrorCall $ " dirOf: expected string or path, got " <> show v
793793
794794-- jww (2018-04-28): This should only be a string argument, and not coerced?
795795unsafeDiscardStringContext
@@ -839,9 +839,9 @@ elemAt_ xs n = fromValue n >>= \n' -> fromValue xs >>= \xs' ->
839839 throwError
840840 $ ErrorCall
841841 $ " builtins.elem: Index "
842- ++ show n'
843- ++ " too large for list of length "
844- ++ show (length xs')
842+ <> show n'
843+ <> " too large for list of length "
844+ <> show (length xs')
845845
846846genList
847847 :: forall e t f m
@@ -855,7 +855,7 @@ genList f = fromValue @Integer >=> \n -> if n >= 0
855855 throwError
856856 $ ErrorCall
857857 $ " builtins.genList: Expected a non-negative number, got "
858- ++ show n
858+ <> show n
859859
860860-- We wrap values solely to provide an Ord instance for genericClosure
861861newtype WValue t f m = WValue (NValue t f m )
@@ -892,7 +892,7 @@ genericClosure = fromValue @(AttrSet (NValue t f m)) >=> \s ->
892892 throwError
893893 $ ErrorCall
894894 $ " builtins.genericClosure: "
895- ++ " Attributes 'startSet' and 'operator' required"
895+ <> " Attributes 'startSet' and 'operator' required"
896896 (Nothing , Just _) ->
897897 throwError
898898 $ ErrorCall
@@ -921,7 +921,7 @@ genericClosure = fromValue @(AttrSet (NValue t f m)) >=> \s ->
921921 case S. toList ks of
922922 [] -> checkComparable k' k'
923923 WValue j : _ -> checkComparable k' j
924- fmap (t : ) <$> go op (ts ++ ys) (S. insert (WValue k') ks)
924+ fmap (t : ) <$> go op (ts <> ys) (S. insert (WValue k') ks)
925925
926926replaceStrings
927927 :: MonadNix e t f m
@@ -937,7 +937,7 @@ replaceStrings tfrom tto ts = fromValue (Deeper tfrom) >>= \(nsFrom :: [NixStrin
937937 $ throwError
938938 $ ErrorCall
939939 $ " 'from' and 'to' arguments to 'replaceStrings'"
940- ++ " have different lengths"
940+ <> " have different lengths"
941941 let
942942 lookupPrefix s = do
943943 (prefix, replacement) <- find ((`Text.isPrefixOf` s) . fst )
@@ -1008,7 +1008,7 @@ functionArgs fun = demand fun $ \case
10081008 throwError
10091009 $ ErrorCall
10101010 $ " builtins.functionArgs: expected function, got "
1011- ++ show v
1011+ <> show v
10121012
10131013toFile
10141014 :: MonadNix e t f m
@@ -1035,7 +1035,7 @@ pathExists_ path = demand path $ \case
10351035 throwError
10361036 $ ErrorCall
10371037 $ " builtins.pathExists: expected path, got "
1038- ++ show v
1038+ <> show v
10391039
10401040hasKind
10411041 :: forall a e t f m
@@ -1105,7 +1105,7 @@ scopedImport asetArg pathArg = fromValue @(AttrSet (NValue t f m)) asetArg >>= \
11051105 traceM " No known current directory"
11061106 pure path
11071107 Just p -> demand p $ fromValue >=> \ (Path p') -> do
1108- traceM $ " Current file being evaluated is: " ++ show p'
1108+ traceM $ " Current file being evaluated is: " <> show p'
11091109 pure $ takeDirectory p' </> path
11101110 clearScopes @ (NValue t f m )
11111111 $ withNixContext (Just path')
@@ -1144,10 +1144,10 @@ lessThan ta tb = demand ta $ \va -> demand tb $ \vb -> do
11441144 throwError
11451145 $ ErrorCall
11461146 $ " builtins.lessThan: expected two numbers or two strings, "
1147- ++ " got "
1148- ++ show va
1149- ++ " and "
1150- ++ show vb
1147+ <> " got "
1148+ <> show va
1149+ <> " and "
1150+ <> show vb
11511151 nvConstant . NBool <$> case (va, vb) of
11521152 (NVConstant ca, NVConstant cb) -> case (ca, cb) of
11531153 (NInt a, NInt b ) -> pure $ a < b
@@ -1221,8 +1221,8 @@ hashString nsAlgo ns = Prim $ do
12211221 throwError
12221222 $ ErrorCall
12231223 $ " builtins.hashString: "
1224- ++ " expected \" md5\" , \" sha1\" , \" sha256\" , or \" sha512\" , got "
1225- ++ show algo
1224+ <> " expected \" md5\" , \" sha1\" , \" sha256\" , or \" sha512\" , got "
1225+ <> show algo
12261226
12271227placeHolder :: MonadNix e t f m => NValue t f m -> m (NValue t f m )
12281228placeHolder = fromValue >=> fromStringNoContext >=> \ t -> do
@@ -1253,11 +1253,11 @@ absolutePathFromValue = \case
12531253 $ throwError
12541254 $ ErrorCall
12551255 $ " string "
1256- ++ show path
1257- ++ " doesn't represent an absolute path"
1256+ <> show path
1257+ <> " doesn't represent an absolute path"
12581258 pure path
12591259 NVPath path -> pure path
1260- v -> throwError $ ErrorCall $ " expected a path, got " ++ show v
1260+ v -> throwError $ ErrorCall $ " expected a path, got " <> show v
12611261
12621262readFile_ :: MonadNix e t f m => NValue t f m -> m (NValue t f m )
12631263readFile_ path = demand path $
@@ -1275,10 +1275,10 @@ findFile_ aset filePath = demand aset $ \aset' -> demand filePath $ \filePath' -
12751275 mres <- findPath @ t @ f @ m x (Text. unpack (stringIgnoreContext ns))
12761276 pure $ nvPath mres
12771277 (NVList _, y) ->
1278- throwError $ ErrorCall $ " expected a string, got " ++ show y
1279- (x, NVStr _) -> throwError $ ErrorCall $ " expected a list, got " ++ show x
1278+ throwError $ ErrorCall $ " expected a string, got " <> show y
1279+ (x, NVStr _) -> throwError $ ErrorCall $ " expected a list, got " <> show x
12801280 (x, y) ->
1281- throwError $ ErrorCall $ " Invalid types for builtins.findFile: " ++ show
1281+ throwError $ ErrorCall $ " Invalid types for builtins.findFile: " <> show
12821282 (x, y)
12831283
12841284data FileType
@@ -1315,7 +1315,7 @@ fromJSON
13151315fromJSON arg = demand arg $ fromValue >=> fromStringNoContext >=> \ encoded ->
13161316 case A. eitherDecodeStrict' @ A. Value $ encodeUtf8 encoded of
13171317 Left jsonError ->
1318- throwError $ ErrorCall $ " builtins.fromJSON: " ++ jsonError
1318+ throwError $ ErrorCall $ " builtins.fromJSON: " <> jsonError
13191319 Right v -> jsonToNValue v
13201320 where
13211321 jsonToNValue = \ case
@@ -1404,7 +1404,7 @@ fetchurl v = demand v $ \case
14041404 throwError
14051405 $ ErrorCall
14061406 $ " builtins.fetchurl: Expected URI or set, got "
1407- ++ show v
1407+ <> show v
14081408 where
14091409 go :: Maybe (NValue t f m ) -> NValue t f m -> m (NValue t f m )
14101410 go _msha = \ case
@@ -1415,7 +1415,7 @@ fetchurl v = demand v $ \case
14151415 throwError
14161416 $ ErrorCall
14171417 $ " builtins.fetchurl: Expected URI or string, got "
1418- ++ show v
1418+ <> show v
14191419
14201420 noContextAttrs ns = case getStringNoContext ns of
14211421 Nothing ->
@@ -1462,7 +1462,7 @@ getContext x = demand x $ \case
14621462 valued :: M. HashMap Text (NValue t f m ) <- sequenceA $ M. map toValue context
14631463 pure $ nvSet valued M. empty
14641464 x ->
1465- throwError $ ErrorCall $ " Invalid type for builtins.getContext: " ++ show x
1465+ throwError $ ErrorCall $ " Invalid type for builtins.getContext: " <> show x
14661466
14671467appendContext
14681468 :: forall e t f m
@@ -1488,13 +1488,13 @@ appendContext x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of
14881488 throwError
14891489 $ ErrorCall
14901490 $ " Invalid types for context value outputs in builtins.appendContext: "
1491- ++ show x
1491+ <> show x
14921492 pure $ NixLikeContextValue path allOutputs outputs
14931493 x ->
14941494 throwError
14951495 $ ErrorCall
14961496 $ " Invalid types for context value in builtins.appendContext: "
1497- ++ show x
1497+ <> show x
14981498 toValue
14991499 $ makeNixString (stringIgnoreContext ns)
15001500 $ fromNixLikeContext
@@ -1507,7 +1507,7 @@ appendContext x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of
15071507 throwError
15081508 $ ErrorCall
15091509 $ " Invalid types for builtins.appendContext: "
1510- ++ show (x, y)
1510+ <> show (x, y)
15111511
15121512newtype Prim m a = Prim { runPrim :: m a }
15131513
0 commit comments