@@ -106,8 +106,8 @@ type WithStringContext = WithStringContextT Identity
106106-- 2021-07-18: NOTE: It should be Context -> Contents.
107107data NixString =
108108 NixString
109- { nsContents :: ! Text
110- , nsContext :: ! ( S. HashSet StringContext )
109+ { nsContext :: ! ( S. HashSet StringContext )
110+ , nsContents :: ! Text
111111 }
112112 deriving (Eq , Ord , Show , Generic )
113113
@@ -126,23 +126,23 @@ instance Hashable NixString
126126
127127-- | Constructs NixString without a context
128128mkNixStringWithoutContext :: Text -> NixString
129- mkNixStringWithoutContext = (` NixString ` mempty )
129+ mkNixStringWithoutContext = NixString mempty
130130
131131-- | Create NixString using a singleton context
132132mkNixStringWithSingletonContext
133133 :: VarName -> StringContext -> NixString
134- mkNixStringWithSingletonContext s c = NixString (coerce @ VarName @ Text s) $ one c
134+ mkNixStringWithSingletonContext s c = NixString (one c) ( coerce @ VarName @ Text s)
135135
136136-- | Create NixString from a Text and context
137137mkNixString :: Text -> S. HashSet StringContext -> NixString
138- mkNixString = NixString
138+ mkNixString t = (` NixString ` t)
139139
140140
141141-- ** Checkers
142142
143143-- | Returns True if the NixString has an associated context
144144hasContext :: NixString -> Bool
145- hasContext (NixString _ c ) = not $ null c
145+ hasContext (NixString c _ ) = not $ null c
146146
147147
148148-- ** Getters
@@ -156,17 +156,17 @@ fromNixLikeContext =
156156
157157-- | Extract the string contents from a NixString that has no context
158158getStringNoContext :: NixString -> Maybe Text
159- getStringNoContext (NixString s c )
159+ getStringNoContext (NixString c s )
160160 | null c = pure s
161161 | otherwise = mempty
162162
163163-- | Extract the string contents from a NixString even if the NixString has an associated context
164164ignoreContext :: NixString -> Text
165- ignoreContext (NixString s _ ) = s
165+ ignoreContext (NixString _ s ) = s
166166
167167-- | Get the contents of a 'NixString' and write its context into the resulting set.
168168extractNixString :: Monad m => NixString -> WithStringContextT m Text
169- extractNixString (NixString s c ) =
169+ extractNixString (NixString c s ) =
170170 WithStringContextT $
171171 s <$ tell c
172172
@@ -229,7 +229,7 @@ addSingletonStringContext = WithStringContextT . tell . one
229229-- | Run an action producing a string with a context and put those into a 'NixString'.
230230runWithStringContextT :: Monad m => WithStringContextT m Text -> m NixString
231231runWithStringContextT (WithStringContextT m) =
232- uncurry NixString <$> runWriterT m
232+ uncurry ( flip NixString ) <$> runWriterT m
233233
234234-- | Run an action producing a string with a context and put those into a 'NixString'.
235235runWithStringContext :: WithStringContextT Identity Text -> NixString
@@ -240,7 +240,7 @@ runWithStringContext = runIdentity . runWithStringContextT
240240
241241-- | Modify the string part of the NixString, leaving the context unchanged
242242modifyNixContents :: (Text -> Text ) -> NixString -> NixString
243- modifyNixContents f (NixString s c ) = NixString (f s) c
243+ modifyNixContents f (NixString c s ) = NixString c (f s)
244244
245245-- | Run an action that manipulates nix strings, and collect the contexts encountered.
246246-- Warning: this may be unsafe, depending on how you handle the resulting context list.
@@ -260,14 +260,14 @@ intercalateNixString sep nss =
260260 uncurry NixString $ mapPair intertwine unpackNss
261261 where
262262
263- intertwine :: ([Text ] -> Text , [ HashSet StringContext ] -> HashSet StringContext )
263+ intertwine :: ([HashSet StringContext ] -> HashSet StringContext , [ Text ] -> Text )
264264 intertwine =
265- ( Text. intercalate (nsContents sep)
266- , S. unions . (:) (nsContext sep)
265+ ( S. unions . (:) (nsContext sep)
266+ , Text. intercalate (nsContents sep)
267267 )
268268
269- unpackNss :: ([Text ], [HashSet StringContext ])
270- unpackNss = (fnss nsContents , fnss nsContext )
269+ unpackNss :: ([HashSet StringContext ], [Text ])
270+ unpackNss = (fnss nsContext , fnss nsContents )
271271 where
272272 fnss :: (NixString -> b ) -> [b ]
273273 fnss = (`fmap` nss) -- do once
0 commit comments