1
1
{-# LANGUAGE Trustworthy #-}
2
+ {-# LANGUAGE DeriveFunctor #-}
2
3
module Data.Crosswalk (
3
4
-- * Crosswalk
4
5
Crosswalk (.. ),
5
6
-- * Bicrosswalk
6
7
Bicrosswalk (.. ),
7
8
) where
8
9
9
- import Control.Applicative (pure , (<$>) )
10
+ import Control.Applicative (pure , (<$>) , Const ( .. ) )
10
11
import Data.Bifoldable (Bifoldable (.. ))
11
12
import Data.Bifunctor (Bifunctor (.. ))
12
13
import Data.Foldable (Foldable (.. ))
13
14
import Data.Functor.Compose (Compose (.. ))
14
15
import Data.Functor.Identity (Identity (.. ))
16
+ import Data.Functor.Sum (Sum (.. ))
17
+ import Data.Functor.These (These1 (.. ))
18
+ import Data.Proxy (Proxy (.. ))
15
19
import Data.Vector.Generic (Vector )
16
20
import Prelude (Either (.. ), Functor (fmap ), Maybe (.. ), id , (.) )
17
21
22
+ import qualified Data.List.NonEmpty as NE
18
23
import qualified Data.Sequence as Seq
19
24
import qualified Data.Vector as V
20
25
import qualified Data.Vector.Generic as VG
@@ -55,15 +60,15 @@ instance Crosswalk [] where
55
60
crosswalk f (x: xs) = alignWith cons (f x) (crosswalk f xs)
56
61
where cons = these pure id (:)
57
62
63
+ instance Crosswalk NE. NonEmpty where
64
+ crosswalk f (x NE. :| [] ) = (NE. :| [] ) <$> f x
65
+ crosswalk f (x1 NE. :| x2 : xs) = alignWith cons (f x1) (crosswalk f (x2 NE. :| xs))
66
+ where cons = these (NE. :| [] ) id (NE. <|)
67
+
58
68
instance Crosswalk Seq. Seq where
59
69
crosswalk f = foldr (alignWith cons . f) nil where
60
70
cons = these Seq. singleton id (Seq. <|)
61
71
62
- instance Crosswalk (These a ) where
63
- crosswalk _ (This _) = nil
64
- crosswalk f (That x) = That <$> f x
65
- crosswalk f (These a x) = These a <$> f x
66
-
67
72
crosswalkVector :: (Vector v a , Vector v b , Align f )
68
73
=> (a -> f b ) -> v a -> f (v b )
69
74
crosswalkVector f = fmap VG. fromList . VG. foldr (alignWith cons . f) nil where
@@ -72,12 +77,37 @@ crosswalkVector f = fmap VG.fromList . VG.foldr (alignWith cons . f) nil where
72
77
instance Crosswalk V. Vector where
73
78
crosswalk = crosswalkVector
74
79
80
+ instance Crosswalk (Either e ) where
81
+ crosswalk _ (Left _) = nil
82
+ crosswalk f (Right x) = Right <$> f x
83
+
84
+ instance Crosswalk (These a ) where
85
+ crosswalk _ (This _) = nil
86
+ crosswalk f (That x) = That <$> f x
87
+ crosswalk f (These a x) = These a <$> f x
88
+
75
89
instance Crosswalk ((,) a ) where
76
90
crosswalk fun (a, x) = fmap ((,) a) (fun x)
77
91
78
92
-- can't (shouldn't) do longer tuples until there are Functor and Foldable
79
93
-- instances for them
80
94
95
+ instance Crosswalk Proxy where
96
+ crosswalk _ _ = nil
97
+
98
+ instance Crosswalk (Const r ) where
99
+ crosswalk _ _ = nil
100
+
101
+ instance (Crosswalk f , Crosswalk g ) => Crosswalk (Sum f g ) where
102
+ crosswalk f (InL xs) = InL <$> crosswalk f xs
103
+ crosswalk f (InR xs) = InR <$> crosswalk f xs
104
+
105
+ instance (Crosswalk f , Crosswalk g ) => Crosswalk (These1 f g ) where
106
+ crosswalk f (This1 xs) = This1 <$> crosswalk f xs
107
+ crosswalk f (That1 ys) = That1 <$> crosswalk f ys
108
+ crosswalk f (These1 xs ys) = alignWith go (crosswalk f xs) (crosswalk f ys)
109
+ where go = these This1 That1 These1
110
+
81
111
instance (Crosswalk f , Crosswalk g ) => Crosswalk (Compose f g ) where
82
112
crosswalk f
83
113
= fmap Compose -- can't coerce: maybe the Align-able thing has role nominal
@@ -113,3 +143,6 @@ instance Bicrosswalk These where
113
143
bicrosswalk f _ (This x) = This <$> f x
114
144
bicrosswalk _ g (That x) = That <$> g x
115
145
bicrosswalk f g (These x y) = align (f x) (g y)
146
+
147
+ instance Bicrosswalk Const where
148
+ bicrosswalk f _ (Const x) = Const <$> f x
0 commit comments