validity-0.12.0.2: Validity typeclass
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Validity

Description

Validity is used to specify additional invariants upon values that are not enforced by the type system.

Let's take an example. Suppose we were to implement a type Prime that represents prime integers.

If you were to completely enforce the invariant that the represented number is a prime, then we could use Natural and only store the index of the given prime in the infinite sequence of prime numbers. This is very safe but also very expensive if we ever want to use the number, because we would have to calculcate all the prime numbers until that index.

Instead we choose to implement Prime by a newtype Prime = Prime Int. Now we have to maintain the invariant that the Int that we use to represent the prime is in fact positive and a prime.

The Validity typeclass allows us to specify this invariant (and enables testing via the genvalidity libraries: https://hackage.haskell.org/package/genvalidity ):

instance Validity Prime where
    validate (Prime n) = check (isPrime n) "The 'Int' is prime."

If certain typeclass invariants exist, you can make these explicit in the validity instance as well. For example, 'Fixed a' is only valid if a has an HasResolution instance, so the correct validity instance is HasResolution a => Validity (Fixed a).

Synopsis

Documentation

class Validity a where Source #

A class of types that have additional invariants defined upon them

Minimal complete definition

Nothing

Methods

validate :: a -> Validation Source #

default validate :: (Generic a, GValidity (Rep a)) => a -> Validation Source #

Instances

Instances details
Validity Int16 Source # 
Instance details

Defined in Data.Validity

Validity Int32 Source # 
Instance details

Defined in Data.Validity

Validity Int64 Source #

Trivially valid

Instance details

Defined in Data.Validity

Validity Int8 Source # 
Instance details

Defined in Data.Validity

Validity Word16 Source # 
Instance details

Defined in Data.Validity

Validity Word32 Source # 
Instance details

Defined in Data.Validity

Validity Word64 Source #

Trivially valid

Instance details

Defined in Data.Validity

Validity Word8 Source # 
Instance details

Defined in Data.Validity

Validity Ordering Source #

Trivially valid

Instance details

Defined in Data.Validity

Validity ValidationChain Source # 
Instance details

Defined in Data.Validity

Validity Integer Source #

Trivially valid

Integer is not trivially valid under the hood, but instantiating Validity correctly would force validity to depend on a specific (big integer library integer-gmp versus integer-simple). This is rather impractical so for the time being we have opted for assuming that an Integer is always valid. Even though this is not technically sound, it is good enough for now.

Instance details

Defined in Data.Validity

Validity Natural Source #

Valid according to isValidNatural

Instance details

Defined in Data.Validity

Validity () Source #

Trivially valid

Instance details

Defined in Data.Validity

Methods

validate :: () -> Validation Source #

Validity Bool Source #

Trivially valid

Instance details

Defined in Data.Validity

Validity Char Source #

Trivially valid

Instance details

Defined in Data.Validity

Validity Double Source #

Trivially valid:

Instance details

Defined in Data.Validity

Validity Float Source #

Trivially valid:

Instance details

Defined in Data.Validity

Validity Int Source #

Trivially valid

Instance details

Defined in Data.Validity

Validity Word Source #

Trivially valid

Instance details

Defined in Data.Validity

(Validity a, Ord a, Num a, Integral a) => Validity (Ratio a) Source #

Valid if the contained numbers are valid and the denominator is strictly positive.

Instance details

Defined in Data.Validity

Validity a => Validity (NonEmpty a) Source #

A nonempty list is valid if all the elements are valid.

See the instance for 'Validity [a]' for more information.

Instance details

Defined in Data.Validity

Validity a => Validity (Maybe a) Source #

A Maybe thing is valid if the thing inside is valid or it's nothing It makes sense to assume that Nothing is valid. If Nothing wasn't valid, you wouldn't have used a Maybe in the datastructure.

Instance details

Defined in Data.Validity

Validity a => Validity [a] Source #

A list of things is valid if all of the things are valid.

This means that the empty list is considered valid. If the empty list should not be considered valid as part of your custom data type, make sure to write a custom Validity instance

Instance details

Defined in Data.Validity

Methods

validate :: [a] -> Validation Source #

(Validity a, Validity b) => Validity (Either a b) Source #

Any Either of things is valid if the contents are valid in either of the cases.

Instance details

Defined in Data.Validity

Methods

validate :: Either a b -> Validation Source #

HasResolution a => Validity (Fixed a) Source #

Valid according to the contained Integer.

Instance details

Defined in Data.Validity

(Validity a, Validity b) => Validity (a, b) Source #

Any tuple of things is valid if both of its elements are valid

Instance details

Defined in Data.Validity

Methods

validate :: (a, b) -> Validation Source #

(Validity a, Validity b, Validity c) => Validity (a, b, c) Source #

Any triple of things is valid if all three of its elements are valid

Instance details

Defined in Data.Validity

Methods

validate :: (a, b, c) -> Validation Source #

(Validity a, Validity b, Validity c, Validity d) => Validity (a, b, c, d) Source #

Any quadruple of things is valid if all four of its elements are valid

Instance details

Defined in Data.Validity

Methods

validate :: (a, b, c, d) -> Validation Source #

(Validity a, Validity b, Validity c, Validity d, Validity e) => Validity (a, b, c, d, e) Source #

Any quintuple of things is valid if all five of its elements are valid

Instance details

Defined in Data.Validity

Methods

validate :: (a, b, c, d, e) -> Validation Source #

(Validity a, Validity b, Validity c, Validity d, Validity e, Validity f) => Validity (a, b, c, d, e, f) Source #

Any sextuple of things is valid if all six of its elements are valid

Instance details

Defined in Data.Validity

Methods

validate :: (a, b, c, d, e, f) -> Validation Source #

Helper functions to define validate

trivialValidation :: a -> Validation Source #

Declare any value to be valid in validation

trivialValidation a = seq a mempty

genericValidate :: (Generic a, GValidity (Rep a)) => a -> Validation Source #

check :: Bool -> String -> Validation Source #

Check that a given invariant holds.

The given string should describe the invariant, not the violation.

Example:

check (x < 5) "x is strictly smaller than 5"

instead of

check (x < 5) "x is greater than 5"

declare :: String -> Bool -> Validation Source #

check, but with the arguments flipped

annotate :: Validity a => a -> String -> Validation Source #

Declare a sub-part as a necessary part for validation, and annotate it with a name.

Example:

validate (a, b) =
    mconcat
        [ annotate a "The first element of the tuple"
        , annotate b "The second element of the tuple"
        ]

delve :: Validity a => String -> a -> Validation Source #

annotate, but with the arguments flipped.

decorate :: String -> Validation -> Validation Source #

Decorate a validation with a location

decorateList :: [a] -> (a -> Validation) -> Validation Source #

Decorate a piecewise validation of a list with their location in the list

decorateString :: String -> (Char -> Validation) -> Validation Source #

decorateList, but specifically for Strings

decorateString = decorateList

invalid :: String -> Validation Source #

Construct a trivially invalid Validation

Example:

data Wrong
    = Wrong
    | Fine
    deriving (Show, Eq)

instance Validity Wrong where
    validate w =
        case w of
            Wrong -> invalid "Wrong"
            Fine -> valid

Helpers for specific types

Char

RealFloat (Double)

Ratio

Utilities

Utilities for validity checking

isValid :: Validity a => a -> Bool Source #

Check whether a value is valid.

isInvalid :: Validity a => a -> Bool Source #

Check whether a value is not valid.

isInvalid = not . isValid

constructValid :: Validity a => a -> Maybe a Source #

Construct a valid element from an unchecked element

constructValidUnsafe :: (Show a, Validity a) => a -> a Source #

Construct a valid element from an unchecked element, throwing error on invalid elements.

Utilities for validation

newtype Validation Source #

The result of validating a value.

mempty means the value was valid.

This type intentionally doesn't have a Validity instance to make sure you can never accidentally use annotate or delve twice.

Constructors

Validation 

Instances

Instances details
Monoid Validation Source # 
Instance details

Defined in Data.Validity

Semigroup Validation Source # 
Instance details

Defined in Data.Validity

Generic Validation Source # 
Instance details

Defined in Data.Validity

Associated Types

type Rep Validation :: Type -> Type #

Show Validation Source # 
Instance details

Defined in Data.Validity

Eq Validation Source # 
Instance details

Defined in Data.Validity

type Rep Validation Source # 
Instance details

Defined in Data.Validity

type Rep Validation = D1 ('MetaData "Validation" "Data.Validity" "validity-0.12.0.2-K6MdFMs3vO79SP2A0X7wiz" 'True) (C1 ('MetaCons "Validation" 'PrefixI 'True) (S1 ('MetaSel ('Just "unValidation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ValidationChain])))

data ValidationChain Source #

checkValidity :: Validity a => a -> Either [ValidationChain] a Source #

validate a given value.

This function returns either all the reasons why the given value is invalid, in the form of a list of ValidationChains, or it returns Right with the input value, as evidence that it is valid.

Note: You may want to use prettyValidation instead, if you want to display these ValidationChains to a user.

validationIsValid :: Validation -> Bool Source #

Check if a Validation concerns a valid value.

prettyValidate :: Validity a => a -> Either String a Source #

Validate a given value

This function will return a nice error if the value is invalid. It will return the original value in Right if it was valid, as evidence that it has been validated.

prettyValidation :: Validation -> Maybe String Source #

Render a Validation in a somewhat pretty way.

This function will return Nothing if the Validation concerned a valid value.

Re-exports

class Semigroup a => Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:

Right identity
x <> mempty = x
Left identity
mempty <> x = x
Associativity
x <> (y <> z) = (x <> y) <> z (Semigroup law)
Concatenation
mconcat = foldr (<>) mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

>>> "Hello world" <> mempty
"Hello world"

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = (<>) since base-4.11.0.0. Should it be implemented manually, since mappend is a synonym for (<>), it is expected that the two functions are defined the same way. In a future GHC release mappend will be removed from Monoid.

mconcat :: [a] -> a #

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

>>> mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"

Instances

Instances details
Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid Validation Source # 
Instance details

Defined in Data.Validity

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

FiniteBits a => Monoid (And a)

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: And a #

mappend :: And a -> And a -> And a #

mconcat :: [And a] -> And a #

FiniteBits a => Monoid (Iff a)

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Iff a #

mappend :: Iff a -> Iff a -> Iff a #

mconcat :: [Iff a] -> Iff a #

Bits a => Monoid (Ior a)

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Ior a #

mappend :: Ior a -> Ior a -> Ior a #

mconcat :: [Ior a] -> Ior a #

Bits a => Monoid (Xor a)

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Xor a #

mappend :: Xor a -> Xor a -> Xor a #

mconcat :: [Xor a] -> Xor a #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

mconcat :: [Down a] -> Down a #

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Monoid p => Monoid (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p #

mappend :: Par1 p -> Par1 p -> Par1 p #

mconcat :: [Par1 p] -> Par1 p #

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (a)

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

mempty :: (a) #

mappend :: (a) -> (a) -> (a) #

mconcat :: [(a)] -> (a) #

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid a => Monoid (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

mconcat :: [Const a b] -> Const a b #

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

Monoid (f p) => Monoid (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p #

mconcat :: [Rec1 f p] -> Rec1 f p #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

Monoid c => Monoid (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p #

mappend :: K1 i c p -> K1 i c p -> K1 i c p #

mconcat :: [K1 i c p] -> K1 i c p #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

mconcat :: [(f :.: g) p] -> (f :.: g) p #

Monoid (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

class Semigroup a where #

The class of semigroups (types with an associative binary operation).

Instances should satisfy the following:

Associativity
x <> (y <> z) = (x <> y) <> z

Since: base-4.9.0.0

Methods

(<>) :: a -> a -> a infixr 6 #

An associative operation.

>>> [1,2,3] <> [4,5,6]
[1,2,3,4,5,6]

Instances

Instances details
Semigroup All

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Semigroup Any

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Semigroup Ordering

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Semigroup Validation Source # 
Instance details

Defined in Data.Validity

Semigroup ()

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: () -> () -> () #

sconcat :: NonEmpty () -> () #

stimes :: Integral b => b -> () -> () #

Bits a => Semigroup (And a)

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: And a -> And a -> And a #

sconcat :: NonEmpty (And a) -> And a #

stimes :: Integral b => b -> And a -> And a #

FiniteBits a => Semigroup (Iff a)

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: Iff a -> Iff a -> Iff a #

sconcat :: NonEmpty (Iff a) -> Iff a #

stimes :: Integral b => b -> Iff a -> Iff a #

Bits a => Semigroup (Ior a)

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: Ior a -> Ior a -> Ior a #

sconcat :: NonEmpty (Ior a) -> Ior a #

stimes :: Integral b => b -> Ior a -> Ior a #

Bits a => Semigroup (Xor a)

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: Xor a -> Xor a -> Xor a #

sconcat :: NonEmpty (Xor a) -> Xor a #

stimes :: Integral b => b -> Xor a -> Xor a #

Semigroup a => Semigroup (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Semigroup (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Semigroup a => Semigroup (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(<>) :: Down a -> Down a -> Down a #

sconcat :: NonEmpty (Down a) -> Down a #

stimes :: Integral b => b -> Down a -> Down a #

Semigroup a => Semigroup (Dual a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a #

sconcat :: NonEmpty (Dual a) -> Dual a #

stimes :: Integral b => b -> Dual a -> Dual a #

Semigroup (Endo a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a #

sconcat :: NonEmpty (Endo a) -> Endo a #

stimes :: Integral b => b -> Endo a -> Endo a #

Num a => Semigroup (Product a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Num a => Semigroup (Sum a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Semigroup p => Semigroup (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: Par1 p -> Par1 p -> Par1 p #

sconcat :: NonEmpty (Par1 p) -> Par1 p #

stimes :: Integral b => b -> Par1 p -> Par1 p #

Semigroup a => Semigroup (IO a)

Since: base-4.10.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: IO a -> IO a -> IO a #

sconcat :: NonEmpty (IO a) -> IO a #

stimes :: Integral b => b -> IO a -> IO a #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Semigroup a => Semigroup (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Semigroup a => Semigroup (a)

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a) -> (a) #

stimes :: Integral b => b -> (a) -> (a) #

Semigroup [a]

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: [a] -> [a] -> [a] #

sconcat :: NonEmpty [a] -> [a] #

stimes :: Integral b => b -> [a] -> [a] #

Semigroup (Either a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b0 => b0 -> Either a b -> Either a b #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Semigroup (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: U1 p -> U1 p -> U1 p #

sconcat :: NonEmpty (U1 p) -> U1 p #

stimes :: Integral b => b -> U1 p -> U1 p #

Semigroup (V1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: V1 p -> V1 p -> V1 p #

sconcat :: NonEmpty (V1 p) -> V1 p #

stimes :: Integral b => b -> V1 p -> V1 p #

Semigroup b => Semigroup (a -> b)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a -> b) -> a -> b #

stimes :: Integral b0 => b0 -> (a -> b) -> a -> b #

(Semigroup a, Semigroup b) => Semigroup (a, b)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) #

sconcat :: NonEmpty (a, b) -> (a, b) #

stimes :: Integral b0 => b0 -> (a, b) -> (a, b) #

Semigroup a => Semigroup (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(<>) :: Const a b -> Const a b -> Const a b #

sconcat :: NonEmpty (Const a b) -> Const a b #

stimes :: Integral b0 => b0 -> Const a b -> Const a b #

(Applicative f, Semigroup a) => Semigroup (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a #

sconcat :: NonEmpty (Ap f a) -> Ap f a #

stimes :: Integral b => b -> Ap f a -> Ap f a #

Alternative f => Semigroup (Alt f a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a #

sconcat :: NonEmpty (Alt f a) -> Alt f a #

stimes :: Integral b => b -> Alt f a -> Alt f a #

Semigroup (f p) => Semigroup (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: Rec1 f p -> Rec1 f p -> Rec1 f p #

sconcat :: NonEmpty (Rec1 f p) -> Rec1 f p #

stimes :: Integral b => b -> Rec1 f p -> Rec1 f p #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) #

stimes :: Integral b0 => b0 -> (a, b, c) -> (a, b, c) #

(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

sconcat :: NonEmpty ((f :*: g) p) -> (f :*: g) p #

stimes :: Integral b => b -> (f :*: g) p -> (f :*: g) p #

Semigroup c => Semigroup (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: K1 i c p -> K1 i c p -> K1 i c p #

sconcat :: NonEmpty (K1 i c p) -> K1 i c p #

stimes :: Integral b => b -> K1 i c p -> K1 i c p #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) #

stimes :: Integral b0 => b0 -> (a, b, c, d) -> (a, b, c, d) #

Semigroup (f (g p)) => Semigroup ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

sconcat :: NonEmpty ((f :.: g) p) -> (f :.: g) p #

stimes :: Integral b => b -> (f :.: g) p -> (f :.: g) p #

Semigroup (f p) => Semigroup (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: M1 i c f p -> M1 i c f p -> M1 i c f p #

sconcat :: NonEmpty (M1 i c f p) -> M1 i c f p #

stimes :: Integral b => b -> M1 i c f p -> M1 i c f p #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) #

stimes :: Integral b0 => b0 -> (a, b, c, d, e) -> (a, b, c, d, e) #