Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (Eq1 t, Functor t) => Matchable t where
- zipMatch :: t a -> t b -> Maybe (t (a, b))
- zipMatchWith :: (a -> b -> Maybe c) -> t a -> t b -> Maybe (t c)
- zipzipMatch :: (Matchable t, Matchable u) => t (u a) -> t (u b) -> Maybe (t (u (a, b)))
- fmapRecovered :: Matchable t => (a -> b) -> t a -> t b
- eqDefault :: (Matchable t, Eq a) => t a -> t a -> Bool
- liftEqDefault :: Matchable t => (a -> b -> Bool) -> t a -> t b -> Bool
- class Matchable' t
- genericZipMatchWith :: (Generic1 t, Matchable' (Rep1 t)) => (a -> b -> Maybe c) -> t a -> t b -> Maybe (t c)
Matchable class
class (Eq1 t, Functor t) => Matchable t where Source #
Containers that allows exact structural matching of two containers.
zipMatch :: t a -> t b -> Maybe (t (a, b)) Source #
Decides if two structures match exactly. If they match, return zipped version of them.
zipMatch ta tb = Just tab
holds if and only if both of
ta = fmap fst tab tb = fmap snd tab
holds. Otherwise, zipMatch ta tb = Nothing
.
For example, the type signature of zipMatch
on the list Functor []
reads as follows:
zipMatch :: [a] -> [b] -> Maybe [(a,b)]
zipMatch as bs
returns Just (zip as bs)
if the lengths of two given lists are
same, and returns Nothing
otherwise.
Example
>>>
zipMatch [1, 2, 3] ['a', 'b', 'c']
Just [(1,'a'),(2,'b'),(3,'c')]>>>
zipMatch [1, 2, 3] ['a', 'b']
Nothing
zipMatchWith :: (a -> b -> Maybe c) -> t a -> t b -> Maybe (t c) Source #
Match two structures. If they match, zip them with given function
(a -> b -> Maybe c)
. Passed function can make whole match fail
by returning Nothing
.
A definition of zipMatchWith
must satisfy:
If there is a pair
(tab, tc)
such that fulfills all following three conditions, thenzipMatchWith f ta tb = Just tc
.ta = fmap fst tab
tb = fmap snd tab
fmap (uncurry f) tab = fmap Just tc
- If there are no such pair,
zipMatchWith f ta tb = Nothing
.
If t
is also Traversable
, the last condition can be dropped and
the equation can be stated without using tc
.
zipMatchWith f ta tb = traverse (uncurry f) tab
zipMatch
can be defined in terms of zipMatchWith
.
And if t
is also Traversable
, zipMatchWith
can be defined in terms of zipMatch
.
When you implement both of them by hand, keep their relation in the way
the default implementation is.
zipMatch = zipMatchWith (curry pure) zipMatchWith f ta tb = zipMatch ta tb >>= traverse (uncurry f)
Instances
Matchable [] Source # | |
Defined in Data.Matchable | |
Matchable Maybe Source # | |
Matchable Identity Source # | |
Matchable NonEmpty Source # | |
Matchable IntMap Source # | |
Matchable Tree Source # | |
Matchable Seq Source # | |
Matchable Vector Source # | |
Eq e => Matchable (Either e) Source # | |
Eq e => Matchable ((,) e) Source # | |
Defined in Data.Matchable | |
Matchable (Proxy :: Type -> Type) Source # | |
Eq k => Matchable (Map k) Source # | |
(Eq k, Hashable k) => Matchable (HashMap k) Source # | |
Eq k => Matchable (Const k :: Type -> Type) Source # | |
Matchable (Tagged t) Source # | |
(Matchable f, Matchable g) => Matchable (Product f g) Source # | |
(Matchable f, Matchable g) => Matchable (Sum f g) Source # | |
(Matchable f, Matchable g) => Matchable (Compose f g) Source # | |
zipzipMatch :: (Matchable t, Matchable u) => t (u a) -> t (u b) -> Maybe (t (u (a, b))) Source #
zipzipMatch = zipMatchWith zipMatch
fmapRecovered :: Matchable t => (a -> b) -> t a -> t b Source #
Matchable t
implies Functor t
.
It is not recommended to implement fmap
through this function,
so it is named fmapRecovered
but not fmapDefault
.
eqDefault :: (Matchable t, Eq a) => t a -> t a -> Bool Source #
Matchable t
implies Eq a => Eq (t a)
.
liftEqDefault :: Matchable t => (a -> b -> Bool) -> t a -> t b -> Bool Source #
Matchable t
implies Eq1 t
.
Define Matchable by Generic
class Matchable' t Source #
An instance of Matchable can be implemened through GHC Generics.
You only need to do two things: Make your type Functor
and Generic1
.
Example
>>>
:set -XDeriveFunctor
>>>
:set -XDeriveGeneric
>>>
:{
data MyTree label a = Leaf a | Node label [MyTree label a] deriving (Show, Read, Eq, Ord, Functor, Generic1) :}
Then you can use genericZipMatchWith
to implement zipMatchWith
method.
You also need Eq1
instance, but liftEqDefault
is provided.
>>>
:{
instance (Eq label) => Matchable (MyTree label) where zipMatchWith = genericZipMatchWith instance (Eq label) => Eq1 (MyTree label) where liftEq = liftEqDefault :}
>>>
zipMatch (Node "foo" [Leaf 1, Leaf 2]) (Node "foo" [Leaf 'a', Leaf 'b'])
Just (Node "foo" [Leaf (1,'a'),Leaf (2,'b')])>>>
zipMatch (Node "foo" [Leaf 1, Leaf 2]) (Node "bar" [Leaf 'a', Leaf 'b'])
Nothing>>>
zipMatch (Node "foo" [Leaf 1]) (Node "foo" [])
Nothing
zipMatchWith'
Instances
Matchable' Par1 Source # | |
Defined in Data.Matchable | |
Matchable' (V1 :: Type -> Type) Source # | |
Defined in Data.Matchable | |
Matchable' (U1 :: Type -> Type) Source # | |
Defined in Data.Matchable | |
Matchable f => Matchable' (Rec1 f) Source # | |
Defined in Data.Matchable | |
Eq c => Matchable' (K1 i c :: Type -> Type) Source # | |
Defined in Data.Matchable | |
(Matchable' f, Matchable' g) => Matchable' (f :+: g) Source # | |
Defined in Data.Matchable | |
(Matchable' f, Matchable' g) => Matchable' (f :*: g) Source # | |
Defined in Data.Matchable | |
Matchable' f => Matchable' (M1 i c f) Source # | |
Defined in Data.Matchable | |
(Matchable f, Matchable' g) => Matchable' (f :.: g) Source # | |
Defined in Data.Matchable |
genericZipMatchWith :: (Generic1 t, Matchable' (Rep1 t)) => (a -> b -> Maybe c) -> t a -> t b -> Maybe (t c) Source #
zipMatchWith via Generics.