{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- | 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; there is also a .hs-boot file to allow "GHC.Base" and other
-- modules to import method default implementations for 'stimes'
--
-- @since 4.11.0.0
module Data.Semigroup.Internal where

import GHC.Base hiding (Any)
import GHC.Enum
import GHC.Num
import GHC.Read
import GHC.Show
import GHC.Generics
import GHC.Real

-- | This is a valid definition of 'stimes' for an idempotent 'Semigroup'.
--
-- When @x <> x = x@, this definition should be preferred, because it
-- works in \(\mathcal{O}(1)\) rather than \(\mathcal{O}(\log n)\).
stimesIdempotent :: Integral b => b -> a -> a
stimesIdempotent :: forall b a. Integral b => b -> a -> a
stimesIdempotent b
n a
x
  | b
n forall a. Ord a => a -> a -> Bool
<= b
0 = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimesIdempotent: positive multiplier expected"
  | Bool
otherwise = a
x

-- | This is a valid definition of 'stimes' for an idempotent 'Monoid'.
--
-- When @mappend x x = x@, this definition should be preferred, because it
-- works in \(\mathcal{O}(1)\) rather than \(\mathcal{O}(\log n)\)
stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid :: forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid b
n a
x = case forall a. Ord a => a -> a -> Ordering
compare b
n b
0 of
  Ordering
LT -> forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimesIdempotentMonoid: negative multiplier"
  Ordering
EQ -> forall a. Monoid a => a
mempty
  Ordering
GT -> a
x

-- | This is a valid definition of 'stimes' for a 'Monoid'.
--
-- Unlike the default definition of 'stimes', it is defined for 0
-- and so it should be preferred where possible.
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
stimesMonoid :: forall b a. (Integral b, Monoid a) => b -> a -> a
stimesMonoid b
n a
x0 = case forall a. Ord a => a -> a -> Ordering
compare b
n b
0 of
  Ordering
LT -> forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimesMonoid: negative multiplier"
  Ordering
EQ -> forall a. Monoid a => a
mempty
  Ordering
GT -> forall {a} {t}. (Integral a, Monoid t) => t -> a -> t
f a
x0 b
n
    where
      f :: t -> a -> t
f t
x a
y
        | forall a. Integral a => a -> Bool
even a
y = t -> a -> t
f (t
x forall a. Monoid a => a -> a -> a
`mappend` t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2)
        | a
y forall a. Eq a => a -> a -> Bool
== a
1 = t
x
        | Bool
otherwise = forall {a} {t}. (Integral a, Monoid t) => t -> a -> t -> t
g (t
x forall a. Monoid a => a -> a -> a
`mappend` t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2) t
x               -- See Note [Half of y - 1]
      g :: t -> a -> t -> t
g t
x a
y t
z
        | forall a. Integral a => a -> Bool
even a
y = t -> a -> t -> t
g (t
x forall a. Monoid a => a -> a -> a
`mappend` t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2) t
z
        | a
y forall a. Eq a => a -> a -> Bool
== a
1 = t
x forall a. Monoid a => a -> a -> a
`mappend` t
z
        | Bool
otherwise = t -> a -> t -> t
g (t
x forall a. Monoid a => a -> a -> a
`mappend` t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2) (t
x forall a. Monoid a => a -> a -> a
`mappend` t
z) -- See Note [Half of y - 1]

-- this is used by the class definitionin GHC.Base;
-- it lives here to avoid cycles
stimesDefault :: (Integral b, Semigroup a) => b -> a -> a
stimesDefault :: forall b a. (Integral b, Semigroup a) => b -> a -> a
stimesDefault b
y0 a
x0
  | b
y0 forall a. Ord a => a -> a -> Bool
<= b
0   = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimes: positive multiplier expected"
  | Bool
otherwise = forall {a} {t}. (Integral a, Semigroup t) => t -> a -> t
f a
x0 b
y0
  where
    f :: t -> a -> t
f t
x a
y
      | forall a. Integral a => a -> Bool
even a
y = t -> a -> t
f (t
x forall a. Semigroup a => a -> a -> a
<> t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2)
      | a
y forall a. Eq a => a -> a -> Bool
== a
1 = t
x
      | Bool
otherwise = forall {a} {t}. (Integral a, Semigroup t) => t -> a -> t -> t
g (t
x forall a. Semigroup a => a -> a -> a
<> t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2) t
x        -- See Note [Half of y - 1]
    g :: t -> a -> t -> t
g t
x a
y t
z
      | forall a. Integral a => a -> Bool
even a
y = t -> a -> t -> t
g (t
x forall a. Semigroup a => a -> a -> a
<> t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2) t
z
      | a
y forall a. Eq a => a -> a -> Bool
== a
1 = t
x forall a. Semigroup a => a -> a -> a
<> t
z
      | Bool
otherwise = t -> a -> t -> t
g (t
x forall a. Semigroup a => a -> a -> a
<> t
x) (a
y forall a. Integral a => a -> a -> a
`quot` a
2) (t
x forall a. Semigroup a => a -> a -> a
<> t
z) -- See Note [Half of y - 1]

{- Note [Half of y - 1]
   ~~~~~~~~~~~~~~~~~~~~~
   Since y is guaranteed to be odd and positive here,
   half of y - 1 can be computed as y `quot` 2, optimising subtraction away.
-}

stimesMaybe :: (Integral b, Semigroup a) => b -> Maybe a -> Maybe a
stimesMaybe :: forall b a. (Integral b, Semigroup a) => b -> Maybe a -> Maybe a
stimesMaybe b
_ Maybe a
Nothing = forall a. Maybe a
Nothing
stimesMaybe b
n (Just a
a) = case forall a. Ord a => a -> a -> Ordering
compare b
n b
0 of
    Ordering
LT -> forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimes: Maybe, negative multiplier"
    Ordering
EQ -> forall a. Maybe a
Nothing
    Ordering
GT -> forall a. a -> Maybe a
Just (forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a)

stimesList  :: Integral b => b -> [a] -> [a]
stimesList :: forall b a. Integral b => b -> [a] -> [a]
stimesList b
n [a]
x
  | b
n forall a. Ord a => a -> a -> Bool
< b
0 = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimes: [], negative multiplier"
  | Bool
otherwise = forall {t}. (Eq t, Num t) => t -> [a]
rep b
n
  where
    rep :: t -> [a]
rep t
0 = []
    rep t
i = [a]
x forall a. [a] -> [a] -> [a]
++ t -> [a]
rep (t
i forall a. Num a => a -> a -> a
- t
1)

-- | The dual of a 'Monoid', obtained by swapping the arguments of 'mappend'.
--
-- >>> getDual (mappend (Dual "Hello") (Dual "World"))
-- "WorldHello"
newtype Dual a = Dual { forall a. Dual a -> a
getDual :: a }
        deriving ( Dual a -> Dual a -> Bool
forall a. Eq a => Dual a -> Dual a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dual a -> Dual a -> Bool
$c/= :: forall a. Eq a => Dual a -> Dual a -> Bool
== :: Dual a -> Dual a -> Bool
$c== :: forall a. Eq a => Dual a -> Dual a -> Bool
Eq       -- ^ @since 2.01
                 , Dual a -> Dual a -> Bool
Dual a -> Dual a -> Ordering
Dual a -> Dual a -> Dual a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Dual a)
forall a. Ord a => Dual a -> Dual a -> Bool
forall a. Ord a => Dual a -> Dual a -> Ordering
forall a. Ord a => Dual a -> Dual a -> Dual a
min :: Dual a -> Dual a -> Dual a
$cmin :: forall a. Ord a => Dual a -> Dual a -> Dual a
max :: Dual a -> Dual a -> Dual a
$cmax :: forall a. Ord a => Dual a -> Dual a -> Dual a
>= :: Dual a -> Dual a -> Bool
$c>= :: forall a. Ord a => Dual a -> Dual a -> Bool
> :: Dual a -> Dual a -> Bool
$c> :: forall a. Ord a => Dual a -> Dual a -> Bool
<= :: Dual a -> Dual a -> Bool
$c<= :: forall a. Ord a => Dual a -> Dual a -> Bool
< :: Dual a -> Dual a -> Bool
$c< :: forall a. Ord a => Dual a -> Dual a -> Bool
compare :: Dual a -> Dual a -> Ordering
$ccompare :: forall a. Ord a => Dual a -> Dual a -> Ordering
Ord      -- ^ @since 2.01
                 , ReadPrec [Dual a]
ReadPrec (Dual a)
ReadS [Dual a]
forall a. Read a => ReadPrec [Dual a]
forall a. Read a => ReadPrec (Dual a)
forall a. Read a => Int -> ReadS (Dual a)
forall a. Read a => ReadS [Dual a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Dual a]
$creadListPrec :: forall a. Read a => ReadPrec [Dual a]
readPrec :: ReadPrec (Dual a)
$creadPrec :: forall a. Read a => ReadPrec (Dual a)
readList :: ReadS [Dual a]
$creadList :: forall a. Read a => ReadS [Dual a]
readsPrec :: Int -> ReadS (Dual a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Dual a)
Read     -- ^ @since 2.01
                 , Int -> Dual a -> ShowS
forall a. Show a => Int -> Dual a -> ShowS
forall a. Show a => [Dual a] -> ShowS
forall a. Show a => Dual a -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Dual a] -> ShowS
$cshowList :: forall a. Show a => [Dual a] -> ShowS
show :: Dual a -> [Char]
$cshow :: forall a. Show a => Dual a -> [Char]
showsPrec :: Int -> Dual a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Dual a -> ShowS
Show     -- ^ @since 2.01
                 , Dual a
