module Language.FunPat.Instances where
import Language.FunPat.Match
instance Matchable () where
() .=. () = Just []
instance Matchable Bool where
a .=. b
| a == b = Just []
| otherwise = Nothing
instance Matchable Char where
a .=. b
| a == b = Just []
| otherwise = Nothing
instance Matchable Integer where
a .=. b
| a == b = Just []
| otherwise = Nothing
instance Matchable Int where
a .=. b
| a == b = Just []
| otherwise = Nothing
instance Matchable Float where
a .=. b
| a == b = Just []
| otherwise = Nothing
instance Matchable Ordering where
x .=. y
| x == y = Just []
| otherwise = Nothing
instance Matchable Double where
x .=. y
| x == y = Just []
| otherwise = Nothing
instance (Matchable a, Matchable b) =>
Matchable (a,b)
where
(a,b) .=. (a',b') = Just [a :=: a', b :=: b']
instance (Matchable a, Matchable b, Matchable c) =>
Matchable (a,b,c)
where
(a,b,c) .=. (a',b',c') = Just [a :=: a', b :=: b', c :=: c' ]
instance (Matchable a, Matchable b, Matchable c, Matchable d) =>
Matchable (a,b,c,d)
where
(a,b,c,d) .=. (a',b',c',d') = Just [a :=: a', b :=: b', c :=: c', d :=: d' ]
instance (Matchable a, Matchable b, Matchable c, Matchable d, Matchable e) =>
Matchable (a,b,c,d,e)
where
(a,b,c,d,e) .=. (a',b',c',d',e') = Just [a :=: a', b :=: b', c :=: c', d :=: d', e :=: e' ]
instance (Matchable a, Matchable b, Matchable c, Matchable d, Matchable e, Matchable f) =>
Matchable (a,b,c,d,e,f)
where
(a,b,c,d,e,f) .=. (a',b',c',d',e',f') = Just [a :=: a', b :=: b', c :=: c', d :=: d', e :=: e', f :=: f' ]
instance (Matchable a, Matchable b, Matchable c, Matchable d, Matchable e, Matchable f, Matchable g) =>
Matchable (a,b,c,d,e,f,g)
where
(a,b,c,d,e,f,g) .=. (a',b',c',d',e',f',g') = Just [a :=: a', b :=: b', c :=: c', d :=: d', e :=: e', f :=: f', g :=: g' ]
instance (Matchable a) =>
Matchable [a]
where
[] .=. [] = Just []
(x:xs) .=. (y:ys) = Just [x :=: y, xs :=: ys]
_ .=. _ = Nothing
instance (Matchable a) =>
Matchable (Maybe a)
where
Just x .=. Just y = Just [x :=: y]
Nothing .=. Nothing = Just []
_ .=. _ = Nothing
instance (Matchable a, Matchable b) =>
Matchable (Either a b)
where
Left x .=. Left y = Just [x :=: y]
Right x .=. Right y = Just [x :=: y]
_ .=. _ = Nothing