{-# LANGUAGE FlexibleContexts #-}
module Generic.Data.Internal.Prelude where
import Control.Applicative (liftA2, Alternative(..))
import Data.Function (on)
import Data.Functor.Classes
import Data.Semigroup
import GHC.Generics
import Generic.Data.Internal.Utils (from', to', liftG2)
geq :: (Generic a, Eq (Rep a ())) => a -> a -> Bool
geq = (==) `on` from'
gcompare :: (Generic a, Ord (Rep a ())) => a -> a -> Ordering
gcompare = compare `on` from'
gmappend :: (Generic a, Semigroup (Rep a ())) => a -> a -> a
gmappend = \a b -> to (from' a <> from' b)
gmempty :: (Generic a, Monoid (Rep a ())) => a
gmempty = to' mempty
gmappend' :: (Generic a, Monoid (Rep a ())) => a -> a -> a
gmappend' = \a b -> to (from' a `mappend` from' b)
gfmap :: (Generic1 f, Functor (Rep1 f)) => (a -> b) -> f a -> f b
gfmap = \f -> to1 . fmap f . from1
gconstmap :: (Generic1 f, Functor (Rep1 f)) => a -> f b -> f a
gconstmap = \a -> to1 . (a <$) . from1
gpure :: (Generic1 f, Applicative (Rep1 f)) => a -> f a
gpure = to1 . pure
gap :: (Generic1 f, Applicative (Rep1 f)) => f (a -> b) -> f a -> f b
gap = liftG2 (<*>)
gliftA2 :: (Generic1 f, Applicative (Rep1 f)) => (a -> b -> c) -> f a -> f b -> f c
gliftA2 = liftG2 . liftA2
gempty :: (Generic1 f, Alternative (Rep1 f)) => f a
gempty = to1 empty
galt :: (Generic1 f, Alternative (Rep1 f)) => f a -> f a -> f a
galt = liftG2 (<|>)
gfoldMap :: (Generic1 f, Foldable (Rep1 f), Monoid m) => (a -> m) -> f a -> m
gfoldMap = \f -> foldMap f . from1
gfoldr :: (Generic1 f, Foldable (Rep1 f)) => (a -> b -> b) -> b -> f a -> b
gfoldr = \f b -> foldr f b . from1
gtraverse
:: (Generic1 f, Traversable (Rep1 f), Applicative m)
=> (a -> m b) -> f a -> m (f b)
gtraverse = \f -> fmap to1 . traverse f . from1
gsequenceA
:: (Generic1 f, Traversable (Rep1 f), Applicative m)
=> f (m a) -> m (f a)
gsequenceA = fmap to1 . sequenceA . from1
gliftEq :: (Generic1 f, Eq1 (Rep1 f)) => (a -> b -> Bool) -> f a -> f b -> Bool
gliftEq = \(==.) a b -> liftEq (==.) (from1 a) (from1 b)
gliftCompare
:: (Generic1 f, Ord1 (Rep1 f))
=> (a -> b -> Ordering) -> f a -> f b -> Ordering
gliftCompare = \compare' a b -> liftCompare compare' (from1 a) (from1 b)