wrapped-0.1.0.0: Provides a single standardized place to hang DerivingVia instances.
Safe HaskellNone
LanguageHaskell2010

Data.Wrapped

Description

Provides Wrapped and Wrapped1 types to hold DerivingVia instances.

Synopsis

Derived Instances

newtype Wrapped (c :: Type -> Constraint) a Source #

A type holding derived instances for classes of kind Type -> Constraint.

For example, Show or Pretty.

Generally, instances derived from SomeClass should be placed on Wrapped SomeClass. This way, they can be grouped into relatively few deriving clauses per type.

Constructors

Wrapped 

Fields

Instances

Instances details
IsList a => IsList (Wrapped IsList a) Source #

Just forwarding the instance; not meant to be used for deriving.

Instance details

Defined in Data.Wrapped

Associated Types

type Item (Wrapped IsList a) #

(IsList a, Eq (Item a)) => Eq (Wrapped IsList a) Source #

Equality of the results of toList.

Instance details

Defined in Data.Wrapped

(IsList a, Ord (Item a)) => Ord (Wrapped IsList a) Source #

Comparison of the results of toList.

Instance details

Defined in Data.Wrapped

(IsList a, Read (Item a)) => Read (Wrapped IsList a) Source #

fromList of a parsed list.

Instance details

Defined in Data.Wrapped

(IsList a, Show (Item a)) => Show (Wrapped IsList a) Source #

Show of the results of toList.

Instance details

Defined in Data.Wrapped

(Generic a, GSemigroup (Rep a)) => Semigroup (Wrapped Generic a) Source #

<> by field-wise <>.

Instance details

Defined in Data.Wrapped

(Generic a, GSemigroup (Rep a), GMonoid (Rep a)) => Monoid (Wrapped Generic a) Source #

mappend by field-wise <>, and mempty by field-wise mempty

Beware: this determines the entire instance including mappend, so do not mix this with a Semigroup instance from another source.

Instance details

Defined in Data.Wrapped

type Item (Wrapped IsList a) Source # 
Instance details

Defined in Data.Wrapped

type Item (Wrapped IsList a) = Item a

newtype Wrapped1 (c :: (k -> Type) -> Constraint) f (a :: k) Source #

A type holding derived instances of kind (k -> Type) -> Constraint.

For example, Functor or Traversable.

See also Wrapped.

Constructors

Wrapped1 

Fields

Instances

Instances details
Functor f => Functor (Wrapped1 (Generic1 :: (Type -> Type) -> Constraint) f) Source #

Forwarding instance for Functor.

If we want Wrapped1 Generic1 f to have instances for things with Functor as a superclass, then it needs to have a Functor instance. There's not much point in providing a Generics-based one, though because DeriveFunctor exists. So, just forward the underlying type's instance.

Instance details

Defined in Data.Wrapped

Methods

fmap :: (a -> b) -> Wrapped1 Generic1 f a -> Wrapped1 Generic1 f b #

(<$) :: a -> Wrapped1 Generic1 f b -> Wrapped1 Generic1 f a #

Foldable f => Foldable (Wrapped1 Foldable f) Source #

Just forwarding the instance; not meant to be used for deriving.

Instance details

Defined in Data.Wrapped

Methods

fold :: Monoid m => Wrapped1 Foldable f m -> m #

foldMap :: Monoid m => (a -> m) -> Wrapped1 Foldable f a -> m #

foldMap' :: Monoid m => (a -> m) -> Wrapped1 Foldable f a -> m #

foldr :: (a -> b -> b) -> b -> Wrapped1 Foldable f a -> b #

foldr' :: (a -> b -> b) -> b -> Wrapped1 Foldable f a -> b #

foldl :: (b -> a -> b) -> b -> Wrapped1 Foldable f a -> b #

foldl' :: (b -> a -> b) -> b -> Wrapped1 Foldable f a -> b #

foldr1 :: (a -> a -> a) -> Wrapped1 Foldable f a -> a #

foldl1 :: (a -> a -> a) -> Wrapped1 Foldable f a -> a #

toList :: Wrapped1 Foldable f a -> [a] #

null :: Wrapped1 Foldable f a -> Bool #

length :: Wrapped1 Foldable f a -> Int #

