{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE Trustworthy #-}
module Data.Functor.Identity (
Identity(..),
) where
import Control.Monad.Fix
import Data.Bits (Bits, FiniteBits)
import Data.Coerce
import Data.Foldable
import Data.Functor.Utils ((#.))
import Foreign.Storable (Storable)
import GHC.Ix (Ix)
import GHC.Base ( Applicative(..), Eq(..), Functor(..), Monad(..)
, Semigroup, Monoid, Ord(..), ($), (.) )
import GHC.Enum (Bounded, Enum)
import GHC.Float (Floating, RealFloat)
import GHC.Generics (Generic, Generic1)
import GHC.Num (Num)
import GHC.Read (Read(..), lex, readParen)
import GHC.Real (Fractional, Integral, Real, RealFrac)
import GHC.Show (Show(..), showParen, showString)
import GHC.Types (Bool(..))
newtype Identity a = Identity { Identity a -> a
runIdentity :: a }
deriving ( Bits
, Bounded
, Enum
, Eq
, FiniteBits
, Floating
, Fractional
, Generic
, Generic1
, Integral
, Ix
, Semigroup
, Monoid
, Num
, Ord
, Real
, RealFrac
, RealFloat
, Storable
)
instance (Read a) => Read (Identity a) where
readsPrec :: Int -> ReadS (Identity a)
readsPrec Int
d = Bool -> ReadS (Identity a) -> ReadS (Identity a)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10) (ReadS (Identity a) -> ReadS (Identity a))
-> ReadS (Identity a) -> ReadS (Identity a)
forall a b. (a -> b) -> a -> b
$ \ String
r ->
[(a -> Identity a
forall a. a -> Identity a
Identity a
x,String
t) | (String
"Identity",String
s) <- ReadS String
lex String
r, (a
x,String
t) <- Int -> ReadS a
forall a. Read a => Int -> ReadS a
Evidence bound by a type signature of the constraint type Read a
readsPrec Int
11 String
s]
instance (Show a) => Show (Identity a) where
showsPrec :: Int -> Identity a -> ShowS
showsPrec Int
d (Identity a
x) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"Identity " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
Evidence bound by a type signature of the constraint type Show a
showsPrec Int
11 a
x
instance Foldable Identity where
foldMap :: (a -> m) -> Identity a -> m
foldMap = (a -> m) -> Identity a -> m
coerce
elem :: a -> Identity a -> Bool
elem = ((a -> Bool) -> (Identity a -> a) -> Identity a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity a -> a
forall a. Identity a -> a
runIdentity) ((a -> Bool) -> Identity a -> Bool)
-> (a -> a -> Bool) -> a -> Identity a -> Bool
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. a -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
(==)
foldl :: (b -> a -> b) -> b -> Identity a -> b
foldl = (b -> a -> b) -> b -> Identity a -> b
coerce
foldl' :: (b -> a -> b) -> b -> Identity a -> b
foldl' = (b -> a -> b) -> b -> Identity a -> b
coerce
foldl1 :: (a -> a -> a) -> Identity a -> a
foldl1 a -> a -> a
_ = Identity a -> a
forall a. Identity a -> a
runIdentity
foldr :: (a -> b -> b) -> b -> Identity a -> b
foldr a -> b -> b
f b
z (Identity a
x) = a -> b -> b
f a
x b
z
foldr' :: (a -> b -> b) -> b -> Identity a -> b
foldr' = (a -> b -> b) -> b -> Identity a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Instance of class: Foldable of the constraint type Foldable Identity
foldr
foldr1 :: (a -> a -> a) -> Identity a -> a
foldr1 a -> a -> a
_ = Identity a -> a
forall a. Identity a -> a
runIdentity
length :: Identity a -> Int
length Identity a
_ = Int
1
maximum :: Identity a -> a
maximum = Identity a -> a
forall a. Identity a -> a
runIdentity
minimum :: Identity a -> a
minimum = Identity a -> a
forall a. Identity a -> a
runIdentity
null :: Identity a -> Bool
null Identity a
_ = Bool
False
product :: Identity a -> a
product = Identity a -> a
forall a. Identity a -> a
runIdentity
sum :: Identity a -> a
sum = Identity a -> a
forall a. Identity a -> a
runIdentity
toList :: Identity a -> [a]
toList (Identity a
x) = [a
x]
instance Functor Identity where
fmap :: (a -> b) -> Identity a -> Identity b
fmap = (a -> b) -> Identity a -> Identity b
coerce
instance Applicative Identity where
pure :: a -> Identity a
pure = a -> Identity a
forall a. a -> Identity a
Identity
<*> :: Identity (a -> b) -> Identity a -> Identity b
(<*>) = Identity (a -> b) -> Identity a -> Identity b
coerce
liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c
liftA2 = (a -> b -> c) -> Identity a -> Identity b -> Identity c
coerce
instance Monad Identity where
Identity a
m >>= :: Identity a -> (a -> Identity b) -> Identity b
>>= a -> Identity b
k = a -> Identity b
k (Identity a -> a
forall a. Identity a -> a
runIdentity Identity a
m)
instance MonadFix Identity where
mfix :: (a -> Identity a) -> Identity a
mfix a -> Identity a
f = a -> Identity a
forall a. a -> Identity a
Identity ((a -> a) -> a
forall a. (a -> a) -> a
fix (Identity a -> a
forall a. Identity a -> a
runIdentity (Identity a -> a) -> (a -> Identity a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Identity a
f))