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

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Monoid
-- Copyright   :  (c) Andy Gill 2001,
--                (c) Oregon Graduate Institute of Science and Technology, 2001
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  portable
--
-- A type @a@ is a 'Monoid' if it provides an associative function ('<>')
-- that lets you combine any two values of type @a@ into one, and a neutral
-- element (`mempty`) such that
--
-- > a <> mempty == mempty <> a == a
--
-- A 'Monoid' is a 'Semigroup' with the added requirement of a neutral element.
-- Thus any 'Monoid' is a 'Semigroup', but not the other way around.
--
-- ==== __Examples__
--
-- The 'Sum' monoid is defined by the numerical addition operator and `0` as neutral element:
--
-- >>> mempty :: Sum Int
-- Sum {getSum = 0}
-- >>> Sum 1 <> Sum 2 <> Sum 3 <> Sum 4 :: Sum Int
-- Sum {getSum = 10}
--
-- We can combine multiple values in a list into a single value using the `mconcat` function.
-- Note that we have to specify the type here since 'Int' is a monoid under several different
-- operations:
--
-- >>> mconcat [1,2,3,4] :: Sum Int
-- Sum {getSum = 10}
-- >>> mconcat [] :: Sum Int
-- Sum {getSum = 0}
--
-- Another valid monoid instance of 'Int' is 'Product' It is defined by multiplication
-- and `1` as neutral element:
--
-- >>> Product 1 <> Product 2 <> Product 3 <> Product 4 :: Product Int
-- Product {getProduct = 24}
-- >>> mconcat [1,2,3,4] :: Product Int
-- Product {getProduct = 24}
-- >>> mconcat [] :: Product Int
-- Product {getProduct = 1}
--
--
-----------------------------------------------------------------------------

module Data.Monoid (
        -- * 'Monoid' typeclass
        Monoid(..),
        (<>),
        Dual(..),
        Endo(..),
        -- * 'Bool' wrappers
        All(..),
        Any(..),
        -- * 'Num' wrappers
        Sum(..),
        Product(..),
        -- * 'Maybe' wrappers
        -- $MaybeExamples
        First(..),
        Last(..),
        -- * 'Alternative' wrapper
        Alt(..),
        -- * 'Applicative' wrapper
        Ap(..)
  ) where

-- Push down the module in the dependency hierarchy.
import GHC.Base hiding (Any)
import GHC.Enum
import GHC.Generics
import GHC.Num
import GHC.Read
import GHC.Show

import Control.Monad.Fail (MonadFail)

import Data.Semigroup.Internal

-- $MaybeExamples
-- To implement @find@ or @findLast@ on any 'Data.Foldable.Foldable':
--
-- @
-- findLast :: Foldable t => (a -> Bool) -> t a -> Maybe a
-- findLast pred = getLast . foldMap (\x -> if pred x
--                                            then Last (Just x)
--                                            else Last Nothing)
-- @
--
-- Much of 'Data.Map.Lazy.Map's interface can be implemented with
-- 'Data.Map.Lazy.alter'. Some of the rest can be implemented with a new
-- 'Data.Map.Lazy.alterF' function and either 'First' or 'Last':
--
-- > alterF :: (Functor f, Ord k) =>
-- >           (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a)
-- >
-- > instance Monoid a => Functor ((,) a)  -- from Data.Functor
--
-- @
-- insertLookupWithKey :: Ord k => (k -> v -> v -> v) -> k -> v
--                     -> Map k v -> (Maybe v, Map k v)
-- insertLookupWithKey combine key value =
--   Arrow.first getFirst . 'Data.Map.Lazy.alterF' doChange key
--   where
--   doChange Nothing = (First Nothing, Just value)
--   doChange (Just oldValue) =
--     (First (Just oldValue),
--      Just (combine key value oldValue))
-- @


