{-# LANGUAGE DeriveFunctor
, DeriveGeneric
, FlexibleContexts
, FlexibleInstances
, FunctionalDependencies
, KindSignatures
, MultiParamTypeClasses
, ScopedTypeVariables
, TypeOperators
, TypeSynonymInstances
, UndecidableInstances
#-}
module Data.Filter
(
constrName
, HasConstructor (..)
, ReduceWith (..)
, Reduce (..)
, (=?=)
, (==>)
, (<||>)
, any_
, (<&&>)
, all_
, Infinite (..)
, mapMaybe
) where
import Control.Monad
import Data.Default
import Data.List
import Data.Maybe
import GHC.Generics
constrName :: (HasConstructor (Rep a), Generic a) => a -> String
constrName = genericConstrName . from
class HasConstructor (f :: * -> *) where
genericConstrName :: f x -> String
instance HasConstructor f => HasConstructor (D1 c f) where
genericConstrName (M1 x) = genericConstrName x
instance (HasConstructor x, HasConstructor y) => HasConstructor (x :+: y) where
genericConstrName (L1 l) = genericConstrName l
genericConstrName (R1 r) = genericConstrName r
instance Constructor c => HasConstructor (C1 c f) where
genericConstrName x = conName x
class ReduceWith a where
reduceWith :: a
reduceWith = undefined
instance {-# OVERLAPPING #-} ReduceWith Bool where
reduceWith = True
instance {-# OVERLAPPING #-} ReduceWith Char where
reduceWith = ' '
instance {-# OVERLAPPABLE #-} (Default a) => ReduceWith a where
reduceWith = def
class (HasConstructor (Rep c), Generic c) => Reduce a c | a -> c where
reduce :: a -> c
instance {-# OVERLAPPABLE #-} (HasConstructor (Rep a), Generic a) => Reduce a a where
reduce = id
instance {-# OVERLAPPABLE #-} (ReduceWith a, Reduce b c) => Reduce (a -> b) c where
reduce = reduce . ($ reduceWith)
(=?=) :: (Reduce a c, Reduce b c) => a -> b -> Bool
infixl 4 =?=
(=?=) a b = constrName (reduce a) == constrName (reduce b)
(==>) :: (a -> Bool) -> (a -> b) -> a -> Maybe b
(==>) p f x = if p x then Just $ f x else Nothing
(<||>) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
infixl 2 <||>
(<||>) = liftM2 (||)
any_ :: [a -> Bool] -> a -> Bool
any_ = foldl' (<||>) $ const False
(<&&>) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
infixl 3 <&&>
(<&&>) = liftM2 (&&)
all_ :: [a -> Bool] -> a -> Bool
all_ = foldl' (<&&>) $ const True
data Infinite a
= NegInfin
| Exact !a
| PosInfin
deriving (Eq, Functor, Read, Show, Ord, Generic)
instance (Eq a, Bounded a, Enum a) => Enum (Infinite a) where
fromEnum NegInfin = fromEnum (minBound :: a) - 1
fromEnum (Exact x) = fromEnum x
fromEnum PosInfin = fromEnum (maxBound :: a) + 1
toEnum x | x == fromEnum (minBound :: a) - 1 = NegInfin
| x == fromEnum (maxBound :: a) + 1 = PosInfin
| otherwise = Exact $ toEnum x
succ NegInfin = Exact minBound
succ PosInfin = PosInfin
succ (Exact x)
| x == maxBound = PosInfin
| otherwise = Exact $ succ x
pred NegInfin = NegInfin
pred PosInfin = Exact maxBound
pred (Exact x)
| x == minBound = NegInfin
| otherwise = Exact $ pred x
instance (Default a) => Default (Infinite a) where
def = Exact def