forall a. a -> a -> Bounded a
forall a. Bounded a => Dual a
maxBound :: Dual a
$cmaxBound :: forall a. Bounded a => Dual a
minBound :: Dual a
$cminBound :: forall a. Bounded a => Dual a
Bounded  -- ^ @since 2.01
                 , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Dual a) x -> Dual a
forall a x. Dual a -> Rep (Dual a) x
$cto :: forall a x. Rep (Dual a) x -> Dual a
$cfrom :: forall a x. Dual a -> Rep (Dual a) x
Generic  -- ^ @since 4.7.0.0
                 , forall a. Rep1 Dual a -> Dual a
forall a. Dual a -> Rep1 Dual a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 Dual a -> Dual a
$cfrom1 :: forall a. Dual a -> Rep1 Dual a
Generic1 -- ^ @since 4.7.0.0
                 )

-- | @since 4.9.0.0
instance Semigroup a => Semigroup (Dual a) where
        Dual a
a <> :: Dual a -> Dual a -> Dual a
<> Dual a
b = forall a. a -> Dual a
Dual (a
b forall a. Semigroup a => a -> a -> a
<> a
a)
        stimes :: forall b. Integral b => b -> Dual a -> Dual a
stimes b
n (Dual a
a) = forall a. a -> Dual a
Dual (forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a)