-- | Maybe monoid returning the leftmost non-Nothing value.
--
-- @'First' a@ is isomorphic to @'Alt' 'Maybe' a@, but precedes it
-- historically.
--
-- >>> getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
-- Just "hello"
newtype First a = First { forall a. First a -> Maybe a
getFirst :: Maybe a }
        deriving ( First a -> First a -> Bool
forall a. Eq a => First a -> First a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: First a -> First a -> Bool
$c/= :: forall a. Eq a => First a -> First a -> Bool
== :: First a -> First a -> Bool
$c== :: forall a. Eq a => First a -> First a -> Bool
Eq          -- ^ @since 2.01
                 , First a -> First a -> Bool
First a -> First a -> Ordering
First a -> First a -> First 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 (First a)
forall a. Ord a => First a -> First a -> Bool
forall a. Ord a => First a -> First a -> Ordering
forall a. Ord a => First a -> First a -> First a
min :: First a -> First a -> First a
$cmin :: forall a. Ord a => First a -> First a -> First a
max :: First a -> First a -> First a
$cmax :: forall a. Ord a => First a -> First a -> First a
>= :: First a -> First a -> Bool
$c>= :: forall a. Ord a => First a -> First a -> Bool
> :: First a -> First a -> Bool
$c> :: forall a. Ord a => First a -> First a -> Bool
<= :: First a -> First a -> Bool
$c<= :: forall a. Ord a => First a -> First a -> Bool
< :: First a -> First a -> Bool
$c< :: forall a. Ord a => First a -> First a -> Bool
compare :: First a -> First a -> Ordering
$ccompare :: forall a. Ord a => First a -> First a -> Ordering
Ord         -- ^ @since 2.01
                 , ReadPrec [First a]
ReadPrec (First a)
ReadS [First a]
forall a. Read a => ReadPrec [First a]
forall a. Read a => ReadPrec (First a)
forall a. Read a => Int -> ReadS (First a)
forall a. Read a => ReadS [First a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [First a]
$creadListPrec :: forall a. Read a => ReadPrec [First a]
readPrec :: ReadPrec (First a)
$creadPrec :: forall a. Read a => ReadPrec (First a)
readList :: ReadS [First a]
$creadList :: forall a. Read a => ReadS [First a]
readsPrec :: Int -> ReadS (First a)
$creadsPrec :: forall a. Read a => Int -> ReadS (First a)
Read        -- ^ @since 2.01
                 , Int -> First a -> ShowS
forall a. Show a => Int -> First a -> ShowS
forall a. Show a => [First a] -> ShowS
forall a. Show a => First a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [First a] -> ShowS
$cshowList :: forall a. Show a => [First a] -> ShowS
show :: First a -> String
$cshow :: forall a. Show a => First a -> String
showsPrec :: Int -> First a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> First a -> ShowS
Show        -- ^ @since 2.01
                 , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (First a) x -> First a
forall a x. First a -> Rep (First a) x
$cto :: forall a x. Rep (First a) x -> First a
$cfrom :: forall a x. First a -> Rep (First a) x
Generic     -- ^ @since 4.7.0.0
                 , forall a. Rep1 First a -> First a
forall a. First a -> Rep1 First 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 First a -> First a
$cfrom1 :: forall a. First a -> Rep1 First a
Generic1    -- ^ @since 4.7.0.0
                 , forall a b. a -> First b -> First a
forall a b. (a -> b) -> First a -> First 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 -> First b -> First a
$c<$ :: forall a b. a -> First b -> First a
fmap :: forall a b. (a -> b) -> First a -> First b
$cfmap :: forall a b. (a -> b) -> First a -> First b
Functor     -- ^ @since 4.8.0.0
                 , Functor First
forall a. a -> First a
forall a b. First a -> First b -> First a
forall a b. First a -> First b -> First b
forall a b. First (a -> b) -> First a -> First b
forall a b c. (a -> b -> c) -> First a -> First b -> First 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 a b. First a -> First b -> First a
$c<* :: forall a b. First a -> First b -> First a
*> :: forall a b. First a -> First b -> First b
$c*> :: forall a b. First a -> First b -> First b
liftA2 :: forall a b c. (a -> b -> c) -> First a -> First b -> First c
$cliftA2 :: forall a b c. (a -> b -> c) -> First a -> First b -> First c
<*> :: forall a b. First (a -> b) -> First a -> First b
$c<*> :: forall a b. First (a -> b) -> First a -> First b
pure :: forall a. a -> First a
$cpure :: forall a. a -> First a
Applicative -- ^ @since 4.8.0.0
                 , Applicative First
forall a. a -> First a
forall a b. First a -> First b -> First b
forall a b. First a -> (a -> First b) -> First 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 -> First a
$creturn :: forall a. a -> First a
>> :: forall a b. First a -> First b -> First b
$c>> :: forall a b. First a -> First b -> First b
>>= :: forall a b. First a -> (a -> First b) -> First b
$c>>= :: forall a b. First a -> (a -> First b) -> First b
Monad       -- ^ @since 4.8.0.0
                 )

-- | @since 4.9.0.0
instance Semigroup (First a) where
        First Maybe a
Nothing <> :: First a -> First a -> First a
<> First a
b = First a
b
        First a
a             <> First a
_ = First a
a
        stimes :: forall b. Integral b => b -> First a -> First a
stimes = forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid

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

-- | Maybe monoid returning the rightmost non-Nothing value.
--
-- @'Last' a@ is isomorphic to @'Dual' ('First' a)@, and thus to
-- @'Dual' ('Alt' 'Maybe' a)@
--
-- >>> getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))
-- Just "world"
newtype Last a = Last { forall a. Last a -> Maybe a
getLast :: Maybe a }
        deriving ( Last a -> Last a -> Bool
forall a. Eq a => Last a -> Last a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Last a -> Last a -> Bool
$c/= :: forall a. Eq a => Last a -> Last a -> Bool
== :: Last a -> Last a -> Bool
$c== :: forall a. Eq a => Last a -> Last a -> Bool
Eq          -- ^ @since 2.01
                 , Last a -> Last a -> Bool
Last a -> Last a -> Ordering
Last a -> Last a -> Last 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 (Last a)
forall a. Ord a => Last a -> Last a -> Bool
forall a. Ord a => Last a -> Last a -> Ordering
forall a. Ord a => Last a -> Last a -> Last a
min :: Last a -> Last a -> Last a
$cmin :: forall a. Ord a => Last a -> Last a -> Last a
max :: Last a -> Last a -> Last a
$cmax :: forall a. Ord a => Last a -> Last a -> Last a
>= :: Last a -> Last a -> Bool
$c>= :: forall a. Ord a => Last a -> Last a -> Bool
> :: Last a -> Last a -> Bool
$c> :: forall a. Ord a => Last a -> Last a -> Bool
<= :: Last a -> Last a -> Bool
$c<= :: forall a. Ord a => Last a -> Last a -> Bool
< :: Last a -> Last a -> Bool
$c< :: forall a. Ord a => Last a -> Last a -> Bool
compare :: Last a -> Last a -> Ordering
$ccompare :: forall a. Ord a => Last a -> Last a -> Ordering
Ord         -- ^ @since 2.01
                 , ReadPrec [Last a]
ReadPrec (Last a)
ReadS [Last a]
forall a. Read a => ReadPrec [Last a]
forall a. Read a => ReadPrec (Last a)
forall a. Read a => Int -> ReadS (Last a)
forall a. Read a => ReadS [Last a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Last a]
$creadListPrec :: forall a. Read a => ReadPrec [Last a]
readPrec :: ReadPrec (Last a)
$creadPrec :: forall a. Read a => ReadPrec (Last a)
readList :: ReadS [Last a]
$creadList :: forall a. Read a => ReadS [Last a]
readsPrec :: Int -> ReadS (Last a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Last a)
Read        -- ^ @since 2.01
                 , Int -> Last a -> ShowS
forall a. Show a => Int -> Last a -> ShowS
forall a. Show a => [Last a] -> ShowS
forall a. Show a => Last a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Last a] -> ShowS
$cshowList :: forall a. Show a => [Last a] -> ShowS
show :: Last a -> String
$cshow :: forall a. Show a => Last a -> String
showsPrec :: Int -> Last a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Last a -> ShowS
Show        -- ^ @since 2.01
                 , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Last a) x -> Last a
