{-# OPTIONS_GHC -Wno-orphans #-}
module Cleff.Internal.Instances () where
import Cleff.Internal.Monad (Eff (Eff))
import Control.Applicative (Applicative (liftA2))
import Control.Monad.Zip (MonadZip (munzip, mzipWith))
import Data.Monoid (Ap (Ap))
import Data.String (IsString (fromString))
deriving via (Ap (Eff es) a) instance Bounded a => Bounded (Eff es a)
instance Num a => Num (Eff es a) where
+ :: Eff es a -> Eff es a -> Eff es a
(+) = (a -> a -> a) -> Eff es a -> Eff es a -> Eff es a
forall (f :: Type -> Type) 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
(+)
(-) = (a -> a -> a) -> Eff es a -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
* :: Eff es a -> Eff es a -> Eff es a
(*) = (a -> a -> a) -> Eff es a -> Eff es a -> Eff es a
forall (f :: Type -> Type) 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 :: Eff es a -> Eff es a
negate = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
negate
abs :: Eff es a -> Eff es a
abs = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
abs
signum :: Eff es a -> Eff es a
signum = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
signum
fromInteger :: Integer -> Eff es a
fromInteger = a -> Eff es a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (a -> Eff es a) -> (Integer -> a) -> Integer -> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger
instance Fractional a => Fractional (Eff es a) where
/ :: Eff es a -> Eff es a -> Eff es a
(/) = (a -> a -> a) -> Eff es a -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Fractional a => a -> a -> a
(/)
recip :: Eff es a -> Eff es a
recip = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Fractional a => a -> a
recip
fromRational :: Rational -> Eff es a
fromRational = a -> Eff es a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (a -> Eff es a) -> (Rational -> a) -> Rational -> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> a
forall a. Fractional a => Rational -> a
fromRational
instance Floating a => Floating (Eff es a) where
pi :: Eff es a
pi = a -> Eff es a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure a
forall a. Floating a => a
pi
exp :: Eff es a -> Eff es a
exp = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
exp
log :: Eff es a -> Eff es a
log = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
log
sqrt :: Eff es a -> Eff es a
sqrt = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sqrt
** :: Eff es a -> Eff es a -> Eff es a
(**) = (a -> a -> a) -> Eff es a -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Floating a => a -> a -> a
(**)
logBase :: Eff es a -> Eff es a -> Eff es a
logBase = (a -> a -> a) -> Eff es a -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Floating a => a -> a -> a
logBase
sin :: Eff es a -> Eff es a
sin = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sin
cos :: Eff es a -> Eff es a
cos = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cos
tan :: Eff es a -> Eff es a
tan = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tan
asin :: Eff es a -> Eff es a
asin = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asin
acos :: Eff es a -> Eff es a
acos = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acos
atan :: Eff es a -> Eff es a
atan = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atan
sinh :: Eff es a -> Eff es a
sinh = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sinh
cosh :: Eff es a -> Eff es a
cosh = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cosh
tanh :: Eff es a -> Eff es a
tanh = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tanh
asinh :: Eff es a -> Eff es a
asinh = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asinh
acosh :: Eff es a -> Eff es a
acosh = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acosh
atanh :: Eff es a -> Eff es a
atanh = (a -> a) -> Eff es a -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atanh
deriving newtype instance Semigroup a => Semigroup (Eff es a)
deriving newtype instance Monoid a => Monoid (Eff es a)
instance IsString a => IsString (Eff es a) where
fromString :: String -> Eff es a
fromString = a -> Eff es a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (a -> Eff es a) -> (String -> a) -> String -> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> a
forall a. IsString a => String -> a
fromString
instance MonadZip (Eff es) where
mzipWith :: (a -> b -> c) -> Eff es a -> Eff es b -> Eff es c
mzipWith = (a -> b -> c) -> Eff es a -> Eff es b -> Eff es c
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
munzip :: Eff es (a, b) -> (Eff es a, Eff es b)
munzip Eff es (a, b)
x = ((a, b) -> a
forall a b. (a, b) -> a
fst ((a, b) -> a) -> Eff es (a, b) -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Eff es (a, b)
x, (a, b) -> b
forall a b. (a, b) -> b
snd ((a, b) -> b) -> Eff es (a, b) -> Eff es b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Eff es (a, b)
x)