{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
module Data.Monoid (
Monoid(..),
(<>),
Dual(..),
Endo(..),
All(..),
Any(..),
Sum(..),
Product(..),
First(..),
Last(..),
Alt(..),
Ap(..)
) where
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
newtype First a = First { forall a. First a -> Maybe a
getFirst :: Maybe a }
deriving ( First a -> First a -> Bool
(First a -> First a -> Bool)
-> (First a -> First a -> Bool) -> Eq (First a)
forall a. Eq a => First a -> First a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$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
/= :: First a -> First a -> Bool
Eq
, Eq (First a)
Eq (First a)
-> (First a -> First a -> Ordering)
-> (First a -> First a -> Bool)
-> (First a -> First a -> Bool)
-> (First a -> First a -> Bool)
-> (First a -> First a -> Bool)
-> (First a -> First a -> First a)
-> (First a -> First a -> First a)
-> Ord (First a)
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
$ccompare :: forall a. Ord a => First a -> First a -> Ordering
compare :: First a -> First a -> Ordering
$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
>= :: First a -> First a -> Bool
$cmax :: forall a. Ord a => First a -> First a -> First a
max :: First a -> First a -> First a
$cmin :: forall a. Ord a => First a -> First a -> First a
min :: First a -> First a -> First a
Ord
, ReadPrec [First a]
ReadPrec (First a)
Int -> ReadS (First a)
ReadS [First a]
(Int -> ReadS (First a))
-> ReadS [First a]
-> ReadPrec (First a)
-> ReadPrec [First a]
-> Read (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
$creadsPrec :: forall a. Read a => Int -> ReadS (First a)
readsPrec :: Int -> ReadS (First a)
$creadList :: forall a. Read a => ReadS [First a]
readList :: ReadS [First a]
$creadPrec :: forall a. Read a => ReadPrec (First a)
readPrec :: ReadPrec (First a)
$creadListPrec :: forall a. Read a => ReadPrec [First a]
readListPrec :: ReadPrec [First a]
Read
, Int -> First a -> ShowS
[First a] -> ShowS
First a -> String
(Int -> First a -> ShowS)
-> (First a -> String) -> ([First a] -> ShowS) -> Show (First a)
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
$cshowsPrec :: forall a. Show a => Int -> First a -> ShowS
showsPrec :: Int -> First a -> ShowS
$cshow :: forall a. Show a => First a -> String
show :: First a -> String
$cshowList :: forall a. Show a => [First a] -> ShowS
showList :: [First a] -> ShowS
Show
, (forall x. First a -> Rep (First a) x)
-> (forall x. Rep (First a) x -> First a) -> Generic (First a)
forall x. Rep (First a) x -> First a
forall x. First a -> Rep (First a) x
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
$cfrom :: forall a x. First a -> Rep (First a) x
from :: forall x. First a -> Rep (First a) x
$cto :: forall a x. Rep (First a) x -> First a
to :: forall x. Rep (First a) x -> First a
Generic
, (forall a. First a -> Rep1 First a)
-> (forall a. Rep1 First a -> First a) -> Generic1 First
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
$cfrom1 :: forall a. First a -> Rep1 First a
from1 :: forall a. First a -> Rep1 First a
$cto1 :: forall a. Rep1 First a -> First a
to1 :: forall a. Rep1 First a -> First a
Generic1
, (forall a b. (a -> b) -> First a -> First b)
-> (forall a b. a -> First b -> First a) -> Functor First
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
$cfmap :: forall a b. (a -> b) -> First a -> First b
fmap :: forall a b. (a -> b) -> First a -> First b
$c<$ :: forall a b. a -> First b -> First a
<$ :: forall a b. a -> First b -> First a
Functor
, Functor First
Functor First
-> (forall a. a -> First a)
-> (forall a b. First (a -> b) -> First a -> First b)
-> (forall a b c. (a -> b -> c) -> First a -> First b -> First c)
-> (forall a b. First a -> First b -> First b)
-> (forall a b. First a -> First b -> First a)
-> Applicative 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
$cpure :: forall a. a -> First a
pure :: forall a. a -> First a
$c<*> :: forall a b. First (a -> b) -> First a -> First b
<*> :: forall a b. First (a -> b) -> First a -> First b
$cliftA2 :: forall a b c. (a -> b -> c) -> First a -> First b -> First c
liftA2 :: forall a b c. (a -> b -> c) -> First a -> First b -> First c
$c*> :: forall a b. First a -> First b -> First b
*> :: forall a b. First a -> First b -> First b
$c<* :: forall a b. First a -> First b -> First a
<* :: forall a b. First a -> First b -> First a
Applicative
, Applicative First
Applicative First
-> (forall a b. First a -> (a -> First b) -> First b)
-> (forall a b. First a -> First b -> First b)
-> (forall a. a -> First a)
-> Monad 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
$c>>= :: forall a b. First a -> (a -> First b) -> First b
>>= :: forall a b. First a -> (a -> First b) -> First b
$c>> :: forall a b. First a -> First b -> First b
>> :: forall a b. First a -> First b -> First b
$creturn :: forall a. a -> First a
return :: forall a. a -> First a
Monad
)
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 = b -> First a -> First a
forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid
instance Monoid (First a) where
mempty :: First a
mempty = Maybe a -> First a
forall a. Maybe a -> First a
First Maybe a
forall a. Maybe a
Nothing
newtype Last a = Last { forall a. Last a -> Maybe a
getLast :: Maybe a }
deriving ( Last a -> Last a -> Bool
(Last a -> Last a -> Bool)
-> (Last a -> Last a -> Bool) -> Eq (Last a)
forall a. Eq a => Last a -> Last a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$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
/= :: Last a -> Last a -> Bool
Eq
, Eq (Last a)
Eq (Last a)
-> (Last a -> Last a -> Ordering)
-> (Last a -> Last a -> Bool)
-> (Last a -> Last a -> Bool)
-> (Last a -> Last a -> Bool)
-> (Last a -> Last a -> Bool)
-> (Last a -> Last a -> Last a)
-> (Last a -> Last a -> Last a)
-> Ord (Last a)
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
$ccompare :: forall a. Ord a => Last a -> Last a -> Ordering
compare :: Last a -> Last a -> Ordering
$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
>= :: Last a -> Last a -> Bool
$cmax :: forall a. Ord a => Last a -> Last a -> Last a
max :: Last a -> Last a -> Last a
$cmin :: forall a. Ord a => Last a -> Last a -> Last a
min :: Last a -> Last a -> Last a
Ord
, ReadPrec [Last a]
ReadPrec (Last a)
Int -> ReadS (Last a)
ReadS [Last a]
(Int -> ReadS (Last a))
-> ReadS [Last a]
-> ReadPrec (Last a)
-> ReadPrec [Last a]
-> Read (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
$creadsPrec :: forall a. Read a => Int -> ReadS (Last a)
readsPrec :: Int -> ReadS (Last a)
$creadList :: forall a. Read a => ReadS [Last a]
readList :: ReadS [Last a]
$creadPrec :: forall a. Read a => ReadPrec (Last a)
readPrec :: ReadPrec (Last a)
$creadListPrec :: forall a. Read a => ReadPrec [Last a]
readListPrec :: ReadPrec [Last a]
Read
, Int -> Last a -> ShowS
[Last a] -> ShowS
Last a -> String
(Int -> Last a -> ShowS)
-> (Last a -> String) -> ([Last a] -> ShowS) -> Show (Last a)
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
$cshowsPrec :: forall a. Show a => Int -> Last a -> ShowS
showsPrec :: Int -> Last a -> ShowS
$cshow :: forall a. Show a => Last a -> String
show :: Last a -> String
$cshowList :: forall a. Show a => [Last a] -> ShowS
showList :: [Last a] -> ShowS
Show
, (forall x. Last a -> Rep (Last a) x)
-> (forall x. Rep (Last a) x -> Last a) -> Generic (Last a)
forall x. Rep (Last a) x -> Last a
forall x. Last a -> Rep (Last a) x
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
$cfrom :: forall a x. Last a -> Rep (Last a) x
from :: forall x. Last a -> Rep (Last a) x
$cto :: forall a x. Rep (Last a) x -> Last a
to :: forall x. Rep (Last a) x -> Last a
Generic
, (forall a. Last a -> Rep1 Last a)
-> (forall a. Rep1 Last a -> Last a) -> Generic1 Last
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
$cfrom1 :: forall a. Last a -> Rep1 Last a
from1 :: forall a. Last a -> Rep1 Last a
$cto1 :: forall a. Rep1 Last a -> Last a
to1 :: forall a. Rep1 Last a -> Last a
Generic1
, (forall a b. (a -> b) -> Last a -> Last b)
-> (forall a b. a -> Last b -> Last a) -> Functor Last
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
$cfmap :: forall a b. (a -> b) -> Last a -> Last b
fmap :: forall a b. (a -> b) -> Last a -> Last b
$c<$ :: forall a b. a -> Last b -> Last a
<$ :: forall a b. a -> Last b -> Last a
Functor
, Functor Last
Functor Last
-> (forall a. a -> Last a)
-> (forall a b. Last (a -> b) -> Last a -> Last b)
-> (forall a b c. (a -> b -> c) -> Last a -> Last b -> Last c)
-> (forall a b. Last a -> Last b -> Last b)
-> (forall a b. Last a -> Last b -> Last a)
-> Applicative 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
$cpure :: forall a. a -> Last a
pure :: forall a. a -> Last a
$c<*> :: forall a b. Last (a -> b) -> Last a -> Last b
<*> :: forall a b. Last (a -> b) -> Last a -> Last b
$cliftA2 :: forall a b c. (a -> b -> c) -> Last a -> Last b -> Last c
liftA2 :: forall a b c. (a -> b -> c) -> Last a -> Last b -> Last c
$c*> :: forall a b. Last a -> Last b -> Last b
*> :: forall a b. Last a -> Last b -> Last b
$c<* :: forall a b. Last a -> Last b -> Last a
<* :: forall a b. Last a -> Last b -> Last a
Applicative
, Applicative Last
Applicative Last
-> (forall a b. Last a -> (a -> Last b) -> Last b)
-> (forall a b. Last a -> Last b -> Last b)
-> (forall a. a -> Last a)
-> Monad 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
$c>>= :: forall a b. Last a -> (a -> Last b) -> Last b
>>= :: forall a b. Last a -> (a -> Last b) -> Last b
$c>> :: forall a b. Last a -> Last b -> Last b
>> :: forall a b. Last a -> Last b -> Last b
$creturn :: forall a. a -> Last a
return :: forall a. a -> Last a
Monad
)
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 = b -> Last a -> Last a
forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid
instance Monoid (Last a) where
mempty :: Last a
mempty = Maybe a -> Last a
forall a. Maybe a -> Last a
Last Maybe a
forall a. Maybe a
Nothing
newtype Ap f a = Ap { forall {k} (f :: k -> *) (a :: k). Ap f a -> f a
getAp :: f a }
deriving ( Applicative (Ap f)
Applicative (Ap f)
-> (forall a. Ap f a)
-> (forall a. Ap f a -> Ap f a -> Ap f a)
-> (forall a. Ap f a -> Ap f [a])
-> (forall a. Ap f a -> Ap f [a])
-> Alternative (Ap f)
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
$cempty :: forall (f :: * -> *) a. Alternative f => Ap f a
empty :: forall a. Ap f a
$c<|> :: forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f a -> Ap f a
<|> :: forall a. Ap f a -> Ap f a -> Ap f a
$csome :: forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f [a]
some :: forall a. Ap f a -> Ap f [a]
$cmany :: forall (f :: * -> *) a. Alternative f => Ap f a -> Ap f [a]
many :: forall a. Ap f a -> Ap f [a]
Alternative
, Functor (Ap f)
Functor (Ap f)
-> (forall a. a -> Ap f a)
-> (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 a b. Ap f a -> Ap f b -> Ap f b)
-> (forall a b. Ap f a -> Ap f b -> Ap f a)
-> Applicative (Ap f)
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
$cpure :: forall (f :: * -> *) a. Applicative f => a -> Ap f a
pure :: forall a. a -> Ap f a
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
Ap f (a -> b) -> Ap f a -> Ap f b
<*> :: forall a b. Ap f (a -> b) -> Ap f a -> Ap f b
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
liftA2 :: forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f b
*> :: 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 a
<* :: forall a b. Ap f a -> Ap f b -> Ap f a
Applicative
, 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]
(Ap f a -> Ap f a)
-> (Ap f a -> Ap f a)
-> (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 -> [Ap f a])
-> Enum (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]
$csucc :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Ap f a
succ :: Ap f a -> Ap f a
$cpred :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Ap f a
pred :: Ap f a -> Ap f a
$ctoEnum :: forall k (f :: k -> *) (a :: k). Enum (f a) => Int -> Ap f a
toEnum :: Int -> Ap f a
$cfromEnum :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> Int
fromEnum :: Ap f a -> Int
$cenumFrom :: forall k (f :: k -> *) (a :: k). Enum (f a) => Ap f a -> [Ap f a]
enumFrom :: 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]
enumFromThen :: 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]
enumFromTo :: 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]
enumFromThenTo :: Ap f a -> Ap f a -> Ap f a -> [Ap f a]
Enum
, Ap f a -> Ap f a -> Bool
(Ap f a -> Ap f a -> Bool)
-> (Ap f a -> Ap f a -> Bool) -> Eq (Ap f a)
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
$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
/= :: Ap f a -> Ap f a -> Bool
Eq
, (forall a b. (a -> b) -> Ap f a -> Ap f b)
-> (forall a b. a -> Ap f b -> Ap f a) -> Functor (Ap f)
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
$cfmap :: forall (f :: * -> *) a b. Functor f => (a -> b) -> Ap f a -> Ap f b
fmap :: forall a b. (a -> b) -> Ap f a -> Ap f b
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Ap f b -> Ap f a
<$ :: forall a b. a -> Ap f b -> Ap f a
Functor
, (forall x. Ap f a -> Rep (Ap f a) x)
-> (forall x. Rep (Ap f a) x -> Ap f a) -> Generic (Ap f a)
forall x. Rep (Ap f a) x -> Ap f a
forall x. Ap f a -> Rep (Ap f a) x
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
$cfrom :: forall k (f :: k -> *) (a :: k) x. Ap f a -> Rep (Ap f a) x
from :: forall 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
to :: forall x. Rep (Ap f a) x -> Ap f a
Generic
, (forall (a :: k). Ap f a -> Rep1 (Ap f) a)
-> (forall (a :: k). Rep1 (Ap f) a -> Ap f a) -> Generic1 (Ap f)
forall (a :: k). Rep1 (Ap f) a -> Ap f a
forall (a :: k). Ap f a -> Rep1 (Ap f) a
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
$cfrom1 :: forall k (f :: k -> *) (a :: k). Ap f a -> Rep1 (Ap f) a
from1 :: forall (a :: k). Ap f a -> Rep1 (Ap f) a
$cto1 :: forall k (f :: k -> *) (a :: k). Rep1 (Ap f) a -> Ap f a
to1 :: forall (a :: k). Rep1 (Ap f) a -> Ap f a
Generic1
, Applicative (Ap f)
Applicative (Ap f)
-> (forall a b. Ap f a -> (a -> Ap f b) -> Ap f b)
-> (forall a b. Ap f a -> Ap f b -> Ap f b)
-> (forall a. a -> Ap f a)
-> Monad (Ap f)
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
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
Ap f a -> (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 -> Ap f b -> Ap f b
>> :: forall a b. Ap f a -> Ap f b -> Ap f b
$creturn :: forall (f :: * -> *) a. Monad f => a -> Ap f a
return :: forall a. a -> Ap f a
Monad
, Monad (Ap f)
Monad (Ap f) -> (forall a. String -> Ap f a) -> MonadFail (Ap f)
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
$cfail :: forall (f :: * -> *) a. MonadFail f => String -> Ap f a
fail :: forall a. String -> Ap f a
MonadFail
, Monad (Ap f)
Alternative (Ap f)
Alternative (Ap f)
-> Monad (Ap f)
-> (forall a. Ap f a)
-> (forall a. Ap f a -> Ap f a -> Ap f a)
-> MonadPlus (Ap f)
forall a. Ap f a
forall a. Ap f a -> Ap f a -> Ap f a
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
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
$cmzero :: forall (f :: * -> *) a. MonadPlus f => Ap f a
mzero :: forall a. Ap f a
$cmplus :: 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
MonadPlus
, Eq (Ap f a)
Eq (Ap f a)
-> (Ap f a -> Ap f a -> Ordering)
-> (Ap f a -> Ap f a -> Bool)
-> (Ap f a -> Ap f a -> Bool)
-> (Ap f a -> Ap f a -> Bool)
-> (Ap f a -> Ap f a -> Bool)
-> (Ap f a -> Ap f a -> Ap f a)
-> (Ap f a -> Ap f a -> Ap f a)
-> Ord (Ap f a)
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
$ccompare :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
Ap f a -> Ap f a -> Ordering
compare :: Ap f a -> Ap f a -> Ordering
$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
>= :: Ap f a -> Ap f a -> Bool
$cmax :: 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
$cmin :: 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
Ord
, ReadPrec [Ap f a]
ReadPrec (Ap f a)
Int -> ReadS (Ap f a)
ReadS [Ap f a]
(Int -> ReadS (Ap f a))
-> ReadS [Ap f a]
-> ReadPrec (Ap f a)
-> ReadPrec [Ap f a]
-> Read (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]
$creadsPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (Ap f a)
readsPrec :: Int -> ReadS (Ap f a)
$creadList :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadS [Ap f a]
readList :: ReadS [Ap f a]
$creadPrec :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec (Ap f a)
readPrec :: ReadPrec (Ap f a)
$creadListPrec :: forall k (f :: k -> *) (a :: k). Read (f a) => ReadPrec [Ap f a]
readListPrec :: ReadPrec [Ap f a]
Read
, Int -> Ap f a -> ShowS
[Ap f a] -> ShowS
Ap f a -> String
(Int -> Ap f a -> ShowS)
-> (Ap f a -> String) -> ([Ap f a] -> ShowS) -> Show (Ap f a)
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
$cshowsPrec :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> Ap f a -> ShowS
showsPrec :: Int -> Ap f a -> ShowS
$cshow :: forall k (f :: k -> *) (a :: k). Show (f a) => Ap f a -> String
show :: Ap f a -> String
$cshowList :: forall k (f :: k -> *) (a :: k). Show (f a) => [Ap f a] -> ShowS
showList :: [Ap f a] -> ShowS
Show
)
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) = f a -> Ap f a
forall {k} (f :: k -> *) (a :: k). f a -> Ap f a
Ap (f a -> Ap f a) -> f a -> Ap f a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> f a -> f a -> f a
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>) f a
x f a
y
instance (Applicative f, Monoid a) => Monoid (Ap f a) where
mempty :: Ap f a
mempty = f a -> Ap f a
forall {k} (f :: k -> *) (a :: k). f a -> Ap f a
Ap (f a -> Ap f a) -> f a -> Ap f a
forall a b. (a -> b) -> a -> b
$ a -> f a
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
instance (Applicative f, Bounded a) => Bounded (Ap f a) where
minBound :: Ap f a
minBound = a -> Ap f a
forall a. a -> Ap f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Bounded a => a
minBound
maxBound :: Ap f a
maxBound = a -> Ap f a
forall a. a -> Ap f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Bounded a => a
maxBound
instance (Applicative f, Num a) => Num (Ap f a) where
+ :: Ap f a -> Ap f a -> Ap f a
(+) = (a -> a -> a) -> Ap f a -> Ap f a -> Ap f a
forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(+)
* :: Ap f a -> Ap f a -> Ap f a
(*) = (a -> a -> a) -> Ap f a -> Ap f a -> Ap f a
forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(*)
negate :: Ap f a -> Ap f a
negate = (a -> a) -> Ap f a -> Ap f a
forall a b. (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
negate
fromInteger :: Integer -> Ap f a
fromInteger = a -> Ap f a
forall a. a -> Ap f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Ap f a) -> (Integer -> a) -> Integer -> Ap f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger
abs :: Ap f a -> Ap f a
abs = (a -> a) -> Ap f a -> Ap f a
forall a b. (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
abs
signum :: Ap f a -> Ap f a
signum = (a -> a) -> Ap f a -> Ap f a
forall a b. (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
signum