-- | @since 2.01
instance Monoid a => Monoid (Dual a) where
        mempty :: Dual a
mempty = forall a. a -> Dual a
Dual forall a. Monoid a => a
mempty

-- | @since 4.8.0.0
instance Functor Dual where
    fmap :: forall a b. (a -> b) -> Dual a -> Dual b
fmap     = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | @since 4.8.0.0
instance Applicative Dual where
    pure :: forall a. a -> Dual a
pure     = forall a. a -> Dual a
Dual
    <*> :: forall a b. Dual (a -> b) -> Dual a -> Dual b
(<*>)    = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | @since 4.8.0.0
instance Monad Dual where
    Dual a
m >>= :: forall a b. Dual a -> (a -> Dual b) -> Dual b
>>= a -> Dual b
k  = a -> Dual b
k (forall a. Dual a -> a
getDual Dual a
m)

-- | The monoid of endomorphisms under composition.
--
-- >>> let computation = Endo ("Hello, " ++) <> Endo (++ "!")
-- >>> appEndo computation "Haskell"
-- "Hello, Haskell!"
newtype Endo a = Endo { forall a. Endo a -> a -> a
appEndo :: a -> a }
               deriving ( forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Endo a) x -> Endo a
forall a x. Endo a -> Rep (Endo a) x
$cto :: forall a x. Rep (Endo a) x -> Endo a
$cfrom :: forall a x. Endo a -> Rep (Endo a) x
Generic -- ^ @since 4.7.0.0
                        )

-- | @since 4.9.0.0
instance Semigroup (Endo a) where
        <> :: Endo a -> Endo a -> Endo a
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: (a -> a) -> (a -> a) -> (a -> a))
        stimes :: forall b. Integral b => b -> Endo a -> Endo a
stimes = forall b a. (Integral b, Monoid a) => b -> a -> a
stimesMonoid

-- | @since 2.01
instance Monoid (Endo a) where
        mempty :: Endo a
mempty = forall a. (a -> a) -> Endo a
Endo forall a. a -> a
id

-- | Boolean monoid under conjunction ('&&').
--
-- >>> getAll (All True <> mempty <> All False)
-- False
--
-- >>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
-- False
newtype All = All { All -> Bool
getAll :: Bool }
        deriving ( All -> All -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: All -> All -> Bool
$c/= :: All -> All -> Bool
== :: All -> All -> Bool
$c== :: All -> All -> Bool
Eq      -- ^ @since 2.01
                 , Eq All
All -> All -> Bool
All -> All -> Ordering
All -> All -> All
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: All -> All -> All
$cmin :: All -> All -> All
max :: All -> All -> All
$cmax :: All -> All -> All
>= :: All -> All -> Bool
$c>= :: All -> All -> Bool
> :: All -> All -> Bool
$c> :: All -> All -> Bool
<= :: All -> All -> Bool
$c<= :: All -> All -> Bool
< :: All -> All -> Bool
$c< :: All -> All -> Bool
compare :: All -> All -> Ordering
$ccompare :: All -> All -> Ordering
Ord     -- ^ @since 2.01
                 , ReadPrec [All]
ReadPrec All
Int -> ReadS All
ReadS [All]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [All]
$creadListPrec :: ReadPrec [All]
readPrec :: ReadPrec All
$creadPrec :: ReadPrec All
readList :: ReadS [All]
$creadList :: ReadS [All]
readsPrec :: Int -> ReadS All
$creadsPrec :: Int -> ReadS All
Read    -- ^ @since 2.01
                 , Int -> All -> ShowS
[All] -> ShowS
All -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [All] -> ShowS
$cshowList :: [All] -> ShowS
show :: All -> [Char]
$cshow :: All -> [Char]
showsPrec :: Int -> All -> ShowS
$cshowsPrec :: Int -> All -> ShowS
Show    -- ^ @since 2.01
                 , All
forall a. a -> a -> Bounded a
maxBound :: All
$cmaxBound :: All
minBound :: All
$cminBound :: All
Bounded -- ^ @since 2.01
                 , forall x. Rep All x -> All
forall x. All -> Rep All x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep All x -> All
$cfrom :: forall x. All -> Rep All x
Generic -- ^ @since 4.7.0.0
                 )

-- | @since 4.9.0.0
instance Semigroup All where
        <> :: All -> All -> All
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce Bool -> Bool -> Bool
(&&)
        stimes :: forall b. Integral b => b -> All -> All
stimes = forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid

-- | @since 2.01
instance Monoid All where
        mempty :: All
mempty = Bool -> All
All Bool
True

-- | Boolean monoid under disjunction ('||').
--
-- >>> getAny (Any True <> mempty <> Any False)
-- True
--
-- >>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
-- True
newtype Any = Any { Any -> Bool
getAny :: Bool }
        deriving ( Any -> Any -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Any -> Any -> Bool
$c/= :: Any -> Any -> Bool
== :: Any -> Any -> Bool
$c== :: Any -> Any -> Bool
Eq      -- ^ @since 2.01
                 , Eq Any
Any -> Any -> Bool
Any -> Any -> Ordering
Any -> Any -> Any
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Any -> Any -> Any
$cmin :: Any -> Any -> Any
max :: Any -> Any -> Any
$cmax :: Any -> Any -> Any
>= :: Any -> Any -> Bool
$c>= :: Any -> Any -> Bool
> :: Any -> Any -> Bool
$c> :: Any -> Any -> Bool
<= :: Any -> Any -> Bool
$c<= :: Any -> Any -> Bool
< :: Any -> Any -> Bool
$c< :: Any -> Any -> Bool
compare :: Any -> Any -> Ordering
$ccompare :: Any -> Any -> Ordering
Ord     -- ^ @since 2.01
                 , ReadPrec [Any]
ReadPrec Any
Int -> ReadS Any
ReadS [Any]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Any]
$creadListPrec :: ReadPrec [Any]
readPrec :: ReadPrec Any
$creadPrec :: ReadPrec Any
readList :: ReadS [Any]
$creadList :: ReadS [Any]
readsPrec :: Int -> ReadS Any
$creadsPrec :: Int -> ReadS Any
Read    -- ^ @since 2.01
                 , Int -> Any -> ShowS
