matchable-0.1.1.1: A type class for Matchable Functors.

Safe HaskellNone
LanguageHaskell2010

Data.Matchable

Contents

Synopsis

Matchable class

class (Eq1 t, Functor t) => Matchable t where Source #

Containers that allows exact structural matching of two containers.

Minimal complete definition

zipMatchWith

Methods

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, then zipMatchWith f ta tb = Just tc.

    1. ta = fmap fst tab
    2. tb = fmap snd tab
    3. 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 # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: [a] -> [b] -> Maybe [(a, b)] Source #

zipMatchWith :: (a -> b -> Maybe c) -> [a] -> [b] -> Maybe [c] Source #

Matchable Maybe Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Maybe a -> Maybe b -> Maybe (Maybe (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Maybe a -> Maybe b -> Maybe (Maybe c) Source #

Matchable Identity Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Identity a -> Identity b -> Maybe (Identity (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Identity a -> Identity b -> Maybe (Identity c) Source #

Matchable NonEmpty Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: NonEmpty a -> NonEmpty b -> Maybe (NonEmpty (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> NonEmpty a -> NonEmpty b -> Maybe (NonEmpty c) Source #

Matchable IntMap Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: IntMap a -> IntMap b -> Maybe (IntMap (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> IntMap a -> IntMap b -> Maybe (IntMap c) Source #

Matchable Tree Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Tree a -> Tree b -> Maybe (Tree (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Tree a -> Tree b -> Maybe (Tree c) Source #

Matchable Seq Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Seq a -> Seq b -> Maybe (Seq (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Seq a -> Seq b -> Maybe (Seq c) Source #

Matchable Vector Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Vector a -> Vector b -> Maybe (Vector (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Vector a -> Vector b -> Maybe (Vector c) Source #

Eq e => Matchable (Either e) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Either e a -> Either e b -> Maybe (Either e (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Either e a -> Either e b -> Maybe (Either e c) Source #

Eq e => Matchable ((,) e) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: (e, a) -> (e, b) -> Maybe (e, (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> (e, a) -> (e, b) -> Maybe (e, c) Source #

Matchable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Proxy a -> Proxy b -> Maybe (Proxy (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Proxy a -> Proxy b -> Maybe (Proxy c) Source #

Eq k => Matchable (Map k) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Map k a -> Map k b -> Maybe (Map k (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Map k a -> Map k b -> Maybe (Map k c) Source #

(Eq k, Hashable k) => Matchable (HashMap k) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: HashMap k a -> HashMap k b -> Maybe (HashMap k (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> HashMap k a -> HashMap k b -> Maybe (HashMap k c) Source #

Eq k => Matchable (Const k :: Type -> Type) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Const k a -> Const k b -> Maybe (Const k (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Const k a -> Const k b -> Maybe (Const k c) Source #

Matchable (Tagged t) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Tagged t a -> Tagged t b -> Maybe (Tagged t (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Tagged t a -> Tagged t b -> Maybe (Tagged t c) Source #

(Matchable f, Matchable g) => Matchable (Product f g) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Product f g a -> Product f g b -> Maybe (Product f g (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Product f g a -> Product f g b -> Maybe (Product f g c) Source #

(Matchable f, Matchable g) => Matchable (Sum f g) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Sum f g a -> Sum f g b -> Maybe (Sum f g (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Sum f g a -> Sum f g b -> Maybe (Sum f g c) Source #

(Matchable f, Matchable g) => Matchable (Compose f g) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatch :: Compose f g a -> Compose f g b -> Maybe (Compose f g (a, b)) Source #

zipMatchWith :: (a -> b -> Maybe c) -> Compose f g a -> Compose f g b -> Maybe (Compose f g c) 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

Minimal complete definition

zipMatchWith'

Instances
Matchable' Par1 Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c) -> Par1 a -> Par1 b -> Maybe (Par1 c)

Matchable' (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c) -> V1 a -> V1 b -> Maybe (V1 c)

Matchable' (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c) -> U1 a -> U1 b -> Maybe (U1 c)

Matchable f => Matchable' (Rec1 f) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c) -> Rec1 f a -> Rec1 f b -> Maybe (Rec1 f c)

Eq c => Matchable' (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c0) -> K1 i c a -> K1 i c b -> Maybe (K1 i c c0)

(Matchable' f, Matchable' g) => Matchable' (f :+: g) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c) -> (f :+: g) a -> (f :+: g) b -> Maybe ((f :+: g) c)

(Matchable' f, Matchable' g) => Matchable' (f :*: g) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c) -> (f :*: g) a -> (f :*: g) b -> Maybe ((f :*: g) c)

Matchable' f => Matchable' (M1 i c f) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c0) -> M1 i c f a -> M1 i c f b -> Maybe (M1 i c f c0)

(Matchable f, Matchable' g) => Matchable' (f :.: g) Source # 
Instance details

Defined in Data.Matchable

Methods

zipMatchWith' :: (a -> b -> Maybe c) -> (f :.: g) a -> (f :.: g) b -> Maybe ((f :.: g) c)

genericZipMatchWith :: (Generic1 t, Matchable' (Rep1 t)) => (a -> b -> Maybe c) -> t a -> t b -> Maybe (t c) Source #

zipMatchWith via Generics.