{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeOperators #-}
module Data.Functor.Contravariant (
Contravariant(..)
, phantom
, (>$<), (>$$<), ($<)
, Predicate(..)
, Comparison(..)
, defaultComparison
, Equivalence(..)
, defaultEquivalence
, comparisonEquivalence
, Op(..)
) where
import Control.Applicative
import Control.Category
import Data.Function (on)
import Data.Functor.Product
import Data.Functor.Sum
import Data.Functor.Compose
import Data.Monoid (Alt(..), All(..))
import Data.Proxy
import GHC.Generics
import Prelude hiding ((.), id)
class Contravariant f where
contramap :: (a' -> a) -> (f a -> f a')
(>$) :: b -> f b -> f a
(>$) = (a -> b) -> f b -> f a
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant f
contramap ((a -> b) -> f b -> f a) -> (b -> a -> b) -> b -> f b -> f a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a -> b
forall a b. a -> b -> a
const
phantom :: (Functor f, Contravariant f) => f a -> f b
phantom :: f a -> f b
phantom f a
x = () () -> f a -> f ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
Evidence bound by a type signature of the constraint type Functor f
<$ f a
x f () -> () -> f b
forall (f :: * -> *) b a. Contravariant f => f b -> b -> f a
Evidence bound by a type signature of the constraint type Contravariant f
$< ()
infixl 4 >$, $<, >$<, >$$<
($<) :: Contravariant f => f b -> b -> f a
$< :: f b -> b -> f a
($<) = (b -> f b -> f a) -> f b -> b -> f a
forall a b c. (a -> b -> c) -> b -> a -> c
flip b -> f b -> f a
forall (f :: * -> *) b a. Contravariant f => b -> f b -> f a
Evidence bound by a type signature of the constraint type Contravariant f
(>$)
(>$<) :: Contravariant f => (a -> b) -> (f b -> f a)
>$< :: (a -> b) -> f b -> f a
(>$<) = (a -> b) -> f b -> f a
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant f
contramap
(>$$<) :: Contravariant f => f b -> (a -> b) -> f a
>$$< :: f b -> (a -> b) -> f a
(>$$<) = ((a -> b) -> f b -> f a) -> f b -> (a -> b) -> f a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> b) -> f b -> f a
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant f
contramap
deriving newtype instance Contravariant f => Contravariant (Alt f)
deriving newtype instance Contravariant f => Contravariant (Rec1 f)
deriving newtype instance Contravariant f => Contravariant (M1 i c f)
instance Contravariant V1 where
contramap :: (a' -> a) -> (V1 a -> V1 a')
contramap :: (a' -> a) -> V1 a -> V1 a'
contramap a' -> a
_ V1 a
x = case V1 a
x of
instance Contravariant U1 where
contramap :: (a' -> a) -> (U1 a -> U1 a')
contramap :: (a' -> a) -> U1 a -> U1 a'
contramap a' -> a
_ U1 a
_ = U1 a'
forall k (p :: k). U1 p
U1
instance Contravariant (K1 i c) where
contramap :: (a' -> a) -> (K1 i c a -> K1 i c a')
contramap :: (a' -> a) -> K1 i c a -> K1 i c a'
contramap a' -> a
_ (K1 c
c) = c -> K1 i c a'
forall k i c (p :: k). c -> K1 i c p
K1 c
c
instance (Contravariant f, Contravariant g) => Contravariant (f :*: g) where
contramap :: (a' -> a) -> ((f :*: g) a -> (f :*: g) a')
contramap :: (a' -> a) -> (:*:) f g a -> (:*:) f g a'
contramap a' -> a
f (f a
xs :*: g a
ys) = (a' -> a) -> f a -> f a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant f
contramap a' -> a
f f a
xs f a' -> g a' -> (:*:) f g a'
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (a' -> a) -> g a -> g a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant g
contramap a' -> a
f g a
ys
instance (Functor f, Contravariant g) => Contravariant (f :.: g) where
contramap :: (a' -> a) -> ((f :.: g) a -> (f :.: g) a')
contramap :: (a' -> a) -> (:.:) f g a -> (:.:) f g a'
contramap a' -> a
f (Comp1 f (g a)
fg) = f (g a') -> (:.:) f g a'
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 ((g a -> g a') -> f (g a) -> f (g a')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap ((a' -> a) -> g a -> g a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant g
contramap a' -> a
f) f (g a)
fg)
instance (Contravariant f, Contravariant g) => Contravariant (f :+: g) where
contramap :: (a' -> a) -> ((f :+: g) a -> (f :+: g) a')
contramap :: (a' -> a) -> (:+:) f g a -> (:+:) f g a'
contramap a' -> a
f (L1 f a
xs) = f a' -> (:+:) f g a'
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 ((a' -> a) -> f a -> f a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant f
contramap a' -> a
f f a
xs)
contramap a' -> a
f (R1 g a
ys) = g a' -> (:+:) f g a'
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 ((a' -> a) -> g a -> g a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant g
contramap a' -> a
f g a
ys)
instance (Contravariant f, Contravariant g) => Contravariant (Sum f g) where
contramap :: (a' -> a) -> (Sum f g a -> Sum f g a')
contramap :: (a' -> a) -> Sum f g a -> Sum f g a'
contramap a' -> a
f (InL f a
xs) = f a' -> Sum f g a'
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL ((a' -> a) -> f a -> f a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant f
contramap a' -> a
f f a
xs)
contramap a' -> a
f (InR g a
ys) = g a' -> Sum f g a'
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR ((a' -> a) -> g a -> g a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant g
contramap a' -> a
f g a
ys)
instance (Contravariant f, Contravariant g)
=> Contravariant (Product f g) where
contramap :: (a' -> a) -> (Product f g a -> Product f g a')
contramap :: (a' -> a) -> Product f g a -> Product f g a'
contramap a' -> a
f (Pair f a
a g a
b) = f a' -> g a' -> Product f g a'
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair ((a' -> a) -> f a -> f a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant f
contramap a' -> a
f f a
a) ((a' -> a) -> g a -> g a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant g
contramap a' -> a
f g a
b)
instance Contravariant (Const a) where
contramap :: (b' -> b) -> (Const a b -> Const a b')
contramap :: (b' -> b) -> Const a b -> Const a b'
contramap b' -> b
_ (Const a
a) = a -> Const a b'
forall {k} a (b :: k). a -> Const a b
Const a
a
instance (Functor f, Contravariant g) => Contravariant (Compose f g) where
contramap :: (a' -> a) -> (Compose f g a -> Compose f g a')
contramap :: (a' -> a) -> Compose f g a -> Compose f g a'
contramap a' -> a
f (Compose f (g a)
fga) = f (g a') -> Compose f g a'
forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k).
f (g a) -> Compose f g a
Compose ((g a -> g a') -> f (g a) -> f (g a')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap ((a' -> a) -> g a -> g a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
Evidence bound by a type signature of the constraint type Contravariant g
contramap a' -> a
f) f (g a)
fga)
instance Contravariant Proxy where
contramap :: (a' -> a) -> (Proxy a -> Proxy a')
contramap :: (a' -> a) -> Proxy a -> Proxy a'
contramap a' -> a
_ Proxy a
_ = Proxy a'
forall {k} (t :: k). Proxy t
Proxy
newtype Predicate a = Predicate { Predicate a -> a -> Bool
getPredicate :: a -> Bool }
deriving
(
Semigroup
,
Monoid
)
via a -> All
deriving
(
Contravariant
)
via Op Bool
newtype Comparison a = Comparison { Comparison a -> a -> a -> Ordering
getComparison :: a -> a -> Ordering }
deriving
newtype
(
Semigroup
,
Monoid
)
instance Contravariant Comparison where
contramap :: (a' -> a) -> (Comparison a -> Comparison a')
contramap :: (a' -> a) -> Comparison a -> Comparison a'
contramap a' -> a
f (Comparison a -> a -> Ordering
g) = (a' -> a' -> Ordering) -> Comparison a'
forall a. (a -> a -> Ordering) -> Comparison a
Comparison ((a -> a -> Ordering) -> (a' -> a) -> a' -> a' -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on a -> a -> Ordering
g a' -> a
f)
defaultComparison :: Ord a => Comparison a
defaultComparison :: Comparison a
defaultComparison = (a -> a -> Ordering) -> Comparison a
forall a. (a -> a -> Ordering) -> Comparison a
Comparison a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord a
compare
newtype Equivalence a = Equivalence { Equivalence a -> a -> a -> Bool
getEquivalence :: a -> a -> Bool }
deriving
(
Semigroup
,
Monoid
)
via a -> a -> All
instance Contravariant Equivalence where
contramap :: (a' -> a) -> (Equivalence a -> Equivalence a')
contramap :: (a' -> a) -> Equivalence a -> Equivalence a'
contramap a' -> a
f (Equivalence a -> a -> Bool
g) = (a' -> a' -> Bool) -> Equivalence a'
forall a. (a -> a -> Bool) -> Equivalence a
Equivalence ((a -> a -> Bool) -> (a' -> a) -> a' -> a' -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on a -> a -> Bool
g a' -> a
f)
defaultEquivalence :: Eq a => Equivalence a
defaultEquivalence :: Equivalence a
defaultEquivalence = (a -> a -> Bool) -> Equivalence a
forall a. (a -> a -> Bool) -> Equivalence a
Equivalence a -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
(==)
comparisonEquivalence :: Comparison a -> Equivalence a
comparisonEquivalence :: Comparison a -> Equivalence a
comparisonEquivalence (Comparison a -> a -> Ordering
p) = (a -> a -> Bool) -> Equivalence a
forall a. (a -> a -> Bool) -> Equivalence a
Equivalence ((a -> a -> Bool) -> Equivalence a)
-> (a -> a -> Bool) -> Equivalence a
forall a b. (a -> b) -> a -> b
$ \a
a a
b -> a -> a -> Ordering
p a
a a
b Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Ordering
== Ordering
EQ
newtype Op a b = Op { Op a b -> b -> a
getOp :: b -> a }
deriving
newtype
(
Semigroup
,
Monoid
)
instance Category Op where
id :: Op a a
id :: Op a a
id = (a -> a) -> Op a a
forall a b. (b -> a) -> Op a b
Op a -> a
forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
External instance of the constraint type Category (->)
id
(.) :: Op b c -> Op a b -> Op a c
Op c -> b
f . :: Op b c -> Op a b -> Op a c
. Op b -> a
g = (c -> a) -> Op a c
forall a b. (b -> a) -> Op a b
Op (b -> a
g (b -> a) -> (c -> b) -> c -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. c -> b
f)
instance Contravariant (Op a) where
contramap :: (b' -> b) -> (Op a b -> Op a b')
contramap :: (b' -> b) -> Op a b -> Op a b'
contramap b' -> b
f Op a b
g = (b' -> a) -> Op a b'
forall a b. (b -> a) -> Op a b
Op (Op a b -> b -> a
forall a b. Op a b -> b -> a
getOp Op a b
g (b -> a) -> (b' -> b) -> b' -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b' -> b
f)
instance Num a => Num (Op a b) where
Op b -> a
f + :: Op a b -> Op a b -> Op a b
+ Op b -> a
g = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ \b
a -> b -> a
f b
a a -> a -> a
forall a. Num a => a -> a -> a
Evidence bound by a type signature of the constraint type Num a
+ b -> a
g b
a
Op b -> a
f * :: Op a b -> Op a b -> Op a b
* Op b -> a
g = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ \b
a -> b -> a
f b
a a -> a -> a
forall a. Num a => a -> a -> a
Evidence bound by a type signature of the constraint type Num a
* b -> a
g b
a
Op b -> a
f - :: Op a b -> Op a b -> Op a b
- Op b -> a
g = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ \b
a -> b -> a
f b
a a -> a -> a
forall a. Num a => a -> a -> a
Evidence bound by a type signature of the constraint type Num a
- b -> a
g b
a
abs :: Op a b -> Op a b
abs (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
Evidence bound by a type signature of the constraint type Num a
abs (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
signum :: Op a b -> Op a b
signum (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
Evidence bound by a type signature of the constraint type Num a
signum (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
fromInteger :: Integer -> Op a b
fromInteger = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (Integer -> b -> a) -> Integer -> Op a b
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. a -> b -> a
forall a b. a -> b -> a
const (a -> b -> a) -> (Integer -> a) -> Integer -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. Integer -> a
forall a. Num a => Integer -> a
Evidence bound by a type signature of the constraint type Num a
fromInteger
instance Fractional a => Fractional (Op a b) where
Op b -> a
f / :: Op a b -> Op a b -> Op a b
/ Op b -> a
g = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ \b
a -> b -> a
f b
a a -> a -> a
forall a. Fractional a => a -> a -> a
Evidence bound by a type signature of the constraint type Fractional a
/ b -> a
g b
a
recip :: Op a b -> Op a b
recip (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Fractional a => a -> a
Evidence bound by a type signature of the constraint type Fractional a
recip (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
fromRational :: Rational -> Op a b
fromRational = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (Rational -> b -> a) -> Rational -> Op a b
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. a -> b -> a
forall a b. a -> b -> a
const (a -> b -> a) -> (Rational -> a) -> Rational -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. Rational -> a
forall a. Fractional a => Rational -> a
Evidence bound by a type signature of the constraint type Fractional a
fromRational
instance Floating a => Floating (Op a b) where
pi :: Op a b
pi = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> b -> a
forall a b. a -> b -> a
const a
forall a. Floating a => a
Evidence bound by a type signature of the constraint type Floating a
pi
exp :: Op a b -> Op a b
exp (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
exp (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
sqrt :: Op a b -> Op a b
sqrt (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
sqrt (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
log :: Op a b -> Op a b
log (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
log (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
sin :: Op a b -> Op a b
sin (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
sin (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
tan :: Op a b -> Op a b
tan (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
tan (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
cos :: Op a b -> Op a b
cos (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
cos (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
asin :: Op a b -> Op a b
asin (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
asin (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
atan :: Op a b -> Op a b
atan (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
atan (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
acos :: Op a b -> Op a b
acos (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
acos (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
sinh :: Op a b -> Op a b
sinh (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
sinh (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
tanh :: Op a b -> Op a b
tanh (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
tanh (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
cosh :: Op a b -> Op a b
cosh (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
cosh (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
asinh :: Op a b -> Op a b
asinh (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
asinh (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
atanh :: Op a b -> Op a b
atanh (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
atanh (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
acosh :: Op a b -> Op a b
acosh (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Floating a => a -> a
Evidence bound by a type signature of the constraint type Floating a
acosh (a -> a) -> (b -> a) -> b -> a
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
External instance of the constraint type Category (->)
. b -> a
f
Op b -> a
f ** :: Op a b -> Op a b -> Op a b
** Op b -> a
g = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ \b
a -> b -> a
f b
a a -> a -> a
forall a. Floating a => a -> a -> a
Evidence bound by a type signature of the constraint type Floating a
** b -> a
g b
a
logBase :: Op a b -> Op a b -> Op a b
logBase (Op b -> a
f) (Op b -> a
g) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ \b
a -> a -> a -> a
forall a. Floating a => a -> a -> a
Evidence bound by a type signature of the constraint type Floating a
logBase (b -> a
f b
a) (b -> a
g b
a)