File tree Expand file tree Collapse file tree 10 files changed +33
-38
lines changed Expand file tree Collapse file tree 10 files changed +33
-38
lines changed Original file line number Diff line number Diff line change 26822682 note : " Use 'stub'"
26832683 rhs : stub
26842684
2685- - warn :
2686- lhs : " Data.Bool.bool True"
2687- rhs : " Use `whenTrue` from HNix Prelude"
2685+ - hint :
2686+ lhs : " bool mempty a b"
2687+ note : " Use `whenTrue`"
2688+ rhs : a `whenTrue` b
2689+
2690+ - hint :
2691+ lhs : " bool a mempty b"
2692+ note : " Use `whenFalse`"
2693+ rhs : a `whenFalse` b
26882694
26892695- hint :
2690- lhs : " maybe mempty"
2696+ lhs : " maybe mempty a b "
26912697 note : " Use `whenJust`"
2692- rhs : whenJust
2698+ rhs : a ` whenJust` b
Original file line number Diff line number Diff line change @@ -248,7 +248,7 @@ exec update source = do
248248 (parseNixTextLoc i)
249249
250250 toAttrSet i =
251- " {" <> i <> bool " ;" mempty (Text. isSuffixOf " ;" i) <> " }"
251+ " {" <> i <> whenFalse " ;" (Text. isSuffixOf " ;" i) <> " }"
252252
253253cmd
254254 :: (MonadNix e t f m , MonadIO m )
Original file line number Diff line number Diff line change @@ -108,11 +108,7 @@ findEnvPathM name = do
108108 (toAbsolutePath @ t @ f $ coerce $ coerce absPath </> " default.nix" )
109109 isDir
110110 exists <- doesFileExist absFile
111- pure $
112- bool
113- mempty
114- (pure absFile)
115- exists
111+ pure $ pure absFile `whenTrue` exists
116112
117113findPathBy
118114 :: forall e t f m
@@ -147,10 +143,7 @@ findPathBy finder ls name = do
147143 case mns of
148144 Just (nsPfx :: NixString ) ->
149145 let pfx = stringIgnoreContext nsPfx in
150- bool
151- mempty
152- (pure $ coerce $ toString pfx)
153- (not $ Text. null pfx)
146+ pure $ coerce $ toString pfx `whenFalse` Text. null pfx
154147 _ -> mempty
155148 )
156149 (M. lookup " prefix" s)
Original file line number Diff line number Diff line change @@ -124,7 +124,7 @@ mkNamedVariadicParamSet name params = mkGeneralParamSet (pure name) params True
124124-- > False -> {}
125125-- @since 0.15.0
126126mkGeneralParamSet :: Maybe Text -> [(Text , Maybe NExpr )] -> Bool -> Params NExpr
127- mkGeneralParamSet mname params variadic = ParamSet (coerce mname) (bool mempty Variadic variadic) (coerce params)
127+ mkGeneralParamSet mname params variadic = ParamSet (coerce mname) (Variadic `whenTrue` variadic) (coerce params)
128128
129129-- | > rec { .. }
130130mkRecSet :: [Binding NExpr ] -> NExpr
@@ -444,4 +444,4 @@ mkBinop = mkOp2
444444-- * `mkVariadicSet` is for variadic;
445445-- * `mkGeneralParamSet` a general constructor.
446446mkParamset :: [(Text , Maybe NExpr )] -> Bool -> Params NExpr
447- mkParamset params variadic = ParamSet Nothing (bool mempty Variadic variadic) (coerce params)
447+ mkParamset params variadic = ParamSet Nothing (Variadic `whenTrue` variadic) (coerce params)
Original file line number Diff line number Diff line change @@ -136,18 +136,15 @@ prettyParams (ParamSet mname variadic pset) =
136136 where
137137 toDoc :: VarName -> Doc ann
138138 toDoc (coerce -> name) =
139- bool
140- mempty
141- (" @" <> pretty name)
142- (not (Text. null name))
139+ (" @" <> pretty name) `whenFalse` Text. null name
143140
144141prettyParamSet :: Variadic -> ParamSet (NixDoc ann ) -> Doc ann
145142prettyParamSet variadic args =
146143 encloseSep
147144 " { "
148145 (align " }" )
149146 sep
150- (fmap prettySetArg args <> bool mempty [" ..." ] (variadic == Variadic ))
147+ (fmap prettySetArg args <> [" ..." ] `whenTrue` (variadic == Variadic ))
151148 where
152149 prettySetArg (n, maybeDef) =
153150 maybe
Original file line number Diff line number Diff line change @@ -119,14 +119,13 @@ sourceContext path (unPos -> begLine) (unPos -> _begCol) (unPos -> endLine) (unP
119119 | otherwise -> " " <> nsp <> " | "
120120 composeLine n l =
121121 [pretty (pad n) <> l]
122- <> bool mempty
123- [ pretty $
122+ <> ([ pretty $
124123 Text. replicate (Text. length (pad n) - 3 ) " "
125124 <> " |"
126125 <> Text. replicate (_begCol + 1 ) " "
127126 <> Text. replicate (_endCol - _begCol) " ^"
128- ]
129- (begLine == endLine && n == endLine )
127+ ] `whenTrue` (begLine == endLine && n == endLine)
128+ )
130129 -- XXX: Consider inserting the message here when it is small enough.
131130 -- ATM some messages are so huge that they take prevalence over the source listing.
132131 -- ++ [ indent (length $ pad n) msg | n == endLine ]
Original file line number Diff line number Diff line change @@ -104,10 +104,7 @@ renderEvalFrame level f =
104104 do
105105 let
106106 scopeInfo =
107- bool
108- mempty
109- [pretty $ Text. show scope]
110- (showScopes opts)
107+ [pretty $ Text. show scope] `whenTrue` showScopes opts
111108 fmap
112109 (\ x -> scopeInfo <> [x])
113110 $ renderLocation ann =<<
Original file line number Diff line number Diff line change @@ -17,6 +17,7 @@ module Nix.Utils
1717 , stub
1818 , pass
1919 , whenTrue
20+ , whenFalse
2021 , list
2122 , whenText
2223 , free
@@ -190,6 +191,14 @@ whenTrue =
190191 mempty
191192{-# inline whenTrue #-}
192193
194+ whenFalse :: (Monoid a )
195+ => a -> Bool -> a
196+ whenFalse f =
197+ bool
198+ f
199+ mempty
200+ {-# inline whenFalse #-}
201+
193202whenJust
194203 :: Monoid b
195204 => (a -> b )
Original file line number Diff line number Diff line change @@ -729,10 +729,7 @@ valueType =
729729 NNull -> TNull
730730 NVStrF ns ->
731731 TString $
732- bool
733- mempty
734- HasContext
735- (stringHasContext ns)
732+ HasContext `whenTrue` stringHasContext ns
736733 NVListF {} -> TList
737734 NVSetF {} -> TSet
738735 NVClosureF {} -> TClosure
Original file line number Diff line number Diff line change @@ -106,10 +106,7 @@ paramsXML (ParamSet mname variadic pset) =
106106 [Elem $ Element (unqual " attrspat" ) (battr <> nattr) (paramSetXML pset) Nothing ]
107107 where
108108 battr =
109- bool
110- mempty
111- [ Attr (unqual " ellipsis" ) " 1" ]
112- (variadic == Variadic )
109+ [ Attr (unqual " ellipsis" ) " 1" ] `whenTrue` (variadic == Variadic )
113110 nattr =
114111 ((: mempty ) . Attr (unqual " name" ) . toString) `whenJust` mname
115112
You can’t perform that action at this time.
0 commit comments