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.Bounded.OneLiner

Contents

Description

Derived methods for Bounded, using Generics.OneLiner and GHC.Generics.

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

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

Synopsis

Newtype wrapper

newtype GBounded a Source #

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

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

Constructors

GBounded 

Fields

Instances

Functor GBounded Source # 

Methods

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

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

Foldable GBounded Source # 

Methods

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

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

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

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

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

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

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

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

toList :: GBounded a -> [a] #

null :: GBounded a -> Bool #

length :: GBounded a -> Int #

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

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

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

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

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

Traversable GBounded Source # 

Methods

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

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

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

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

(ADT a, Constraints a Bounded) => Bounded (GBounded a) Source # 
Eq a => Eq (GBounded a) Source # 

Methods

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

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

Data a => Data (GBounded a) Source # 

Methods

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

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

toConstr :: GBounded a -> Constr #

dataTypeOf :: GBounded a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (GBounded a) Source # 

Methods

compare :: GBounded a -> GBounded a -> Ordering #

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

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

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

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

max :: GBounded a -> GBounded a -> GBounded a #

min :: GBounded a -> GBounded a -> GBounded a #

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

Methods

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

show :: GBounded a -> String #

showList :: [GBounded a] -> ShowS #

Generic (GBounded a) Source # 

Associated Types

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

Methods

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

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

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

Generics-derived methods

gMinBound :: forall a. (ADT a, Constraints a Bounded) => a Source #

minBound implemented by using minBound for all of the components for the first constructor

gMaxBound :: forall a. (ADT a, Constraints a Bounded) => a Source #

maxBound implemented by using maxBound for all of the components for the last constructor