[Any] -> ShowS
Any -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Any] -> ShowS
$cshowList :: [Any] -> ShowS
show :: Any -> [Char]
$cshow :: Any -> [Char]
showsPrec :: Int -> Any -> ShowS
$cshowsPrec :: Int -> Any -> ShowS
Show    -- ^ @since 2.01
                 , Any
forall a. a -> a -> Bounded a
maxBound :: Any
$cmaxBound :: Any
minBound :: Any
$cminBound :: Any
Bounded -- ^ @since 2.01
                 , forall x. Rep Any x -> Any
forall x. Any -> Rep Any x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Any x -> Any
$cfrom :: forall x. Any -> Rep Any x
Generic -- ^ @since 4.7.0.0
                 )

-- | @since 4.9.0.0
instance Semigroup Any where
        <> :: Any -> Any -> Any
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce Bool -> Bool -> Bool
(||)
        stimes :: forall b. Integral b => b -> Any -> Any
stimes = forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid

-- | @since 2.01
instance Monoid Any where
        mempty :: Any
mempty = Bool -> Any
Any Bool
False

-- | Monoid under addition.
--
-- >>> getSum (Sum 1 <> Sum 2 <> mempty)
-- 3
newtype Sum a = Sum { forall a. Sum a -> a
getSum :: a }
        deriving ( Sum a -> Sum a -> Bool
forall a. Eq a => Sum a -> Sum a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sum a -> Sum a -> Bool
$c/= :: forall a. Eq a => Sum a -> Sum a -> Bool
== :: Sum a -> Sum a -> Bool
$c== :: forall a. Eq a => Sum a -> Sum a -> Bool
Eq       -- ^ @since 2.01
                 , Sum a -> Sum a -> Bool
Sum a -> Sum a -> Ordering
Sum a -> Sum a -> Sum a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Sum a)
forall a. Ord a => Sum a -> Sum a -> Bool
forall a. Ord a => Sum a -> Sum a -> Ordering
forall a. Ord a => Sum a -> Sum a -> Sum a
min :: Sum a -> Sum a -> Sum a
$cmin :: forall a. Ord a => Sum a -> Sum a -> Sum a
max :: Sum a -> Sum a -> Sum a
$cmax :: forall a. Ord a => Sum a -> Sum a -> Sum a
>= :: Sum a -> Sum a -> Bool
$c>= :: forall a. Ord a => Sum a -> Sum a -> Bool
> :: Sum a -> Sum a -> Bool
$c> :: forall a. Ord a => Sum a -> Sum a -> Bool
<= :: Sum a -> Sum a -> Bool
$c<= :: forall a. Ord a => Sum a -> Sum a -> Bool
< :: Sum a -> Sum a -> Bool
$c< :: forall a. Ord a => Sum a -> Sum a -> Bool
compare :: Sum a -> Sum a -> Ordering
$ccompare :: forall a. Ord a => Sum a -> Sum a -> Ordering
Ord      -- ^ @since 2.01
                 , ReadPrec [Sum a]
ReadPrec (Sum a)
ReadS [Sum a]
forall a. Read a => ReadPrec [Sum a]
forall a. Read a => ReadPrec (Sum a)
forall a. Read a => Int -> ReadS (Sum a)
forall a. Read a => ReadS [Sum a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Sum a]
$creadListPrec :: forall a. Read a => ReadPrec [Sum a]
readPrec :: ReadPrec (Sum a)
$creadPrec :: forall a. Read a => ReadPrec (Sum a)
readList :: ReadS [Sum a]
$creadList :: forall a. Read a => ReadS [Sum a]
readsPrec :: Int -> ReadS (Sum a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Sum a)
Read     -- ^ @since 2.01
                 , Int -> Sum a -> ShowS
forall a. Show a => Int -> Sum a -> ShowS
forall a. Show a => [Sum a] -> ShowS
forall a. Show a => Sum a -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Sum a] -> ShowS
$cshowList :: forall a. Show a => [Sum a] -> ShowS
show :: Sum a -> [Char]
$cshow :: forall a. Show a => Sum a -> [Char]
showsPrec :: Int -> Sum a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Sum a -> ShowS
Show     -- ^ @since 2.01
                 , Sum a
forall a. a -> a -> Bounded a
forall a. Bounded a => Sum a
maxBound :: Sum a
$cmaxBound :: forall a. Bounded a => Sum a
minBound :: Sum a
$cminBound :: forall a. Bounded a => Sum a
Bounded  -- ^ @since 2.01
                 , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Sum a) x -> Sum a
forall a x. Sum a -> Rep (Sum a) x
$cto :: forall a x. Rep (Sum a) x -> Sum a
$cfrom :: forall a x. Sum a -> Rep (Sum a) x
Generic  -- ^ @since 4.7.0.0
                 , forall a. Rep1 Sum a -> Sum a
