precursor-0.1.0.0: Prelude replacement

Safe HaskellNone
LanguageHaskell2010

Precursor.Algebra.Monoid

Contents

Synopsis

Monoid typeclass

class Monoid a where #

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

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend 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.

Minimal complete definition

mempty, mappend

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: () #

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

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

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ByteString 
Monoid ByteString 
Monoid IntSet 
Monoid Doc 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Monoid Builder 
Monoid [a] 

Methods

mempty :: [a] #

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

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

Monoid 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 there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

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

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

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

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

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

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

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

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

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

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

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

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

(Ord a, Bounded a) => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

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

(Ord a, Bounded a) => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

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

Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

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

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

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

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

Monoid (Endo a) 

Methods

mempty :: Endo a #

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

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

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

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

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

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

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

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

Monoid (First a) 

Methods

mempty :: First a #

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

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

Monoid (Last a) 

Methods

mempty :: Last a #

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

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

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

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

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

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

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

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

Monoid (Doc a) 

Methods

mempty :: Doc a #

mappend :: Doc a -> Doc a -> Doc a #

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

Semiring a => Monoid (Product a) # 

Methods

mempty :: Product a #

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

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

Semiring a => Monoid (Sum a) # 

Methods

mempty :: Sum a #

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

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

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

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

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

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

Methods

mempty :: (a, b) #

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

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

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

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

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

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

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

Methods

mempty :: (a, b, c) #

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

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

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

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

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

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a #

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

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

(Semigroup a, Monoid a) => Monoid (Tagged k s a) 

Methods

mempty :: Tagged k s a #

mappend :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mconcat :: [Tagged k s a] -> Tagged k s a #

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

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 a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

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) #

mempty :: Monoid a => a #

Identity of mappend

mappend :: Monoid a => a -> a -> a #

An associative operation

newtype Dual a :: * -> * #

The dual of a Monoid, obtained by swapping the arguments of mappend.

Constructors

Dual 

Fields

Instances

Monad Dual 

Methods

(>>=) :: Dual a -> (a -> Dual b) -> Dual b #

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

return :: a -> Dual a #

fail :: String -> Dual a #

Functor Dual 

Methods

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

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

MonadFix Dual 

Methods

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

Applicative Dual 

Methods

pure :: a -> Dual a #

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

(*>) :: Dual a -> Dual b -> Dual b #

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

Foldable Dual 

Methods

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

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

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

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

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

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

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

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

toList :: Dual a -> [a] #

null :: Dual a -> Bool #

length :: Dual a -> Int #

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

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

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

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

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

Traversable Dual 

Methods

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

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

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

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

Generic1 Dual 

Associated Types

type Rep1 (Dual :: * -> *) :: * -> * #

Methods

from1 :: Dual a -> Rep1 Dual a #

to1 :: Rep1 Dual a -> Dual a #

Bounded a => Bounded (Dual a) 

Methods

minBound :: Dual a #

maxBound :: Dual a #

Eq a => Eq (Dual a) 

Methods

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

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

Ord a => Ord (Dual a) 

Methods

compare :: Dual a -> Dual a -> Ordering #

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

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

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

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

max :: Dual a -> Dual a -> Dual a #

min :: Dual a -> Dual a -> Dual a #

Read a => Read (Dual a) 
Show a => Show (Dual a) 

Methods

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

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Generic (Dual a) 

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Dual a) 

Methods

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

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

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

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

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

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