forall a x. Last a -> Rep (Last a) x
$cto :: forall a x. Rep (Last a) x -> Last a
$cfrom :: forall a x. Last a -> Rep (Last a) x
Generic     -- ^ @since 4.7.0.0
                 , forall a. Rep1 Last a -> Last a
forall a. Last a -> Rep1 Last 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 Last a -> Last a
$cfrom1 :: forall a. Last a -> Rep1 Last a
Generic1    -- ^ @since 4.7.0.0
                 , forall a b. a -> Last b -> Last a
forall a b. (a -> b) -> Last a -> Last 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 -> Last b -> Last a
$c<$ :: forall a b. a -> Last b -> Last a
fmap :: forall a b. (a -> b) -> Last a -> Last b
$cfmap :: forall a b. (a -> b) -> Last a -> Last b
Functor     -- ^ @since 4.8.0.0
                 , Functor Last
forall a. a -> Last a
forall a b. Last a -> Last b -> Last a
forall a b. Last a -> Last b -> Last b
forall a b. Last (a -> b) -> Last a -> Last b
forall a b c. (a -> b -> c) -> Last a -> Last b -> Last 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 a b. Last a -> Last b -> Last a
$c<* :: forall a b. Last a -> Last b -> Last a
*> :: forall a b. Last a -> Last b -> Last b
$c*> :: forall a b. Last a -> Last b -> Last b
liftA2 :: forall a b c. (a -> b -> c) -> Last a -> Last b -> Last c
$cliftA2 :: forall a b c. (a -> b -> c) -> Last a -> Last b -> Last c
<*> :: forall a b. Last (a -> b) -> Last a -> Last b
$c<*> :: forall a b. Last (a -> b) -> Last a -> Last b
pure :: forall a. a -> Last a
$cpure :: forall a. a -> Last a
Applicative -- ^ @since 4.8.0.0
                 , Applicative Last