forall a. Sum a -> Rep1 Sum a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 Sum a -> Sum a
$cfrom1 :: forall a. Sum a -> Rep1 Sum a
Generic1 -- ^ @since 4.7.0.0
                 , Integer -> Sum a
Sum a -> Sum a
Sum a -> Sum a -> Sum a
forall a. Num a => Integer -> Sum a
forall a. Num a => Sum a -> Sum a
forall a. Num a => Sum a -> Sum a -> Sum a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Sum a
$cfromInteger :: forall a. Num a => Integer -> Sum a
signum :: Sum a -> Sum a
$csignum :: forall a. Num a => Sum a -> Sum a
abs :: Sum a -> Sum a
$cabs :: forall a. Num a => Sum a -> Sum a
negate :: Sum a -> Sum a
$cnegate :: forall a. Num a => Sum a -> Sum a
* :: Sum a -> Sum a -> Sum a
$c* :: forall a. Num a => Sum a -> Sum a -> Sum a
- :: Sum a -> Sum a -> Sum a
$c- :: forall a. Num a => Sum a -> Sum a -> Sum a
+ :: Sum a -> Sum a -> Sum a
$c+ :: forall a. Num a => Sum a -> Sum a -> Sum a
Num      -- ^ @since 4.7.0.0
                 )

-- | @since 4.9.0.0
instance Num a => Semigroup (Sum a) where
        <> :: Sum a -> Sum a -> Sum a
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => a -> a -> a
(+) :: a -> a -> a)
        stimes :: forall b. Integral b => b -> Sum a -> Sum a
stimes b
n (Sum a
a) = forall a. a -> Sum a
Sum (forall a b. (Integral a, Num b) => a -> b
fromIntegral b
n forall a. Num a => a -> a -> a
* a
a)

-- | @since 2.01
instance Num a => Monoid (Sum a) where
        mempty :: Sum a
mempty = forall a. a -> Sum a
Sum a
0

-- | @since 4.8.0.0
instance Functor Sum where
    fmap :: forall a b. (a -> b) -> Sum a -> Sum b
fmap     = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | @since 4.8.0.0
instance Applicative Sum where
    pure :: forall a. a -> Sum a
pure     = forall a. a -> Sum a
Sum
    <*> :: forall a b. Sum (a -> b) -> Sum a -> Sum b
(<*>)    = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | @since 4.8.0.0
instance Monad Sum where
    Sum a
m >>= :: forall a b. Sum a -> (a -> Sum b) -> Sum b
>>= a -> Sum b
k  = a -> Sum b
k (forall a. Sum a -> a
getSum Sum a
m)

-- | Monoid under multiplication.
--
-- >>> getProduct (Product 3 <> Product 4 <> mempty)
-- 12
newtype Product a = Product { forall a. Product a -> a
getProduct :: a }
        deriving ( Product a -> Product a -> Bool
forall a. Eq a => Product a -> Product a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Product a -> Product a -> Bool
$c/= :: forall a. Eq a => Product a -> Product a -> Bool
== :: Product a -> Product a -> Bool
$c== :: forall a. Eq a => Product a -> Product a -> Bool
Eq       -- ^ @since 2.01
                 , Product a -> Product a -> Bool
Product a -> Product a -> Ordering
Product a -> Product a -> Product a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Product a)
forall a. Ord a => Product a -> Product a -> Bool
forall a. Ord a => Product a -> Product a -> Ordering
forall a. Ord a => Product a -> Product a -> Product a
min :: Product a -> Product a -> Product a
$cmin :: forall a. Ord a => Product a -> Product a -> Product a
max :: Product a -> Product a -> Product a
$cmax :: forall a. Ord a => Product a -> Product a -> Product a
>= :: Product a -> Product a -> Bool
$c>= :: forall a. Ord a => Product a -> Product a -> Bool
> :: Product a -> Product a -> Bool
$c> :: forall a. Ord a => Product a -> Product a -> Bool
<= :: Product a -> Product a -> Bool
$c<= :: forall a. Ord a => Product a -> Product a -> Bool
< :: Product a -> Product a -> Bool
$c< :: forall a. Ord a => Product a -> Product a -> Bool
compare :: Product a -> Product a -> Ordering
$ccompare :: forall a. Ord a => Product a -> Product a -> Ordering
Ord      -- ^ @since 2.01
                 , ReadPrec [Product a]
ReadPrec (Product a)
ReadS [Product a]
forall a. Read a => ReadPrec [Product a]
forall a. Read a => ReadPrec (Product a)
forall a. Read a => Int -> ReadS (Product a)
forall a. Read a => ReadS [Product a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Product a]
$creadListPrec :: forall a. Read a => ReadPrec [Product a]
readPrec :: ReadPrec (Product a)
$creadPrec :: forall a. Read a => ReadPrec (Product a)
readList :: ReadS [Product a]
$creadList :: forall a. Read a => ReadS [Product a]
readsPrec :: Int -> ReadS (Product a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Product a)
Read     -- ^ @since 2.01
                 , Int -> Product a -> ShowS
forall a. Show a => Int -> Product a -> ShowS
forall a. Show a => [Product a] -> ShowS
forall a. Show a => Product a -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Product a] -> ShowS
$cshowList :: forall a. Show a => [Product a] -> ShowS
show :: Product a -> [Char]
$cshow :: forall a. Show a => Product a -> [Char]
showsPrec :: Int -> Product a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Product a -> ShowS
Show     -- ^ @since 2.01
                 , Product a
