@@ -71,7 +71,9 @@ import Data.Patch.MapWithPatchingMove (PatchMapWithPatchingMove(..), To)
71
71
import qualified Data.Patch.MapWithPatchingMove as PM -- already a transparent synonym
72
72
73
73
import Control.Lens hiding (FunctorWithIndex , FoldableWithIndex , TraversableWithIndex )
74
+ #if !MIN_VERSION_lens(5,0,0)
74
75
import qualified Control.Lens as L
76
+ #endif
75
77
import Data.List
76
78
import Data.Map (Map )
77
79
import qualified Data.Map as Map
@@ -109,8 +111,8 @@ pattern Coerce x <- (coerce -> x)
109
111
110
112
{-# COMPLETE PatchMapWithMove #-}
111
113
pattern PatchMapWithMove :: Map k (NodeInfo k v ) -> PatchMapWithMove k v
112
- -- | Extract the representation of the 'PatchMapWithMove' as a map of
113
- -- 'NodeInfo'.
114
+ -- | Extract the representation of the t 'PatchMapWithMove' as a map of
115
+ -- t 'NodeInfo'.
114
116
unPatchMapWithMove :: PatchMapWithMove k v -> Map k (NodeInfo k v )
115
117
pattern PatchMapWithMove { unPatchMapWithMove } = PatchMapWithMove' (PatchMapWithPatchingMove (Coerce unPatchMapWithMove))
116
118
@@ -145,27 +147,27 @@ instance L.FoldableWithIndex k (PatchMapWithMove k) where ifoldMap = Data.Fold
145
147
instance L. TraversableWithIndex k (PatchMapWithMove k ) where itraverse = Data.Traversable.WithIndex. itraverse
146
148
#endif
147
149
148
- -- | Create a 'PatchMapWithMove', validating it
150
+ -- | Create a t 'PatchMapWithMove', validating it
149
151
patchMapWithMove :: Ord k => Map k (NodeInfo k v ) -> Maybe (PatchMapWithMove k v )
150
152
patchMapWithMove = fmap PatchMapWithMove' . PM. patchMapWithPatchingMove . coerce
151
153
152
- -- | Create a 'PatchMapWithMove' that inserts everything in the given 'Map'
154
+ -- | Create a t 'PatchMapWithMove' that inserts everything in the given 'Map'
153
155
patchMapWithMoveInsertAll :: Map k v -> PatchMapWithMove k v
154
156
patchMapWithMoveInsertAll = PatchMapWithMove' . PM. patchMapWithPatchingMoveInsertAll
155
157
156
- -- | Make a @'PatchMapWithMove' k v@ which has the effect of inserting or updating a value @v@ to the given key @k@, like 'Map.insert'.
158
+ -- | Make a @t 'PatchMapWithMove' k v@ which has the effect of inserting or updating a value @v@ to the given key @k@, like 'Map.insert'.
157
159
insertMapKey :: k -> v -> PatchMapWithMove k v
158
160
insertMapKey k v = PatchMapWithMove' $ PM. insertMapKey k v
159
161
160
- -- | Make a @'PatchMapWithMove' k v@ which has the effect of moving the value from the first key @k@ to the second key @k@, equivalent to:
162
+ -- | Make a @t 'PatchMapWithMove' k v@ which has the effect of moving the value from the first key @k@ to the second key @k@, equivalent to:
161
163
--
162
164
-- @
163
165
-- 'Map.delete' src (maybe map ('Map.insert' dst) (Map.lookup src map))
164
166
-- @
165
167
moveMapKey :: Ord k => k -> k -> PatchMapWithMove k v
166
168
moveMapKey src dst = PatchMapWithMove' $ PM. moveMapKey src dst
167
169
168
- -- | Make a @'PatchMapWithMove' k v@ which has the effect of swapping two keys in the mapping, equivalent to:
170
+ -- | Make a @t 'PatchMapWithMove' k v@ which has the effect of swapping two keys in the mapping, equivalent to:
169
171
--
170
172
-- @
171
173
-- let aMay = Map.lookup a map
@@ -177,13 +179,13 @@ moveMapKey src dst = PatchMapWithMove' $ PM.moveMapKey src dst
177
179
swapMapKey :: Ord k => k -> k -> PatchMapWithMove k v
178
180
swapMapKey src dst = PatchMapWithMove' $ PM. swapMapKey src dst
179
181
180
- -- | Make a @'PatchMapWithMove' k v@ which has the effect of deleting a key in the mapping, equivalent to 'Map.delete'.
182
+ -- | Make a @t 'PatchMapWithMove' k v@ which has the effect of deleting a key in the mapping, equivalent to 'Map.delete'.
181
183
deleteMapKey :: k -> PatchMapWithMove k v
182
184
deleteMapKey = PatchMapWithMove' . PM. deleteMapKey
183
185
184
- -- | Wrap a @'Map' k (NodeInfo k v)@ representing patch changes into a @'PatchMapWithMove' k v@, without checking any invariants.
186
+ -- | Wrap a @'Map' k (NodeInfo k v)@ representing patch changes into a @t 'PatchMapWithMove' k v@, without checking any invariants.
185
187
--
186
- -- __Warning:__ when using this function, you must ensure that the invariants of 'PatchMapWithMove' are preserved; they will not be checked.
188
+ -- __Warning:__ when using this function, you must ensure that the invariants of t 'PatchMapWithMove' are preserved; they will not be checked.
187
189
unsafePatchMapWithMove :: Map k (NodeInfo k v ) -> PatchMapWithMove k v
188
190
unsafePatchMapWithMove = coerce PM. unsafePatchMapWithPatchingMove
189
191
@@ -196,25 +198,25 @@ instance Ord k => Patch (PatchMapWithMove k v) where
196
198
patchMapWithMoveNewElements :: PatchMapWithMove k v -> [v ]
197
199
patchMapWithMoveNewElements = PM. patchMapWithPatchingMoveNewElements . unPatchMapWithMove'
198
200
199
- -- | Return a @'Map' k v@ with all the inserts/updates from the given @'PatchMapWithMove' k v@.
201
+ -- | Return a @'Map' k v@ with all the inserts/updates from the given @t 'PatchMapWithMove' k v@.
200
202
patchMapWithMoveNewElementsMap :: PatchMapWithMove k v -> Map k v
201
203
patchMapWithMoveNewElementsMap = PM. patchMapWithPatchingMoveNewElementsMap . unPatchMapWithMove'
202
204
203
- -- | Create a 'PatchMapWithMove' that, if applied to the given 'Map', will sort
205
+ -- | Create a t 'PatchMapWithMove' that, if applied to the given 'Map', will sort
204
206
-- its values using the given ordering function. The set keys of the 'Map' is
205
207
-- not changed.
206
208
patchThatSortsMapWith :: Ord k => (v -> v -> Ordering ) -> Map k v -> PatchMapWithMove k v
207
209
patchThatSortsMapWith cmp = PatchMapWithMove' . PM. patchThatSortsMapWith cmp
208
210
209
- -- | Create a 'PatchMapWithMove' that, if applied to the first 'Map' provided,
211
+ -- | Create a t 'PatchMapWithMove' that, if applied to the first 'Map' provided,
210
212
-- will produce a 'Map' with the same values as the second 'Map' but with the
211
213
-- values sorted with the given ordering function.
212
214
patchThatChangesAndSortsMapWith :: (Ord k , Ord v ) => (v -> v -> Ordering ) -> Map k v -> Map k v -> PatchMapWithMove k v
213
215
patchThatChangesAndSortsMapWith cmp oldByIndex newByIndexUnsorted = patchThatChangesMap oldByIndex newByIndex
214
216
where newList = Map. toList newByIndexUnsorted
215
217
newByIndex = Map. fromList $ zip (fst <$> newList) $ sortBy cmp $ snd <$> newList
216
218
217
- -- | Create a 'PatchMapWithMove' that, if applied to the first 'Map' provided,
219
+ -- | Create a t 'PatchMapWithMove' that, if applied to the first 'Map' provided,
218
220
-- will produce the second 'Map'.
219
221
patchThatChangesMap :: (Ord k , Ord v ) => Map k v -> Map k v -> PatchMapWithMove k v
220
222
patchThatChangesMap oldByIndex newByIndex = PatchMapWithMove' $
@@ -260,6 +262,7 @@ instance Foldable (NodeInfo k) where
260
262
instance Traversable (NodeInfo k ) where
261
263
traverse = bitraverseNodeInfo pure
262
264
265
+ -- | Like 'Data.Bitraversable.bitraverse'
263
266
bitraverseNodeInfo
264
267
:: Applicative f
265
268
=> (k0 -> f k1 )
@@ -269,11 +272,11 @@ bitraverseNodeInfo fk fv = fmap NodeInfo'
269
272
. PM. bitraverseNodeInfo fk (\ ~ Proxy -> pure Proxy ) fv
270
273
. coerce
271
274
272
- -- | Change the 'From' value of a 'NodeInfo'
275
+ -- | Change the 'From' value of a t 'NodeInfo'
273
276
nodeInfoMapFrom :: (From k v -> From k v ) -> NodeInfo k v -> NodeInfo k v
274
277
nodeInfoMapFrom f = coerce $ PM. nodeInfoMapFrom (unFrom' . f . From' )
275
278
276
- -- | Change the 'From' value of a 'NodeInfo', using a 'Functor' (or
279
+ -- | Change the 'From' value of a t 'NodeInfo', using a 'Functor' (or
277
280
-- 'Applicative', 'Monad', etc.) action to get the new value
278
281
nodeInfoMapMFrom
279
282
:: Functor f
@@ -283,7 +286,7 @@ nodeInfoMapMFrom f = fmap NodeInfo'
283
286
. PM. nodeInfoMapMFrom (fmap unFrom' . f . From' )
284
287
. coerce
285
288
286
- -- | Set the 'To' field of a 'NodeInfo'
289
+ -- | Set the 'To' field of a t 'NodeInfo'
287
290
nodeInfoSetTo :: To k -> NodeInfo k v -> NodeInfo k v
288
291
nodeInfoSetTo = coerce . PM. nodeInfoSetTo
289
292
@@ -308,6 +311,7 @@ pattern From_Delete = From' PM.From_Delete
308
311
pattern From_Move :: k -> From k v
309
312
pattern From_Move k = From' (PM. From_Move k Proxy )
310
313
314
+ -- | Like 'Data.Bitraversable.bitraverse'
311
315
bitraverseFrom
312
316
:: Applicative f
313
317
=> (k0 -> f k1 )
0 commit comments