one-liner-instances-0.1.2.0: Generics-based implementations for common typeclasses

Copyright(c) Justin Le 2018
LicenseBSD-3
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Ord.OneLiner

Contents

Description

Derived methods for Eq and Ord, using Generics.OneLiner and GHC.Generics.

Can be used for any types (deriving Generic) where every field is an instance of Eq (or Ord).

Also includes a newtype wrapper that imbues any such data type with instant Eq and Ord instances, which can one day be used with DerivingVia syntax to derive instances automatically.

Synopsis

Newtype wrapper

newtype GOrd a Source #

If a is a data type whose fields are all instances of Eq, then GOrd a has a Eq instance.

If a is a data type whose fields are all instances of Ord, then GOrd a has a Ord instance.

Will one day be able to be used with DerivingVia syntax, to derive instances automatically.

Constructors

GOrd 

Fields

Instances

Functor GOrd Source # 

Methods

fmap :: (a -> b) -> GOrd a -> GOrd b #

(<$) :: a -> GOrd b -> GOrd a #

Foldable GOrd Source # 

Methods

fold :: Monoid m => GOrd m -> m #

foldMap :: Monoid m => (a -> m) -> GOrd a -> m #

foldr :: (a -> b -> b) -> b -> GOrd a -> b #

foldr' :: (a -> b -> b) -> b -> GOrd a -> b #

foldl :: (b -> a -> b) -> b -> GOrd a -> b #

foldl' :: (b -> a -> b) -> b -> GOrd a -> b #

foldr1 :: (a -> a -> a) -> GOrd a -> a #

foldl1 :: (a -> a -> a) -> GOrd a -> a #

toList :: GOrd a -> [a] #

null :: GOrd a -> Bool #

length :: GOrd a -> Int #

elem :: Eq a => a -> GOrd a -> Bool #

maximum :: Ord a => GOrd a -> a #

minimum :: Ord a => GOrd a -> a #

sum :: Num a => GOrd a -> a #

product :: Num a => GOrd a -> a #

Traversable GOrd Source # 

Methods

traverse :: Applicative f => (a -> f b) -> GOrd a -> f (GOrd b) #

sequenceA :: Applicative f => GOrd (f a) -> f (GOrd a) #

mapM :: Monad m => (a -> m b) -> GOrd a -> m (GOrd b) #

sequence :: Monad m => GOrd (m a) -> m (GOrd a) #

(ADT a, Constraints a Eq) => Eq (GOrd a) Source # 

Methods

(==) :: GOrd a -> GOrd a -> Bool #

(/=) :: GOrd a -> GOrd a -> Bool #

Data a => Data (GOrd a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GOrd a -> c (GOrd a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GOrd a) #

toConstr :: GOrd a -> Constr #

dataTypeOf :: GOrd a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (GOrd a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GOrd a)) #

gmapT :: (forall b. Data b => b -> b) -> GOrd a -> GOrd a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GOrd a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GOrd a -> r #

gmapQ :: (forall d. Data d => d -> u) -> GOrd a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GOrd a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GOrd a -> m (GOrd a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GOrd a -> m (GOrd a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GOrd a -> m (GOrd a) #

(ADT a, Constraints a Eq, Constraints a Ord) => Ord (GOrd a) Source # 

Methods

compare :: GOrd a -> GOrd a -> Ordering #

(<) :: GOrd a -> GOrd a -> Bool #

(<=) :: GOrd a -> GOrd a -> Bool #

(>) :: GOrd a -> GOrd a -> Bool #

(>=) :: GOrd a -> GOrd a -> Bool #

max :: GOrd a -> GOrd a -> GOrd a #

min :: GOrd a -> GOrd a -> GOrd a #

Read a => Read (GOrd a) Source # 
Show a => Show (GOrd a) Source # 

Methods

showsPrec :: Int -> GOrd a -> ShowS #

show :: GOrd a -> String #

showList :: [GOrd a] -> ShowS #

Generic (GOrd a) Source # 

Associated Types

type Rep (GOrd a) :: * -> * #

Methods

from :: GOrd a -> Rep (GOrd a) x #

to :: Rep (GOrd a) x -> GOrd a #

type Rep (GOrd a) Source # 
type Rep (GOrd a) = D1 * (MetaData "GOrd" "Data.Ord.OneLiner" "one-liner-instances-0.1.2.0-1uJ4q7KgUngCJixYpNuD63" True) (C1 * (MetaCons "GOrd" PrefixI True) (S1 * (MetaSel (Just Symbol "getGOrd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))

Generics-derived methods

Eq

gEquals :: forall a. (ADT a, Constraints a Eq) => a -> a -> Bool Source #

== implemented by using == between all of the components, lexicographically. First compares constructors.

gNotEquals :: forall a. (ADT a, Constraints a Eq) => a -> a -> Bool Source #

/= implemented by using /= between all of the components, lexicographically. First compares constructors.

Ord

gCompare :: forall a. (ADT a, Constraints a Ord) => a -> a -> Ordering Source #

compare implemented by using compare between all of the components, lexicographically. First compares constructors.

gLTE :: forall a. (ADT a, Constraints a Ord) => a -> a -> Bool Source #

<= implemented by using <= between all of the components. First compares constructors.

gLT :: forall a. (ADT a, Constraints a Ord) => a -> a -> Bool Source #

< implemented by using < between all of the components. First compares constructors.

gGTE :: forall a. (ADT a, Constraints a Ord) => a -> a -> Bool Source #

>= implemented by using >= between all of the components. First compares constructors.

gGT :: forall a. (ADT a, Constraints a Ord) => a -> a -> Bool Source #

> implemented by using > between all of the components. First compares constructors.

gMax :: forall a. (ADT a, Constraints a Ord) => a -> a -> a Source #

max implemented by using max between all of the components. First compares constructors. If two items are equal, returns the second.

gMin :: forall a. (ADT a, Constraints a Ord) => a -> a -> a Source #

min implemented by using min between all of the components. First compares constructors. If two items are equal, returns the first.