forall a. a -> a -> Bounded a
forall a. Bounded a => Product a
maxBound :: Product a
$cmaxBound :: forall a. Bounded a => Product a
minBound :: Product a
$cminBound :: forall a. Bounded a => Product a
Bounded  -- ^ @since 2.01
                 , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Product a) x -> Product a
forall a x. Product a -> Rep (Product a) x
$cto :: forall a x. Rep (Product a) x -> Product a
$cfrom :: forall a x. Product a -> Rep (Product a) x
Generic  -- ^ @since 4.7.0.0
                 , forall a. Rep1 Product a -> Product a
forall a. Product a -> Rep1 Product a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 Product a -> Product a
$cfrom1 :: forall a. Product a -> Rep1 Product a
Generic1 -- ^ @since 4.7.0.0
                 , Integer -> Product a
Product a -> Product a
Product a -> Product a -> Product a
forall a. Num a => Integer -> Product a
forall a. Num a => Product a -> Product a
forall a. Num a => Product a -> Product a -> Product a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Product a
$cfromInteger :: forall a. Num a => Integer -> Product a
signum :: Product a -> Product a
$csignum :: forall a. Num a => Product a -> Product a
abs :: Product a -> Product a
$cabs :: forall a. Num a => Product a -> Product a
negate :: Product a -> Product a
$cnegate :: forall a. Num a => Product a -> Product a
* :: Product a -> Product a -> Product a
$c* :: forall a. Num a => Product a -> Product a -> Product a
- :: Product a -> Product a -> Product a
$c- :: forall a. Num a => Product a -> Product a -> Product a
+ :: Product a -> Product a -> Product a
$c+ :: forall a. Num a => Product a -> Product a -> Product a
Num      -- ^ @since 4.7.0.0
                 )

-- | @since 4.9.0.0
instance Num a => Semigroup (Product a) where
        <> :: Product a -> Product a -> Product a
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => a -> a -> a
(*) :: a -> a -> a)
        stimes :: forall b. Integral b => b -> Product a -> Product a
stimes b
n (Product a
a) = forall a. a -> Product a
Product (a
a forall a b. (Num a, Integral b) => a -> b -> a
^ b
n)


-- | @since 2.01
instance Num a => Monoid (Product a) where
        mempty :: Product a
mempty = forall a. a -> Product a
Product a
1

-- | @since 4.8.0.0
instance Functor Product where
    fmap :: forall a b. (a -> b) -> Product a -> Product b
fmap     = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | @since 4.8.0.0
instance Applicative Product where
    pure :: forall a. a -> Product a
pure     = forall a. a -> Product a
Product
    <*> :: forall a b. Product (a -> b) -> Product a -> Product b
(<*>)    = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | @since 4.8.0.0
instance Monad Product where
    Product a
m >>= :: forall a b. Product a -> (a -> Product b) -> Product b
>>= a -> Product b
k  = a -> Product b
k (forall a. Product a -> a
getProduct Product a
m)


