| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
GHC.Internal.Data.Semigroup.Internal
Description
Auxiliary definitions for Semigroup
This module provides some newtype wrappers and helpers which are
reexported from the Data.Semigroup module or imported directly
by some other modules.
This module also provides internal definitions related to the
Semigroup class some.
This module exists mostly to simplify or workaround import-graph issues.
@since base-4.11.0.0
Synopsis
- stimesIdempotent :: Integral b => b -> a -> a
- stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
- stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
- newtype Dual a = Dual {
- getDual :: a
- newtype Endo a = Endo {
- appEndo :: a -> a
- stimesEndoError :: a
- newtype All = All {}
- newtype Any = Any {}
- newtype Sum a = Sum {
- getSum :: a
- newtype Product a = Product {
- getProduct :: a
- newtype Alt (f :: k -> Type) (a :: k) = Alt {
- getAlt :: f a
Documentation
stimesIdempotent :: Integral b => b -> a -> a Source #
stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a Source #
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a Source #
The dual of a Monoid, obtained by swapping the arguments of (<>).
Dual a <> Dual b == Dual (b <> a)
Examples
>>>Dual "Hello" <> Dual "World"Dual {getDual = "WorldHello"}
>>>Dual (Dual "Hello") <> Dual (Dual "World")Dual {getDual = Dual {getDual = "HelloWorld"}}
Instances
| Applicative Dual Source # | @since base-4.8.0.0 | ||||
| Functor Dual Source # | @since base-4.8.0.0 | ||||
| Monad Dual Source # | @since base-4.8.0.0 | ||||
| MonadFix Dual Source # | @since base-4.8.0.0 | ||||
| Foldable Dual Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Dual m -> m Source # foldMap :: Monoid m => (a -> m) -> Dual a -> m Source # foldMap' :: Monoid m => (a -> m) -> Dual a -> m Source # foldr :: (a -> b -> b) -> b -> Dual a -> b Source # foldr' :: (a -> b -> b) -> b -> Dual a -> b Source # foldl :: (b -> a -> b) -> b -> Dual a -> b Source # foldl' :: (b -> a -> b) -> b -> Dual a -> b Source # foldr1 :: (a -> a -> a) -> Dual a -> a Source # foldl1 :: (a -> a -> a) -> Dual a -> a Source # toList :: Dual a -> [a] Source # null :: Dual a -> Bool Source # length :: Dual a -> Int Source # elem :: Eq a => a -> Dual a -> Bool Source # maximum :: Ord a => Dual a -> a Source # minimum :: Ord a => Dual a -> a Source # | |||||
| Traversable Dual Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
| Generic1 Dual Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Monoid a => Monoid (Dual a) Source # | @since base-2.01 | ||||
| Semigroup a => Semigroup (Dual a) Source # | @since base-4.9.0.0 | ||||
| Data a => Data (Dual a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dual a -> c (Dual a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dual a) Source # toConstr :: Dual a -> Constr Source # dataTypeOf :: Dual a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dual a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dual a)) Source # gmapT :: (forall b. Data b => b -> b) -> Dual a -> Dual a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Dual a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dual a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source # | |||||
| Bounded a => Bounded (Dual a) Source # | @since base-2.01 | ||||
| Generic (Dual a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Read a => Read (Dual a) Source # | @since base-2.01 | ||||
| Show a => Show (Dual a) Source # | @since base-2.01 | ||||
| Eq a => Eq (Dual a) Source # | @since base-2.01 | ||||
| Ord a => Ord (Dual a) Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep1 Dual Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep (Dual a) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
The monoid of endomorphisms under composition.
Endo f <> Endo g == Endo (f . g)
Examples
>>>let computation = Endo ("Hello, " ++) <> Endo (++ "!")>>>appEndo computation "Haskell""Hello, Haskell!"
>>>let computation = Endo (*3) <> Endo (+1)>>>appEndo computation 16
Instances
| Monoid (Endo a) Source # | @since base-2.01 | ||||
| Semigroup (Endo a) Source # | @since base-4.9.0.0 | ||||
| Generic (Endo a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| type Rep (Endo a) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
stimesEndoError :: a Source #
Boolean monoid under conjunction (&&).
All x <> All y = All (x && y)
Examples
>>>All True <> mempty <> All False)All {getAll = False}
>>>mconcat (map (\x -> All (even x)) [2,4,6,7,8])All {getAll = False}
>>>All True <> memptyAll {getAll = True}
Instances
| Monoid All Source # | @since base-2.01 | ||||
| Semigroup All Source # | @since base-4.9.0.0 | ||||
| Data All Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> All -> c All Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c All Source # toConstr :: All -> Constr Source # dataTypeOf :: All -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c All) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c All) Source # gmapT :: (forall b. Data b => b -> b) -> All -> All Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source # gmapQ :: (forall d. Data d => d -> u) -> All -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> All -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> All -> m All Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All Source # | |||||
| Bounded All Source # | @since base-2.01 | ||||
| Generic All Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Read All Source # | @since base-2.01 | ||||
| Show All Source # | @since base-2.01 | ||||
| Eq All Source # | @since base-2.01 | ||||
| Ord All Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep All Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Boolean monoid under disjunction (||).
Any x <> Any y = Any (x || y)
Examples
>>>Any True <> mempty <> Any FalseAny {getAny = True}
>>>mconcat (map (\x -> Any (even x)) [2,4,6,7,8])Any {getAny = True}
>>>Any False <> memptyAny {getAny = False}
Instances
| Monoid Any Source # | @since base-2.01 | ||||
| Semigroup Any Source # | @since base-4.9.0.0 | ||||
| Data Any Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Any -> c Any Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Any Source # toConstr :: Any -> Constr Source # dataTypeOf :: Any -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) Source # gmapT :: (forall b. Data b => b -> b) -> Any -> Any Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m Any Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any Source # | |||||
| Bounded Any Source # | @since base-2.01 | ||||
| Generic Any Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Read Any Source # | @since base-2.01 | ||||
| Show Any Source # | @since base-2.01 | ||||
| Eq Any Source # | @since base-2.01 | ||||
| Ord Any Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep Any Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Monoid under addition.
Sum a <> Sum b = Sum (a + b)
Examples
>>>Sum 1 <> Sum 2 <> memptySum {getSum = 3}
>>>mconcat [ Sum n | n <- [3 .. 9]]Sum {getSum = 42}
Instances
| Applicative Sum Source # | @since base-4.8.0.0 | ||||
| Functor Sum Source # | @since base-4.8.0.0 | ||||
| Monad Sum Source # | @since base-4.8.0.0 | ||||
| MonadFix Sum Source # | @since base-4.8.0.0 | ||||
| Foldable Sum Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Sum m -> m Source # foldMap :: Monoid m => (a -> m) -> Sum a -> m Source # foldMap' :: Monoid m => (a -> m) -> Sum a -> m Source # foldr :: (a -> b -> b) -> b -> Sum a -> b Source # foldr' :: (a -> b -> b) -> b -> Sum a -> b Source # foldl :: (b -> a -> b) -> b -> Sum a -> b Source # foldl' :: (b -> a -> b) -> b -> Sum a -> b Source # foldr1 :: (a -> a -> a) -> Sum a -> a Source # foldl1 :: (a -> a -> a) -> Sum a -> a Source # toList :: Sum a -> [a] Source # null :: Sum a -> Bool Source # length :: Sum a -> Int Source # elem :: Eq a => a -> Sum a -> Bool Source # maximum :: Ord a => Sum a -> a Source # minimum :: Ord a => Sum a -> a Source # | |||||
| Traversable Sum Source # | @since base-4.8.0.0 | ||||
| Generic1 Sum Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Num a => Monoid (Sum a) Source # | @since base-2.01 | ||||
| Num a => Semigroup (Sum a) Source # | @since base-4.9.0.0 | ||||
| Data a => Data (Sum a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) Source # toConstr :: Sum a -> Constr Source # dataTypeOf :: Sum a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) Source # gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source # | |||||
| Bounded a => Bounded (Sum a) Source # | @since base-2.01 | ||||
| Generic (Sum a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Num a => Num (Sum a) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| Read a => Read (Sum a) Source # | @since base-2.01 | ||||
| Show a => Show (Sum a) Source # | @since base-2.01 | ||||
| Eq a => Eq (Sum a) Source # | @since base-2.01 | ||||
| Ord a => Ord (Sum a) Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep1 Sum Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep (Sum a) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Monoid under multiplication.
Product x <> Product y == Product (x * y)
Examples
>>>Product 3 <> Product 4 <> memptyProduct {getProduct = 12}
>>>mconcat [ Product n | n <- [2 .. 10]]Product {getProduct = 3628800}
Constructors
| Product | |
Fields
| |
Instances
| Applicative Product Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| Functor Product Source # | @since base-4.8.0.0 | ||||
| Monad Product Source # | @since base-4.8.0.0 | ||||
| MonadFix Product Source # | @since base-4.8.0.0 | ||||
| Foldable Product Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Product m -> m Source # foldMap :: Monoid m => (a -> m) -> Product a -> m Source # foldMap' :: Monoid m => (a -> m) -> Product a -> m Source # foldr :: (a -> b -> b) -> b -> Product a -> b Source # foldr' :: (a -> b -> b) -> b -> Product a -> b Source # foldl :: (b -> a -> b) -> b -> Product a -> b Source # foldl' :: (b -> a -> b) -> b -> Product a -> b Source # foldr1 :: (a -> a -> a) -> Product a -> a Source # foldl1 :: (a -> a -> a) -> Product a -> a Source # toList :: Product a -> [a] Source # null :: Product a -> Bool Source # length :: Product a -> Int Source # elem :: Eq a => a -> Product a -> Bool Source # maximum :: Ord a => Product a -> a Source # minimum :: Ord a => Product a -> a Source # | |||||
| Traversable Product Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
| Generic1 Product Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Num a => Monoid (Product a) Source # | @since base-2.01 | ||||
| Num a => Semigroup (Product a) Source # | @since base-4.9.0.0 | ||||
| Data a => Data (Product a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product a -> c (Product a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product a) Source # toConstr :: Product a -> Constr Source # dataTypeOf :: Product a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product a)) Source # gmapT :: (forall b. Data b => b -> b) -> Product a -> Product a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Product a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Product a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source # | |||||
| Bounded a => Bounded (Product a) Source # | @since base-2.01 | ||||
| Generic (Product a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Num a => Num (Product a) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal Methods (+) :: Product a -> Product a -> Product a Source # (-) :: Product a -> Product a -> Product a Source # (*) :: Product a -> Product a -> Product a Source # negate :: Product a -> Product a Source # abs :: Product a -> Product a Source # signum :: Product a -> Product a Source # fromInteger :: Integer -> Product a Source # | |||||
| Read a => Read (Product a) Source # | @since base-2.01 | ||||
| Show a => Show (Product a) Source # | @since base-2.01 | ||||
| Eq a => Eq (Product a) Source # | @since base-2.01 | ||||
| Ord a => Ord (Product a) Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep1 Product Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep (Product a) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
newtype Alt (f :: k -> Type) (a :: k) Source #
Monoid under <|>.
Alt l <> Alt r == Alt (l <|> r)
Examples
>>>Alt (Just 12) <> Alt (Just 24)Alt {getAlt = Just 12}
>>>Alt Nothing <> Alt (Just 24)Alt {getAlt = Just 24}
@since base-4.8.0.0
Instances
| Generic1 (Alt f :: k -> Type) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Alternative f => Alternative (Alt f) Source # | @since base-4.8.0.0 | ||||
| Applicative f => Applicative (Alt f) Source # | @since base-4.8.0.0 | ||||
| Functor f => Functor (Alt f) Source # | @since base-4.8.0.0 | ||||
| Monad f => Monad (Alt f) Source # | @since base-4.8.0.0 | ||||
| MonadPlus f => MonadPlus (Alt f) Source # | @since base-4.8.0.0 | ||||
| MonadFix f => MonadFix (Alt f) Source # | @since base-4.8.0.0 | ||||
| Foldable f => Foldable (Alt f) Source # | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Alt f m -> m Source # foldMap :: Monoid m => (a -> m) -> Alt f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Alt f a -> m Source # foldr :: (a -> b -> b) -> b -> Alt f a -> b Source # foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source # foldl :: (b -> a -> b) -> b -> Alt f a -> b Source # foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source # foldr1 :: (a -> a -> a) -> Alt f a -> a Source # foldl1 :: (a -> a -> a) -> Alt f a -> a Source # toList :: Alt f a -> [a] Source # null :: Alt f a -> Bool Source # length :: Alt f a -> Int Source # elem :: Eq a => a -> Alt f a -> Bool Source # maximum :: Ord a => Alt f a -> a Source # minimum :: Ord a => Alt f a -> a Source # | |||||
| Traversable f => Traversable (Alt f) Source # | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
| Alternative f => Monoid (Alt f a) Source # | @since base-4.8.0.0 | ||||
| Alternative f => Semigroup (Alt f a) Source # | @since base-4.9.0.0 | ||||
| (Data (f a), Data a, Typeable f) => Data (Alt f a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) Source # toConstr :: Alt f a -> Constr Source # dataTypeOf :: Alt f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # | |||||
| Enum (f a) => Enum (Alt f a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal Methods succ :: Alt f a -> Alt f a Source # pred :: Alt f a -> Alt f a Source # toEnum :: Int -> Alt f a Source # fromEnum :: Alt f a -> Int Source # enumFrom :: Alt f a -> [Alt f a] Source # enumFromThen :: Alt f a -> Alt f a -> [Alt f a] Source # enumFromTo :: Alt f a -> Alt f a -> [Alt f a] Source # enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] Source # | |||||
| Generic (Alt f a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Num (f a) => Num (Alt f a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| Read (f a) => Read (Alt f a) Source # | @since base-4.8.0.0 | ||||
| Show (f a) => Show (Alt f a) Source # | @since base-4.8.0.0 | ||||
| Eq (f a) => Eq (Alt f a) Source # | @since base-4.8.0.0 | ||||
| Ord (f a) => Ord (Alt f a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep1 (Alt f :: k -> Type) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep (Alt f a) Source # | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||