type Rep1 Dual 
type Rep1 Dual = D1 (MetaData "Dual" "Data.Monoid" "base" True) (C1 (MetaCons "Dual" PrefixI True) (S1 (MetaSel (Just Symbol "getDual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Dual a) 
type Rep (Dual a) = D1 (MetaData "Dual" "Data.Monoid" "base" True) (C1 (MetaCons "Dual" PrefixI True) (S1 (MetaSel (Just Symbol "getDual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype Endo a :: * -> * #

The monoid of endomorphisms under composition.

Constructors

Endo 

Fields

Instances

Generic (Endo a) 

Associated Types

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

Methods

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

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

Semigroup (Endo a) 

Methods

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

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

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

Monoid (Endo a) 

Methods

mempty :: Endo a #

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

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

type Rep (Endo a) 
type Rep (Endo a) = D1 (MetaData "Endo" "Data.Monoid" "base" True) (C1 (MetaCons "Endo" PrefixI True) (S1 (MetaSel (Just Symbol "appEndo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (a -> a))))

Semiring wrappers

newtype Sum a Source #

Monoid under addition.

Constructors

Sum 

Fields

Instances

Monad Sum Source # 

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b #

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

return :: a -> Sum a #

fail :: String -> Sum a #

Functor Sum Source # 

Methods

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

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

Applicative Sum Source # 

Methods

pure :: a -> Sum a #

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

(*>) :: Sum a -> Sum b -> Sum b #

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

Generic1 Sum Source # 

Associated Types

type Rep1 (Sum :: * -> *) :: * -> * #

Methods

from1 :: Sum a -> Rep1 Sum a #

to1 :: Rep1 Sum a -> Sum a #

Bounded a => Bounded (Sum a) Source # 

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a) Source # 

Methods

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

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

Ord a => Ord (Sum a) Source # 

Methods

compare :: Sum a -> Sum a -> Ordering #

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

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

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

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

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Generic (Sum a) Source # 

Associated Types

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

Methods

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

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

Semiring a => Semigroup (Sum a) Source # 

Methods

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

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

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

Semiring a => Monoid (Sum a) Source # 

Methods

mempty :: Sum a #

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

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

TextShow a => TextShow (Sum a) Source # 

Methods

showbPrec :: Int -> Sum a -> Builder #

showb :: Sum a -> Builder #

showbList :: [Sum a] -> Builder #

showtPrec :: Int -> Sum a -> Text #

showt :: Sum a -> Text #

showtList :: [Sum a] -> Text #

showtlPrec :: Int -> Sum a -> Text #

showtl :: Sum a -> Text #

showtlList :: [Sum a] -> Text #

Num a => Num (Sum a) Source # 

Methods

fromInteger :: Integer -> Sum a Source #

type Rep1 Sum Source # 
type Rep1 Sum = D1 (MetaData "Sum" "Precursor.Algebra.Monoid" "precursor-0.1.0.0-CLpG2xMRVfMB9mhHgiVbN4" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just Symbol "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Sum a) Source # 
type Rep (Sum a) = D1 (MetaData "Sum" "Precursor.Algebra.Monoid" "precursor-0.1.0.0-CLpG2xMRVfMB9mhHgiVbN4" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just Symbol "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype Product a Source #

Monoid under multiplication.

Constructors

Product 

Fields

Instances

Monad Product Source # 

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b #

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

return :: a -> Product a #

fail :: String -> Product a #

Functor Product Source # 

Methods

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

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

Applicative Product Source # 

Methods

pure :: a -> Product a #

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

(*>) :: Product a -> Product b -> Product b #

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

Generic1 Product Source # 

Associated Types

type Rep1 (Product :: * -> *) :: * -> * #

Methods

from1 :: Product a -> Rep1 Product a #

to1 :: Rep1 Product a -> Product a #

Bounded a => Bounded (Product a) Source # 
Eq a => Eq (Product a) Source # 

Methods

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

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

Ord a => Ord (Product a) Source # 

Methods

compare :: Product a -> Product a -> Ordering #

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

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

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

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

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Generic (Product a) Source # 

Associated Types

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

Methods

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

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

Semiring a => Semigroup (Product a) Source # 

Methods

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

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

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

Semiring a => Monoid (Product a) Source # 

Methods

mempty :: Product a #

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

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

TextShow a => TextShow (Product a) Source # 
Num a => Num (Product a) Source # 
type Rep1 Product Source # 
type Rep1 Product = D1 (MetaData "Product" "Precursor.Algebra.Monoid" "precursor-0.1.0.0-CLpG2xMRVfMB9mhHgiVbN4" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just Symbol "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Product a) Source # 
type Rep (Product a) = D1 (MetaData "Product" "Precursor.Algebra.Monoid" "precursor-0.1.0.0-CLpG2xMRVfMB9mhHgiVbN4" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just Symbol "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

A better monoid for Maybe

newtype Option a :: * -> * #

Option is effectively Maybe with a better instance of Monoid, built off of an underlying Semigroup instead of an underlying Monoid.

Ideally, this type would not exist at all and we would just fix the Monoid instance of Maybe

Constructors

Option 

Fields

Instances

Monad Option 

Methods

(>>=) :: Option a -> (a -> Option b) -> Option b #

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

return :: a -> Option a #

fail :: String -> Option a #

Functor Option 

Methods

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

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

MonadFix Option 

Methods

mfix :: (a -> Option a) -> Option a #

Applicative Option 

Methods

pure :: a -> Option a #

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

(*>) :: Option a -> Option b -> Option b #

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

Foldable Option 

Methods

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

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

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

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

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

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

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

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

toList :: Option a -> [a] #

null :: Option a -> Bool #

length :: Option a -> Int #

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

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

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

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

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

Traversable Option 

Methods

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

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

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

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

Generic1 Option 

Associated Types

type Rep1 (Option :: * -> *) :: * -> * #

Methods

from1 :: Option a -> Rep1 Option a #

to1 :: Rep1 Option a -> Option a #

Alternative Option 

Methods

empty :: Option a #

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

some :: Option a -> Option [a] #

many :: Option a -> Option [a] #

MonadPlus Option 

Methods

mzero :: Option a #

mplus :: Option a -> Option a -> Option a #

Eq a => Eq (Option a) 

Methods

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

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

Data a => Data (Option a) 

Methods

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

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

toConstr :: Option a -> Constr #

dataTypeOf :: Option a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Option a) 

Methods

compare :: Option a -> Option a -> Ordering #

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

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

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

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

max :: Option a -> Option a -> Option a #

min :: Option a -> Option a -> Option a #

Read a => Read (Option a) 
Show a => Show (Option a) 

Methods

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

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Generic (Option a) 

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Option a) 

Methods

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

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

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

Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

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

type Rep1 Option 
type Rep1 Option = D1 (MetaData "Option" "Data.Semigroup" "base" True) (C1 (MetaCons "Option" PrefixI True) (S1 (MetaSel (Just Symbol "getOption") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))
type Rep (Option a) 
type Rep (Option a) = D1 (MetaData "Option" "Data.Semigroup" "base" True) (C1 (MetaCons "Option" PrefixI True) (S1 (MetaSel (Just Symbol "getOption") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))

option :: b -> (a -> b) -> Option a -> b #

Fold an Option case-wise, just like maybe.