Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Wrapped (c :: Type -> Constraint) a = Wrapped {
- unWrapped :: a
- newtype Wrapped1 (c :: (k -> Type) -> Constraint) f (a :: k) = Wrapped1 {
- unWrapped1 :: f a
- class GSemigroup f where
- gsop :: f x -> f x -> f x
- class GMonoid f where
- gmempty :: f x
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
. This way, they can be grouped into relatively few
deriving clauses per type.Wrapped
SomeClass
Instances
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
.
Wrapped1 | |
|
Instances
Wrapped Generic
Instances of
work on Wrapped
Generic
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 Monoid
s.
Likewise,
works on Wrapped1
Generic1
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.
Instances
GSemigroup (U1 :: k -> Type) Source # | |
Semigroup a => GSemigroup (K1 i a :: k -> Type) Source # | |
(GSemigroup f, GSemigroup g) => GSemigroup (f :*: g :: k -> Type) Source # | |
GSemigroup a => GSemigroup (M1 i c a :: k -> Type) Source # | |
class GMonoid f where Source #
Generic Monoid.
Exported just to give Haddock something to link to; use Wrapped Generic
with -XDerivingVia
instead.
Instances
GMonoid (U1 :: k -> Type) Source # | |
Defined in Data.Wrapped | |
Monoid a => GMonoid (K1 i a :: k -> Type) Source # | |
Defined in Data.Wrapped | |
(GMonoid f, GMonoid g) => GMonoid (f :*: g :: k -> Type) Source # | |
Defined in Data.Wrapped | |
GMonoid f => GMonoid (M1 i m f :: k -> Type) Source # | |
Defined in Data.Wrapped |
Wrapped IsList
Instances of
work by conversion to/from list.Wrapped
IsList
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
requires that the type is a type constructor
whose argument is the list element, this works on any type with an Foldable
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.