Skip to content

Commit 131d7fb

Browse files
Add support for mapping variant cases (#37)
1 parent 3f12411 commit 131d7fb

File tree

5 files changed

+449
-22
lines changed

5 files changed

+449
-22
lines changed

src/Data/Functor/Variant.purs

Lines changed: 189 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -4,16 +4,23 @@ module Data.Functor.Variant
44
, prj
55
, on
66
, onMatch
7+
, over
8+
, overOne
9+
, overSome
710
, case_
811
, match
912
, default
13+
, traverse
14+
, traverseOne
15+
, traverseSome
1016
, expand
1117
, contract
1218
, UnvariantF(..)
1319
, UnvariantF'
1420
, unvariantF
1521
, revariantF
1622
, class VariantFShows, variantFShows
23+
, class VariantFMaps, variantFMaps, Mapper
1724
, class TraversableVFRL
1825
, class FoldableVFRL
1926
, traverseVFRL
@@ -29,19 +36,20 @@ import Control.Alternative (class Alternative, empty)
2936
import Data.List as L
3037
import Data.Symbol (class IsSymbol, reflectSymbol)
3138
import Data.Traversable as TF
32-
import Data.Variant.Internal (class Contractable, class VariantFMatchCases) as Exports
33-
import Data.Variant.Internal (class Contractable, class VariantFMatchCases, class VariantTags, VariantFCase, VariantCase, contractWith, lookup, unsafeGet, unsafeHas, variantTags)
39+
import Data.Variant.Internal (class Contractable, class VariantFMatchCases, class VariantFMapCases) as Exports
40+
import Data.Variant.Internal (class Contractable, class VariantFMapCases, class VariantFMatchCases, class VariantFTraverseCases, class VariantTags, VariantFCase, VariantCase, contractWith, lookup, unsafeGet, unsafeHas, variantTags)
3441
import Partial.Unsafe (unsafeCrashWith)
3542
import Prim.Row as R
3643
import Prim.RowList as RL
37-
import Type.Equality (class TypeEquals)
3844
import Type.Proxy (Proxy(..))
3945
import Unsafe.Coerce (unsafeCoerce)
4046

47+
newtype Mapper f = Mapper (forall a b. (a b) f a f b)
48+
4149
newtype VariantFRep f a = VariantFRep
4250
{ type String
4351
, value f a
44-
, map x y. (x y) f x f y
52+
, map Mapper f
4553
}
4654

4755
data UnknownF :: Type -> Type
@@ -55,7 +63,7 @@ instance functorVariantF ∷ Functor (VariantF r) where
5563
case coerceY a of
5664
VariantFRep v → coerceV $ VariantFRep
5765
{ type: v.type
58-
, value: v.map f v.value
66+
, value: case v.map of Mapper m → m f v.value
5967
, map: v.map
6068
}
6169
where
@@ -133,7 +141,7 @@ inj
133141
proxy sym
134142
f a
135143
VariantF r2 a
136-
inj p value = coerceV $ VariantFRep { type: reflectSymbol p, value, map }
144+
inj p value = coerceV $ VariantFRep { type: reflectSymbol p, value, map: Mapper map }
137145
where
138146
coerceV VariantFRep f a VariantF r2 a
139147
coerceV = unsafeCoerce
@@ -214,6 +222,166 @@ onMatch r k v =
214222
coerceR VariantF r3 a VariantF r2 a
215223
coerceR = unsafeCoerce
216224

225+
-- | Map over one case of a variant, putting the result back at the same label,
226+
-- | with a fallback function to handle the remaining cases.
227+
overOne
228+
sym f g a b r1 r2 r3 r4
229+
. R.Cons sym f r1 r2
230+
R.Cons sym g r4 r3
231+
IsSymbol sym
232+
Functor g
233+
Proxy sym
234+
(f a g b)
235+
(VariantF r1 a VariantF r3 b)
236+
VariantF r2 a
237+
VariantF r3 b
238+
overOne p f = on p (inj p <<< f)
239+
240+
-- | Map over several cases of a variant using a `Record` containing functions
241+
-- | for each case. Each case gets put back at the same label it was matched
242+
-- | at, i.e. its label in the record. Labels not found in the record are
243+
-- | handled using the fallback function.
244+
overSome
245+
r rl rlo ri ro r1 r2 r3 r4 a b
246+
. RL.RowToList r rl
247+
VariantFMapCases rl ri ro a b
248+
RL.RowToList ro rlo
249+
VariantTags rlo
250+
VariantFMaps rlo
251+
R.Union ri r2 r1
252+
R.Union ro r4 r3
253+
Record r
254+
(VariantF r2 a VariantF r3 b)
255+
VariantF r1 a
256+
VariantF r3 b
257+
overSome r k v =
258+
case coerceV v of
259+
VariantFRep v' | unsafeHas v'.type r →
260+
let
261+
tags = variantTags (Proxy Proxy rlo)
262+
maps = variantFMaps (Proxy Proxy rlo)
263+
map = lookup "map" v'.type tags maps
264+
in coerceV' (VariantFRep { type: v'.type, map, value: unsafeGet v'.type r v'.value })
265+
_ → k (coerceR v)
266+
267+
where
268+
coerceV f. VariantF r1 a VariantFRep f a
269+
coerceV = unsafeCoerce
270+
271+
coerceV' g. VariantFRep g b VariantF r3 b
272+
coerceV' = unsafeCoerce
273+
274+
coerceR VariantF r1 a VariantF r2 a
275+
coerceR = unsafeCoerce
276+
277+
-- | Map over some labels (with access to the containers) and use `map f` for
278+
-- | the rest (just changing the index type). For example:
279+
-- |
280+
-- | ```purescript
281+
-- | over { label: \(Identity a) -> Just (show (a - 5)) } show
282+
-- | :: forall r.
283+
-- | VariantF ( label :: Identity | r ) Int ->
284+
-- | VariantF ( label :: Maybe | r ) String
285+
-- | ```
286+
-- |
287+
-- | `over r f` is like `(map f >>> expand) # overSome r` but with
288+
-- | a more easily solved constraint (i.e. it can be solved once the type of
289+
-- | `r` is known).
290+
over
291+
r rl rlo ri ro r1 r2 r3 a b
292+
. RL.RowToList r rl
293+
VariantFMapCases rl ri ro a b
294+
RL.RowToList ro rlo
295+
VariantTags rlo
296+
VariantFMaps rlo
297+
R.Union ri r2 r1
298+
R.Union ro r2 r3 -- this is "backwards" for `expand`, but still safe
299+
Record r
300+
(a b)
301+
VariantF r1 a
302+
VariantF r3 b
303+
over r f = overSome r (map f >>> unsafeExpand) where
304+
unsafeExpand = unsafeCoerce VariantF r2 b VariantF r3 b
305+
306+
-- | Traverse over one case of a variant (in a functorial/monadic context `m`),
307+
-- | putting the result back at the same label, with a fallback function.
308+
traverseOne
309+
sym f g a b r1 r2 r3 r4 m
310+
. R.Cons sym f r1 r2
311+
R.Cons sym g r4 r3
312+
IsSymbol sym
313+
Functor g
314+
Functor m
315+
Proxy sym
316+
(f a m (g b))
317+
(VariantF r1 a m (VariantF r3 b))
318+
VariantF r2 a
319+
m (VariantF r3 b)
320+
traverseOne p f = on p (map (inj p) <<< f)
321+
322+
-- | Traverse over several cases of a variant using a `Record` containing
323+
-- | traversals. Each case gets put back at the same label it was matched
324+
-- | at, i.e. its label in the record. Labels not found in the record are
325+
-- | handled using the fallback function.
326+
traverseSome
327+
r rl rlo ri ro r1 r2 r3 r4 a b m
328+
. RL.RowToList r rl
329+
VariantFTraverseCases m rl ri ro a b
330+
RL.RowToList ro rlo
331+
VariantTags rlo
332+
VariantFMaps rlo
333+
R.Union ri r2 r1
334+
R.Union ro r4 r3
335+
Functor m
336+
Record r
337+
(VariantF r2 a m (VariantF r3 b))
338+
VariantF r1 a
339+
m (VariantF r3 b)
340+
traverseSome r k v =
341+
case coerceV v of
342+
VariantFRep v' | unsafeHas v'.type r →
343+
let
344+
tags = variantTags (Proxy Proxy rlo)
345+
maps = variantFMaps (Proxy Proxy rlo)
346+
map = lookup "map" v'.type tags maps
347+
in unsafeGet v'.type r v'.value <#> \value ->
348+
coerceV' (VariantFRep { type: v'.type, map, value })
349+
_ → k (coerceR v)
350+
351+
where
352+
coerceV f. VariantF r1 a VariantFRep f a
353+
coerceV = unsafeCoerce
354+
355+
coerceV' g. VariantFRep g b VariantF r3 b
356+
coerceV' = unsafeCoerce
357+
358+
coerceR VariantF r1 a VariantF r2 a
359+
coerceR = unsafeCoerce
360+
361+
-- | Traverse over some labels (with access to the containers) and use
362+
-- | `traverse f` for the rest (just changing the index type).
363+
-- |
364+
-- | `traverse r f` is like `(traverse f >>> expand) # traverseSome r` but with
365+
-- | a more easily solved constraint (i.e. it can be solved once the type of
366+
-- | `r` is known).
367+
traverse
368+
r rl rlo ri ro r1 r2 r3 a b m
369+
. RL.RowToList r rl
370+
VariantFTraverseCases m rl ri ro a b
371+
RL.RowToList ro rlo
372+
VariantTags rlo
373+
VariantFMaps rlo
374+
R.Union ri r2 r1
375+
R.Union ro r2 r3 -- this is "backwards" for `expand`, but still safe
376+
Applicative m
377+
TF.Traversable (VariantF r2)
378+
Record r
379+
(a m b)
380+
VariantF r1 a
381+
m (VariantF r3 b)
382+
traverse r f = traverseSome r (TF.traverse f >>> map unsafeExpand) where
383+
unsafeExpand = unsafeCoerce VariantF r2 b VariantF r3 b
384+
217385
-- | Combinator for exhaustive pattern matching.
218386
-- | ```purescript
219387
-- | caseFn :: VariantF (foo :: Maybe, bar :: Tuple String, baz :: Either String) Int -> String
@@ -320,7 +488,7 @@ unvariantF v = case (unsafeCoerce v ∷ VariantFRep UnknownF Unit) of
320488
. UnvariantF' r a x
321489
{ reflectSymbol proxy "" String }
322490
{}
323-
{ map a b. (a b) UnknownF a UnknownF b }
491+
{ map Mapper UnknownF }
324492
proxy ""
325493
UnknownF Unit
326494
x
@@ -337,7 +505,7 @@ class VariantFShows rl x where
337505
instance showVariantFNilVariantFShows RL.Nil x where
338506
variantFShows _ _ = L.Nil
339507

340-
instance showVariantFCons ∷ (VariantFShows rs x, TypeEquals a f, Show (f x), Show x) VariantFShows (RL.Cons sym a rs) x where
508+
instance showVariantFCons ∷ (VariantFShows rs x, Show (f x), Show x) VariantFShows (RL.Cons sym f rs) x where
341509
variantFShows _ p =
342510
L.Cons (coerceShow show) (variantFShows (Proxy Proxy rs) p)
343511
where
@@ -353,3 +521,16 @@ instance showVariantF ∷ (RL.RowToList r rl, VariantTags rl, VariantFShows rl a
353521
body = lookup "show" v.type tags shows (unsafeCoerce v.value VariantCase)
354522
in
355523
"(inj @" <> show v.type <> " " <> body <> ")"
524+
525+
class VariantFMaps (rlRL.RowList (Type Type)) where
526+
variantFMaps Proxy rl L.List (Mapper VariantFCase)
527+
528+
instance mapVariantFNilVariantFMaps RL.Nil where
529+
variantFMaps _ = L.Nil
530+
531+
instance mapVariantFCons ∷ (VariantFMaps rs, Functor f) VariantFMaps (RL.Cons sym f rs) where
532+
variantFMaps _ =
533+
L.Cons (coerceMap (Mapper map)) (variantFMaps (Proxy Proxy rs))
534+
where
535+
coerceMap Mapper f Mapper VariantFCase
536+
coerceMap = unsafeCoerce

0 commit comments

Comments
 (0)