elem :: Eq a => a -> Wrapped1 Foldable f a -> Bool #

maximum :: Ord a => Wrapped1 Foldable f a -> a #

minimum :: Ord a => Wrapped1 Foldable f a -> a #

sum :: Num a => Wrapped1 Foldable f a -> a #

product :: Num a => Wrapped1 Foldable f a -> a #

(Foldable f, Eq a) => Eq (Wrapped1 Foldable f a) Source #

Equality of the results of toList.

Instance details

Defined in Data.Wrapped

(Foldable f, Ord a) => Ord (Wrapped1 Foldable f a) Source #

Comparison of the results of toList.

Instance details

Defined in Data.Wrapped

(Foldable f, Show a) => Show (Wrapped1 Foldable f a) Source #

Show of the results of toList.

Instance details

Defined in Data.Wrapped

(Applicative f, Semigroup a) => Semigroup (Wrapped1 Applicative f a) Source #

Provide (<>) by liftA2 of an underlying (<>).

Instance details

Defined in Data.Wrapped

(Applicative f, Monoid m) => Monoid (Wrapped1 Applicative f m) Source #

Provide mappend by liftA2 and mempty by pure mempty.

Instance details

Defined in Data.Wrapped

Wrapped Generic

Instances of Wrapped Generic work on Rep types by to and from.

Typically these implement the "obvious" way to make a sum-of-products type (an algebraic data type) an instance of the given class. For example, for Monoid, it provides field-wise mappend and mempty of types that are products of other Monoids.

Likewise, Wrapped1 Generic1 works on Rep1 types by to1 and from1. This is the same concept applied to type constructors with one parameter.

class GSemigroup f where Source #

Generic Semigroup.

Exported just to give Haddock something to link to; use Wrapped Generic with -XDerivingVia instead.

Methods

gsop :: f x -> f x -> f x Source #

Instances

Instances details
GSemigroup (U1 :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gsop :: forall (x :: k0). U1 x -> U1 x -> U1 x Source #

Semigroup a => GSemigroup (K1 i a :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gsop :: forall (x :: k0). K1 i a x -> K1 i a x -> K1 i a x Source #

(GSemigroup f, GSemigroup g) => GSemigroup (f :*: g :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gsop :: forall (x :: k0). (f :*: g) x -> (f :*: g) x -> (f :*: g) x Source #

GSemigroup a => GSemigroup (M1 i c a :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gsop :: forall (x :: k0). M1 i c a x -> M1 i c a x -> M1 i c a x Source #

class GMonoid f where Source #

Generic Monoid.

Exported just to give Haddock something to link to; use Wrapped Generic with -XDerivingVia instead.

Methods

gmempty :: f x Source #

Instances

Instances details
GMonoid (U1 :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gmempty :: forall (x :: k0). U1 x Source #

Monoid a => GMonoid (K1 i a :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gmempty :: forall (x :: k0). K1 i a x Source #

(GMonoid f, GMonoid g) => GMonoid (f :*: g :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gmempty :: forall (x :: k0). (f :*: g) x Source #

GMonoid f => GMonoid (M1 i m f :: k -> Type) Source # 
Instance details

Defined in Data.Wrapped

Methods

gmempty :: forall (x :: k0). M1 i m f x Source #

Wrapped IsList

Instances of Wrapped IsList work by conversion to/from list.

For example, we provide Eq, Ord, and Show instances that convert both operands to lists and compare them, and a Read instance that parses a list and converts to the desired type.

Whereas Wrapped Foldable requires that the type is a type constructor whose argument is the list element, this works on any type with an IsList instance.

On the other hand, IsList requires that the type can be converted from a list, not only to a list, so it can often require unneeded constraints compared to Foldable.

Generally, if both of these compile, they should be expected to be equivalent. More specifically, if you implement instances for Wrapped Foldable or Wrapped IsList these types, you should ensure that, as long as the Foldable instance of f and the IsList instance of f a are consistent, the instances are the same; and if you adopt instances from this type, you should ensure that your Foldable and IsList instances agree, and may then assume that IsList and Foldable give the same instances.

Instances of Wrapped Foldable work by folding over the type.

See above for a description of how this differs from Wrapped IsList.