-- | Monoid under '<|>'.
--
-- >>> getAlt (Alt (Just 12) <> Alt (Just 24))
-- Just 12
--
-- >>> getAlt $ Alt Nothing <> Alt (Just 24)
-- Just 24
--
-- @since 4.8.0.0
newtype Alt f a = Alt {forall {k} (f :: k -> *) (a :: k). Alt f a -> f a
getAlt :: f a}
  deriving ( forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (f :: k -> *) (a :: k) x. Rep (Alt f a) x -> Alt f a
forall k (f :: k -> *) (a :: k) x. Alt f a -> Rep (Alt f a) x
$cto :: forall k (f :: k -> *) (a :: k) x. Rep (Alt f a) x -> Alt f a
$cfrom :: forall k (f :: k -> *) (a :: k) x. Alt f a -> Rep (Alt f a) x
Generic     -- ^ @since 4.8.0.0
           , forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
forall k (f :: k -> *) (a :: k). Rep1 (Alt f) a -> Alt f a
forall k (f :: k -> *) (a :: k). Alt f a -> Rep1 (Alt f) a
$cto1 :: forall k (f :: k -> *) (a :: k). Rep1 (Alt f) a -> Alt f a
$cfrom1 :: forall k (f :: k -> *) (a :: k). Alt f a -> Rep1 (Alt f) a
Generic1    -- ^ @since 4.8.0.0
           , ReadPrec [Alt f a]
ReadPrec (Alt f a)
ReadS [Alt f a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec [Alt f a]
forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec (Alt f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (Alt f a)
forall k (f :: k -> *) (a :: k). Read (f a) => ReadS [Alt f a]
readListPrec :: ReadPrec [Alt f a]
$creadListPrec :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec [Alt f a]
readPrec :: ReadPrec (Alt f a)
$creadPrec :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec (Alt f a)
readList :: ReadS [Alt f a]
$creadList :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadS [Alt f a]
readsPrec :: Int -> ReadS (Alt f a)
$creadsPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (Alt f a)
Read        -- ^ @since 4.8.0.0
           , Int -> Alt f a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> Alt f a -> ShowS
forall k (f :: k -> *) (a :: k). Show (f a) => [Alt f a] -> ShowS
forall k (f :: k -> *) (a :: k). Show (f a) => Alt f a -> [Char]
showList :: [Alt f a] -> ShowS
$cshowList :: forall k (f :: k -> *) (a :: k). Show (f a) => [Alt f a] -> ShowS
show :: Alt f a -> [Char]
$cshow :: forall k (f :: k -> *) (a :: k). Show (f a) => Alt f a -> [Char]
showsPrec :: Int -> Alt f a -> ShowS
$cshowsPrec :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> Alt f a -> ShowS
Show        -- ^ @since 4.8.0.0
           , Alt f a -> Alt f a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> *) (a :: k).
Eq (f a) =>
Alt f a -> Alt f a -> Bool
/= :: Alt f a -> Alt f a -> Bool
$c/= :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
Alt f a -> Alt f a -> Bool
== :: Alt f a -> Alt f a -> Bool
$c== :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
Alt f a -> Alt f a -> Bool
Eq          -- ^ @since 4.8.0.0
           , Alt f a -> Alt f a -> Bool
Alt f a -> Alt f a -> Ordering
Alt f a -> Alt f a -> Alt f a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {k} {f :: k -> *} {a :: k}. Ord (f a) => Eq (Alt f a)
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Bool
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Ordering
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Alt f a
min :: Alt f a -> Alt f a -> Alt f a
$cmin :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Alt f a
max :: Alt f a -> Alt f a -> Alt f a
$cmax :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Alt f a
>= :: Alt f a -> Alt f a -> Bool
$c>= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Bool
> :: Alt f a -> Alt f a -> Bool
$c> :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Bool
<= :: Alt f a -> Alt f a -> Bool
$c<= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Bool
< :: Alt f a -> Alt f a -> Bool
$c< :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Bool
compare :: Alt f a -> Alt f a -> Ordering
$ccompare :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Alt f a -> Alt f a -> Ordering
Ord         -- ^ @since 4.8.0.0
           , Integer -> Alt f a
Alt f a -> Alt f a
Alt f a -> Alt f a -> Alt f a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall k (f :: k -> *) (a :: k). Num (f a) => Integer -> Alt f a
forall k (f :: k -> *) (a :: k). Num (f a) => Alt f a -> Alt f a
forall k (f :: k -> *) (a :: k).
Num (f a) =>
Alt f a -> Alt f a -> Alt f a
fromInteger :: Integer -> Alt f a
$cfromInteger :: forall k (f :: k -> *) (a :: k). Num (f a) => Integer -> Alt f a
signum :: Alt f a -> Alt f a
$csignum :: forall k (f :: k -> *) (a :: k). Num (f a) => Alt f a -> Alt f a
abs :: Alt f a -> Alt f a
$cabs :: forall k (f :: k -> *) (a :: k). Num (f a) => Alt f a -> Alt f a
negate :: Alt f a -> Alt f a
$cnegate :: forall k (f :: k -> *) (a :: k). Num (f a) => Alt f a -> Alt f a
* :: Alt f a -> Alt f a -> Alt f a
$c* :: forall k (f :: k -> *) (a :: k).
Num (f a) =>
Alt f a -> Alt f a -> Alt f a
- :: Alt f a -> Alt f a -> Alt f a
$c- :: forall k (f :: k -> *) (a :: k).
Num (f a) =>
Alt f a -> Alt f a -> Alt f a
+ :: Alt f a -> Alt f a -> Alt f a
$c+ :: forall k (f :: k -> *) (a :: k).
Num (f a) =>
Alt f a -> Alt f a -> Alt f a
Num         -- ^ @since 4.8.0.0
           , Int -> Alt f a
Alt f a -> Int
Alt f a -> [Alt f a]
Alt f a -> Alt f a
Alt f a -> Alt f a -> [Alt f a]
Alt f a -> Alt f a -> Alt f a -> [Alt f a]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
forall k (f :: k -> *) (a :: k). Enum (f a) => Int -> Alt f a
forall k (f :: k -> *) (a :: k). Enum (f a) => Alt f a -> Int
forall k (f :: k -> *) (a :: k). Enum (f a) => Alt f a -> [Alt f a]
forall k (f :: k -> *) (a :: k). Enum (f a) => Alt f a -> Alt f a
forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Alt f a -> Alt f a -> [Alt f a]
forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Alt f a -> Alt f a -> Alt f a -> [Alt f a]
enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a]
$cenumFromThenTo :: forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Alt f a -> Alt f a -> Alt f a -> [Alt f a]
enumFromTo :: Alt f a -> Alt f a -> [Alt f a]
$cenumFromTo :: forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Alt f a -> Alt f a -> [Alt f a]
enumFromThen :: Alt f a -> Alt f a -> [Alt f a]
$cenumFromThen :: forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Alt f a -> Alt f a -> [Alt f a]
enumFrom :: Alt f a -> [Alt f a]
$cenumFrom :: forall k (f :: k -> *) (a :: k). Enum (f a) => Alt f a -> [Alt f a]
fromEnum :: Alt f a -> Int
$cfromEnum :: forall k (f :: k -> *) (a :: k). Enum (f a) => Alt f a -> Int
toEnum :: Int -> Alt f a
$ctoEnum :: forall k (f :: k -> *) (a :: k). Enum (f a) => Int -> Alt f a
pred :: Alt f a -> Alt f a
$cpred :: forall k (f :: k -> *) (a :: k). Enum (f a) => Alt f a -> Alt f a
succ :: Alt f a -> Alt f a
$csucc :: forall k (f :: k -> *) (a :: k). Enum (f a) => Alt f a -> Alt f a
Enum        -- ^ @since 4.8.0.0
           , forall a. a -> Alt f a
forall a b. Alt f a -> Alt f b -> Alt f b
forall a b. Alt f a -> (a -> Alt f b) -> Alt f b
forall {f :: * -> *}. Monad f => Applicative (Alt f)
forall (f :: * -> *) a. Monad f => a -> Alt f a
forall (f :: * -> *) a b. Monad f => Alt f a -> Alt f b -> Alt f b
forall (f :: * -> *) a b.
Monad f =>
Alt f a -> (a -> Alt f b) -> Alt f b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Alt f a
$creturn :: forall (f :: * -> *) a. Monad f => a -> Alt f a
>> :: forall a b. Alt f a -> Alt f b -> Alt f b
$c>> :: forall (f :: * -> *) a b. Monad f => Alt f a -> Alt f b -> Alt f b
>>= :: forall a b. Alt f a -> (a -> Alt f b) -> Alt f b
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
Alt f a -> (a -> Alt f b) -> Alt f b
Monad       -- ^ @since 4.8.0.0
           , forall a. Alt f a
forall a. Alt f a -> Alt f a -> Alt f a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
forall {f :: * -> *}. MonadPlus f => Monad (Alt f)
forall {f :: * -> *}. MonadPlus f => Alternative (Alt f)
forall (f :: * -> *) a. MonadPlus f => Alt f a
forall (f :: * -> *) a.
MonadPlus f =>
Alt f a -> Alt f a -> Alt f a
mplus :: forall a. Alt f a -> Alt f a -> Alt f a
$cmplus :: forall (f :: * -> *) a.
MonadPlus f =>
Alt f a -> Alt f a -> Alt f a
mzero :: forall a. Alt f a
$cmzero :: forall (f :: * -> *) a. MonadPlus f => Alt f a
MonadPlus   -- ^ @since 4.8.0.0
           , forall a. a -> Alt f a
forall a b. Alt f a -> Alt f b -> Alt f a
forall a b. Alt f a -> Alt f b -> Alt f b
forall a b. Alt f (a -> b) -> Alt f a -> Alt f b
forall a b c. (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall {f :: * -> *}. Applicative f => Functor (Alt f)
forall (f :: * -> *) a. Applicative f => a -> Alt f a
forall (f :: * -> *) a b.
Applicative f =>
Alt f a -> Alt f b -> Alt f a
forall (f :: * -> *) a b.
Applicative f =>
Alt f a -> Alt f b -> Alt f b
forall (f :: * -> *) a b.
Applicative f =>
Alt f (a -> b) -> Alt f a -> Alt f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Alt f a -> Alt f b -> Alt f c
<* :: forall a b. Alt f a -> Alt f b -> Alt f a
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
Alt f a -> Alt f b -> Alt f a
*> :: forall a b. Alt f a -> Alt f b -> Alt f b
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
Alt f a -> Alt f b -> Alt f b
liftA2 :: forall a b c. (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Alt f a -> Alt f b -> Alt f c
<*> :: forall a b. Alt f (a -> b) -> Alt f a -> Alt f b
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
Alt f (a -> b) -> Alt f a -> Alt f b
pure :: forall a. a -> Alt f a
$cpure :: forall (f :: * -> *) a. Applicative f => a -> Alt f a
Applicative -- ^ @since 4.8.0.0
           , forall a. Alt f a
forall a. Alt f a -> Alt f [a]
forall a. Alt f a -> Alt f a -> Alt f a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
forall {f :: * -> *}. Alternative f => Applicative (Alt f)
forall (f :: * -> *) a. Alternative f => Alt f a
forall (f :: * -> *) a. Alternative f => Alt f a -> Alt f [a]
forall (f :: * -> *) a.
Alternative f =>
Alt f a -> Alt f a -> Alt f a
many :: forall a. Alt f a -> Alt f [a]
$cmany :: forall (f :: * -> *) a. Alternative f => Alt f a -> Alt f [a]
some :: forall a. Alt f a -> Alt f [a]
$csome :: forall (f :: * -> *) a. Alternative f => Alt f a -> Alt f [a]
<|> :: forall a. Alt f a -> Alt f a -> Alt f a
$c<|> :: forall (f :: * -> *) a.
Alternative f =>
Alt f a -> Alt f a -> Alt f a
empty :: forall a. Alt f a
$cempty :: forall (f :: * -> *) a. Alternative f => Alt f a
Alternative -- ^ @since 4.8.0.0
           , forall a b. a -> Alt f b -> Alt f a
forall a b. (a -> b) -> Alt f a -> Alt f b
forall (f :: * -> *) a b. Functor f => a -> Alt f b -> Alt f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Alt f a -> Alt f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Alt f b -> Alt f a
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Alt f b -> Alt f a
fmap :: forall a b. (a -> b) -> Alt f a -> Alt f b
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Alt f a -> Alt f b
Functor     -- ^ @since 4.8.0.0
           )

-- | @since 4.9.0.0
instance Alternative f => Semigroup (Alt f a) where
    <> :: Alt f a -> Alt f a -> Alt f a
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) :: f a -> f a -> f a)
    stimes :: forall b. Integral b => b -> Alt f a -> Alt f a
stimes = forall b a. (Integral b, Monoid a) => b -> a -> a
stimesMonoid

-- | @since 4.8.0.0
instance Alternative f => Monoid (Alt f a) where
    mempty :: Alt f a
mempty = forall {k} (f :: k -> *) (a :: k). f a -> Alt f a
Alt forall (f :: * -> *) a. Alternative f => f a
empty