Skip to content

Commit 2c9ef54

Browse files
committed
Add Crosswalk instances for: NonEmpty, Proxy, Const, Functor.Sum, These1
1 parent d39a29a commit 2c9ef54

File tree

2 files changed

+53
-9
lines changed

2 files changed

+53
-9
lines changed

semialign/src/Data/Crosswalk.hs

+39-6
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,25 @@
11
{-# LANGUAGE Trustworthy #-}
2+
{-# LANGUAGE DeriveFunctor #-}
23
module Data.Crosswalk (
34
-- * Crosswalk
45
Crosswalk (..),
56
-- * Bicrosswalk
67
Bicrosswalk (..),
78
) where
89

9-
import Control.Applicative (pure, (<$>))
10+
import Control.Applicative (pure, (<$>), Const(..))
1011
import Data.Bifoldable (Bifoldable (..))
1112
import Data.Bifunctor (Bifunctor (..))
1213
import Data.Foldable (Foldable (..))
1314
import Data.Functor.Compose (Compose (..))
1415
import Data.Functor.Identity (Identity (..))
16+
import Data.Functor.Sum (Sum (..))
17+
import Data.Functor.These (These1 (..))
18+
import Data.Proxy (Proxy (..))
1519
import Data.Vector.Generic (Vector)
1620
import Prelude (Either (..), Functor (fmap), Maybe (..), id, (.))
1721

22+
import qualified Data.List.NonEmpty as NE
1823
import qualified Data.Sequence as Seq
1924
import qualified Data.Vector as V
2025
import qualified Data.Vector.Generic as VG
@@ -55,15 +60,15 @@ instance Crosswalk [] where
5560
crosswalk f (x:xs) = alignWith cons (f x) (crosswalk f xs)
5661
where cons = these pure id (:)
5762

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+
5868
instance Crosswalk Seq.Seq where
5969
crosswalk f = foldr (alignWith cons . f) nil where
6070
cons = these Seq.singleton id (Seq.<|)
6171

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-
6772
crosswalkVector :: (Vector v a, Vector v b, Align f)
6873
=> (a -> f b) -> v a -> f (v b)
6974
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
7277
instance Crosswalk V.Vector where
7378
crosswalk = crosswalkVector
7479

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+
7589
instance Crosswalk ((,) a) where
7690
crosswalk fun (a, x) = fmap ((,) a) (fun x)
7791

7892
-- can't (shouldn't) do longer tuples until there are Functor and Foldable
7993
-- instances for them
8094

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+
81111
instance (Crosswalk f, Crosswalk g) => Crosswalk (Compose f g) where
82112
crosswalk f
83113
= fmap Compose -- can't coerce: maybe the Align-able thing has role nominal
@@ -113,3 +143,6 @@ instance Bicrosswalk These where
113143
bicrosswalk f _ (This x) = This <$> f x
114144
bicrosswalk _ g (That x) = That <$> g x
115145
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

these-tests/test/Tests/Crosswalk.hs

+14-3
Original file line numberDiff line numberDiff line change
@@ -3,10 +3,15 @@
33
{-# LANGUAGE ScopedTypeVariables #-}
44
module Tests.Crosswalk (crosswalkProps) where
55

6+
import Control.Applicative (Const)
67
import Control.Monad.Trans.Instances ()
78
import Data.Functor.Compose (Compose (..))
89
import Data.Functor.Identity (Identity (..))
10+
import Data.Functor.Sum (Sum)
11+
import Data.Functor.These (These1)
12+
import Data.List.NonEmpty (NonEmpty)
913
import Data.Map (Map)
14+
import Data.Proxy (Proxy)
1015
import Data.Semigroup (Semigroup (..))
1116
import Data.Sequence (Seq)
1217
import Data.Typeable (Typeable, typeOf1)
@@ -27,13 +32,19 @@ import Tests.Orphans ()
2732

2833
crosswalkProps :: TestTree
2934
crosswalkProps = testGroup "Crosswalk"
30-
[ crosswalkLaws (P :: P [])
35+
[ crosswalkLaws (P :: P Identity)
3136
, crosswalkLaws (P :: P Maybe)
32-
, crosswalkLaws (P :: P Identity)
33-
, crosswalkLaws (P :: P (These Int))
37+
, crosswalkLaws (P :: P [])
38+
, crosswalkLaws (P :: P NonEmpty)
3439
, crosswalkLaws (P :: P Seq)
3540
, crosswalkLaws (P :: P V.Vector)
41+
, crosswalkLaws (P :: P (Either Int))
42+
, crosswalkLaws (P :: P (These Int))
3643
, crosswalkLaws (P :: P ((,) Int))
44+
, crosswalkLaws (P :: P Proxy)
45+
, crosswalkLaws (P :: P (Const Int))
46+
, crosswalkLaws (P :: P (Sum [] []))
47+
, crosswalkLaws (P :: P (These1 [] []))
3748
, crosswalkLaws (P :: P (Compose [] []))
3849
]
3950

0 commit comments

Comments
 (0)