forall a. a -> Last a
forall a b. Last a -> Last b -> Last b
forall a b. Last a -> (a -> Last b) -> Last 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 -> Last a
$creturn :: forall a. a -> Last a
>> :: forall a b. Last a -> Last b -> Last b
$c>> :: forall a b. Last a -> Last b -> Last b
>>= :: forall a b. Last a -> (a -> Last b) -> Last b
$c>>= :: forall a b. Last a -> (a -> Last b) -> Last b
Monad       -- ^ @since 4.8.0.0
                 )

-- | @since 4.9.0.0
instance Semigroup (Last a) where
        Last a
a <> :: Last a -> Last a -> Last a
<> Last Maybe a
Nothing = Last a
a
        Last a
_ <> Last a
b                   = Last a
b
        stimes :: forall b. Integral b => b -> Last a -> Last a
stimes = forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid

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

-- | This data type witnesses the lifting of a 'Monoid' into an
-- 'Applicative' pointwise.
--
-- @since 4.12.0.0
newtype Ap f a = Ap { forall {k} (f :: k -> *) (a :: k). Ap f a -> f a
getAp :: f a }
        deriving ( forall a. Ap f a
forall a. Ap f a -> Ap f [a]
forall a. Ap f a -> Ap f a -> Ap 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 (Ap f)
forall (f :: * -> *) a. Alternative f => Ap f a
forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f [a]
forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f a -> Ap f a
many :: forall a. Ap f a -> Ap f [a]
$cmany :: forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f [a]
some :: forall a. Ap f a -> Ap f [a]
$csome :: forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f [a]
<|> :: forall a. Ap f a -> Ap f a -> Ap f a
$c<|> :: forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f a -> Ap f a
empty :: forall a. Ap f a
$cempty :: forall (f :: * -> *) a. Alternative f => Ap f a
Alternative -- ^ @since 4.12.0.0
                 , forall a. a -> Ap f a
forall a b. Ap f a -> Ap f b -> Ap f a
forall a b. Ap f a -> Ap f b -> Ap f b
forall a b. Ap f (a -> b) -> Ap f a -> Ap f b
forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap 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 (Ap f)
forall (f :: * -> *) a. Applicative f => a -> Ap f a
forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f a
forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f b
forall (f :: * -> *) a b.
Applicative f =>
Ap f (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
<* :: forall a b. Ap f a -> Ap f b -> Ap f a
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f a
*> :: forall a b. Ap f a -> Ap f b -> Ap f b
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f b
liftA2 :: forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
<*> :: forall a b. Ap f (a -> b) -> Ap f a -> Ap f b
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
Ap f (a -> b) -> Ap f a -> Ap f b
pure :: forall a. a -> Ap f a
$cpure :: forall (f :: * -> *) a. Applicative f => a -> Ap f a
Applicative -- ^ @since 4.12.0.0
                 , Int -> Ap f a
Ap f a -> Int
Ap f a -> [Ap f a]
Ap f a -> Ap f a
Ap f a -> Ap f a -> [Ap f a]
Ap f a -> Ap f a -> Ap f a -> [Ap 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 -> Ap f a
forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Int
forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> [Ap f a]
forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Ap f a
forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Ap f a -> Ap f a -> [Ap f a]
forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Ap f a -> Ap f a -> Ap f a -> [Ap f a]
enumFromThenTo :: Ap f a -> Ap f a -> Ap f a -> [Ap f a]
$cenumFromThenTo :: forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Ap f a -> Ap f a -> Ap f a -> [Ap f a]
enumFromTo :: Ap f a -> Ap f a -> [Ap f a]
$cenumFromTo :: forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Ap f a -> Ap f a -> [Ap f a]
enumFromThen :: Ap f a -> Ap f a -> [Ap f a]
$cenumFromThen :: forall k (f :: k -> *) (a :: k).
Enum (f a) =>
Ap f a -> Ap f a -> [Ap f a]
enumFrom :: Ap f a -> [Ap f a]
$cenumFrom :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> [Ap f a]
fromEnum :: Ap f a -> Int
$cfromEnum :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Int
toEnum :: Int -> Ap f a
$ctoEnum :: forall k (f :: k -> *) (a :: k). Enum (f a) => Int -> Ap f a
pred :: Ap f a -> Ap f a
$cpred :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Ap f a
succ :: Ap f a -> Ap f a
$csucc :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Ap f a
Enum        -- ^ @since 4.12.0.0
                 , Ap f a -> Ap f a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> *) (a :: k).
Eq (f a) =>
Ap f a -> Ap f a -> Bool
/= :: Ap f a -> Ap f a -> Bool
$c/= :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
Ap f a -> Ap f a -> Bool
== :: Ap f a -> Ap f a -> Bool
$c== :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
Ap f a -> Ap f a -> Bool
Eq          -- ^ @since 4.12.0.0
                 , forall a b. a -> Ap f b -> Ap f a
forall a b. (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *) a b. Functor f => a -> Ap f b -> Ap f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> Ap f a -> Ap 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 -> Ap f b -> Ap f a
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Ap f b -> Ap f a
fmap :: forall a b. (a -> b) -> Ap f a -> Ap f b
$cfmap :: forall (f :: * -> *) a b. Functor f => (a -> b) -> Ap f a -> Ap f b
Functor     -- ^ @since 4.12.0.0
                 , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (f :: k -> *) (a :: k) x. Rep (Ap f a) x -> Ap f a
forall k (f :: k -> *) (a :: k) x. Ap f a -> Rep (Ap f a) x
$cto :: forall k (f :: k -> *) (a :: k) x. Rep (Ap f a) x -> Ap f a
$cfrom :: forall k (f :: k -> *) (a :: k) x. Ap f a -> Rep (Ap f a) x
Generic     -- ^ @since 4.12.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 (Ap f) a -> Ap f a
forall k (f :: k -> *) (a :: k). Ap f a -> Rep1 (Ap f) a
$cto1 :: forall k (f :: k -> *) (a :: k). Rep1 (Ap f) a -> Ap f a
$cfrom1 :: forall k (f :: k -> *) (a :: k). Ap f a -> Rep1 (Ap f) a
Generic1    -- ^ @since 4.12.0.0
                 , forall a. a -> Ap f a
forall a b. Ap f a -> Ap f b -> Ap f b
forall a b. Ap f a -> (a -> Ap f b) -> Ap f b
forall {f :: * -> *}. Monad f => Applicative (Ap f)
forall (f :: * -> *) a. Monad f => a -> Ap f a
forall (f :: * -> *) a b. Monad f => Ap f a -> Ap f b -> Ap f b
forall (f :: * -> *) a b.
Monad f =>
Ap f a -> (a -> Ap f b) -> Ap 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 -> Ap f a
$creturn :: forall (f :: * -> *) a. Monad f => a -> Ap f a
>> :: forall a b. Ap f a -> Ap f b -> Ap f b
$c>> :: forall (f :: * -> *) a b. Monad f => Ap f a -> Ap f b -> Ap f b
>>= :: forall a b. Ap f a -> (a -> Ap f b) -> Ap f b
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
Ap f a -> (a -> Ap f b) -> Ap f b
Monad       -- ^ @since 4.12.0.0
                 , forall a. String -> Ap f a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
forall {f :: * -> *}. MonadFail f => Monad (Ap f)
forall (f :: * -> *) a. MonadFail f => String -> Ap f a
fail :: forall a. String -> Ap f a
$cfail :: forall (f :: * -> *) a. MonadFail f => String -> Ap f a
MonadFail   -- ^ @since 4.12.0.0
                 , forall a. Ap f a
forall a. Ap f a -> Ap f a -> Ap 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 (Ap f)
forall {f :: * -> *}. MonadPlus f => Alternative (Ap f)
forall (f :: * -> *) a. MonadPlus f => Ap f a
forall (f :: * -> *) a. MonadPlus f => Ap f a -> Ap f a -> Ap f a
mplus :: forall a. Ap f a -> Ap f a -> Ap f a
$cmplus :: forall (f :: * -> *) a. MonadPlus f => Ap f a -> Ap f a -> Ap f a
mzero :: forall a. Ap f a
$cmzero :: forall (f :: * -> *) a. MonadPlus f => Ap f a
MonadPlus   -- ^ @since 4.12.0.0
                 , Ap f a -> Ap f a -> Bool
Ap f a -> Ap f a -> Ordering
Ap f a -> Ap f a -> Ap 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 (Ap f a)
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Bool
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Ordering
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Ap f a
min :: Ap f a -> Ap f a -> Ap f a
$cmin :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Ap f a
max :: Ap f a -> Ap f a -> Ap f a
$cmax :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Ap f a
>= :: Ap f a -> Ap f a -> Bool
$c>= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Bool
> :: Ap f a -> Ap f a -> Bool
$c> :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Bool
<= :: Ap f a -> Ap f a -> Bool
$c<= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Bool
< :: Ap f a -> Ap f a -> Bool
$c< :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Bool
compare :: Ap f a -> Ap f a -> Ordering
$ccompare :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Ordering
Ord         -- ^ @since 4.12.0.0
                 , ReadPrec [Ap f a]
ReadPrec (Ap f a)
ReadS [Ap 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 [Ap f a]
forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec (Ap f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (Ap f a)
forall k (f :: k -> *) (a :: k). Read (f a) => ReadS [Ap f a]
readListPrec :: ReadPrec [Ap f a]
$creadListPrec :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec [Ap f a]
readPrec :: ReadPrec (Ap f a)
$creadPrec :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec (Ap f a)
readList :: ReadS [Ap f a]
$creadList :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadS [Ap f a]
readsPrec :: Int -> ReadS (Ap f a)
$creadsPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (Ap f a)
Read        -- ^ @since 4.12.0.0
                 , Int -> Ap f a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> Ap f a -> ShowS
forall k (f :: k -> *) (a :: k). Show (f a) => [Ap f a] -> ShowS
forall k (f :: k -> *) (a :: k). Show (f a) => Ap f a -> String
showList :: [Ap f a] -> ShowS
$cshowList :: forall k (f :: k -> *) (a :: k). Show (f a) => [Ap f a] -> ShowS
show :: Ap f a -> String
$cshow :: forall k (f :: k -> *) (a :: k). Show (f a) => Ap f a -> String
showsPrec :: Int -> Ap f a -> ShowS
$cshowsPrec :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> Ap f a -> ShowS
Show        -- ^ @since 4.12.0.0
                 )

-- | @since 4.12.0.0
instance (Applicative f, Semigroup a) => Semigroup (Ap f a) where
        (Ap f a
x) <> :: Ap f a -> Ap f a -> Ap f a
<> (Ap f a
y) = forall {k} (f :: k -> *) (a :: k). f a -> Ap f a
Ap forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Semigroup a => a -> a -> a
(<>) f a
x f a
y

-- | @since 4.12.0.0
instance (Applicative f, Monoid a) => Monoid (Ap f a) where
        mempty :: Ap f a
mempty = forall {k} (f :: k -> *) (a :: k). f a -> Ap f a
Ap forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Monoid a => a
mempty

-- | @since 4.12.0.0
instance (Applicative f, Bounded a) => Bounded (Ap f a) where
  minBound :: Ap f a
minBound = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Bounded a => a
minBound
  maxBound :: Ap f a
maxBound = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Bounded a => a
maxBound

-- | Note that even if the underlying 'Num' and 'Applicative' instances are
-- lawful, for most 'Applicative's, this instance will not be lawful. If you use
-- this instance with the list 'Applicative', the following customary laws will
-- not hold:
--
-- Commutativity:
--
-- >>> Ap [10,20] + Ap [1,2]
-- Ap {getAp = [11,12,21,22]}
-- >>> Ap [1,2] + Ap [10,20]
-- Ap {getAp = [11,21,12,22]}
--
-- Additive inverse:
--
-- >>> Ap [] + negate (Ap [])
-- Ap {getAp = []}
-- >>> fromInteger 0 :: Ap [] Int
-- Ap {getAp = [0]}
--
-- Distributivity:
--
-- >>> Ap [1,2] * (3 + 4)
-- Ap {getAp = [7,14]}
-- >>> (Ap [1,2] * 3) + (Ap [1,2] * 4)
-- Ap {getAp = [7,11,10,14]}
--
-- @since 4.12.0.0
instance (Applicative f, Num a) => Num (Ap f a) where
  + :: Ap f a -> Ap f a -> Ap f a
(+)         = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(+)
  * :: Ap f a -> Ap f a -> Ap f a
(*)         = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(*)
  negate :: Ap f a -> Ap f a
negate      = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
negate
  fromInteger :: Integer -> Ap f a
fromInteger = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger
  abs :: Ap f a -> Ap f a
abs         = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
abs
  signum :: Ap f a -> Ap f a
signum      = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
signum

{-
{--------------------------------------------------------------------
  Testing
--------------------------------------------------------------------}
instance Arbitrary a => Arbitrary (Maybe a) where
  arbitrary = oneof [return Nothing, Just `fmap` arbitrary]

prop_mconcatMaybe :: [Maybe [Int]] -> Bool
prop_mconcatMaybe x =
  fromMaybe [] (mconcat x) == mconcat (catMaybes x)

prop_mconcatFirst :: [Maybe Int] -> Bool
prop_mconcatFirst x =
  getFirst (mconcat (map First x)) == listToMaybe (catMaybes x)
prop_mconcatLast :: [Maybe Int] -> Bool
prop_mconcatLast x =
  getLast (mconcat (map Last x)) == listLastToMaybe (catMaybes x)
        where listLastToMaybe [] = Nothing
              listLastToMaybe lst = Just (last lst)
-- -}

-- $setup
-- >>> import Prelude