module Numeric.Noise.Internal (
module Math,
Noise2 (..),
next2,
map2,
clamp2,
const2,
Noise3 (..),
next3,
map3,
clamp3,
const3,
) where
import Numeric.Noise.Internal.Math as Math (
Hash,
Seed,
clamp,
cubicInterp,
hermiteInterp,
lerp,
quinticInterp,
)
newtype Noise2 a = Noise2
{forall a. Noise2 a -> Seed -> a -> a -> a
unNoise2 :: Seed -> a -> a -> a}
next2 :: Noise2 a -> Noise2 a
next2 :: forall a. Noise2 a -> Noise2 a
next2 (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 (\Seed
s a
x a
y -> Seed -> a -> a -> a
f (Seed
s Seed -> Seed -> Seed
forall a. Num a => a -> a -> a
+ Seed
1) a
x a
y)
{-# INLINE next2 #-}
map2 :: (a -> a) -> Noise2 a -> Noise2 a
map2 :: forall a. (a -> a) -> Noise2 a -> Noise2 a
map2 a -> a
f (Noise2 Seed -> a -> a -> a
g) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 (\Seed
s a
x a
y -> a -> a
f (Seed -> a -> a -> a
g Seed
s a
x a
y))
{-# INLINE map2 #-}
clamp2 :: (Ord a) => a -> a -> Noise2 a -> Noise2 a
clamp2 :: forall a. Ord a => a -> a -> Noise2 a -> Noise2 a
clamp2 a
l a
u (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a -> a -> a
forall a. Ord a => a -> a -> a -> a
clamp a
l a
u (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE clamp2 #-}
const2 :: a -> Noise2 a
const2 :: forall a. a -> Noise2 a
const2 a
a = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 (\Seed
_ a
_ a
_ -> a
a)
{-# INLINE const2 #-}
instance (Num a) => Num (Noise2 a) where
Noise2 Seed -> a -> a -> a
f + :: Noise2 a -> Noise2 a -> Noise2 a
+ Noise2 Seed -> a -> a -> a
g = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> Seed -> a -> a -> a
f Seed
s a
x a
y a -> a -> a
forall a. Num a => a -> a -> a
+ Seed -> a -> a -> a
g Seed
s a
x a
y
{-# INLINE (+) #-}
Noise2 Seed -> a -> a -> a
f * :: Noise2 a -> Noise2 a -> Noise2 a
* Noise2 Seed -> a -> a -> a
g = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> Seed -> a -> a -> a
f Seed
s a
x a
y a -> a -> a
forall a. Num a => a -> a -> a
* Seed -> a -> a -> a
g Seed
s a
x a
y
{-# INLINE (*) #-}
abs :: Noise2 a -> Noise2 a
abs (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Num a => a -> a
abs (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE abs #-}
signum :: Noise2 a -> Noise2 a
signum (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Num a => a -> a
signum (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE signum #-}
fromInteger :: Integer -> Noise2 a
fromInteger Integer
i = a -> Noise2 a
forall a. a -> Noise2 a
const2 (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
i)
{-# INLINE fromInteger #-}
negate :: Noise2 a -> Noise2 a
negate (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Num a => a -> a
negate (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE negate #-}
instance (Fractional a) => Fractional (Noise2 a) where
fromRational :: Rational -> Noise2 a
fromRational Rational
r = a -> Noise2 a
forall a. a -> Noise2 a
const2 (Rational -> a
forall a. Fractional a => Rational -> a
fromRational Rational
r)
{-# INLINE fromRational #-}
recip :: Noise2 a -> Noise2 a
recip (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Fractional a => a -> a
recip (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE recip #-}
Noise2 Seed -> a -> a -> a
f / :: Noise2 a -> Noise2 a -> Noise2 a
/ Noise2 Seed -> a -> a -> a
g = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> Seed -> a -> a -> a
f Seed
s a
x a
y a -> a -> a
forall a. Fractional a => a -> a -> a
/ Seed -> a -> a -> a
g Seed
s a
x a
y
{-# INLINE (/) #-}
instance (Floating a) => Floating (Noise2 a) where
pi :: Noise2 a
pi = a -> Noise2 a
forall a. a -> Noise2 a
const2 a
forall a. Floating a => a
pi
{-# INLINE pi #-}
exp :: Noise2 a -> Noise2 a
exp (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
exp (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE exp #-}
log :: Noise2 a -> Noise2 a
log (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
log (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE log #-}
sin :: Noise2 a -> Noise2 a
sin (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
sin (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE sin #-}
cos :: Noise2 a -> Noise2 a
cos (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
cos (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE cos #-}
asin :: Noise2 a -> Noise2 a
asin (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
asin (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE asin #-}
acos :: Noise2 a -> Noise2 a
acos (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
acos (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE acos #-}
atan :: Noise2 a -> Noise2 a
atan (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
atan (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE atan #-}
sinh :: Noise2 a -> Noise2 a
sinh (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
sinh (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE sinh #-}
cosh :: Noise2 a -> Noise2 a
cosh (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
cosh (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE cosh #-}
asinh :: Noise2 a -> Noise2 a
asinh (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
asinh (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE asinh #-}
acosh :: Noise2 a -> Noise2 a
acosh (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
acosh (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE acosh #-}
atanh :: Noise2 a -> Noise2 a
atanh (Noise2 Seed -> a -> a -> a
f) = (Seed -> a -> a -> a) -> Noise2 a
forall a. (Seed -> a -> a -> a) -> Noise2 a
Noise2 ((Seed -> a -> a -> a) -> Noise2 a)
-> (Seed -> a -> a -> a) -> Noise2 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y -> a -> a
forall a. Floating a => a -> a
atanh (Seed -> a -> a -> a
f Seed
s a
x a
y)
{-# INLINE atanh #-}
newtype Noise3 a = Noise3
{forall a. Noise3 a -> Seed -> a -> a -> a -> a
unNoise3 :: Seed -> a -> a -> a -> a}
next3 :: Noise3 a -> Noise3 a
next3 :: forall a. Noise3 a -> Noise3 a
next3 (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 (\Seed
s a
x a
y a
z -> Seed -> a -> a -> a -> a
f (Seed
s Seed -> Seed -> Seed
forall a. Num a => a -> a -> a
+ Seed
1) a
x a
y a
z)
{-# INLINE next3 #-}
map3 :: (a -> a) -> Noise3 a -> Noise3 a
map3 :: forall a. (a -> a) -> Noise3 a -> Noise3 a
map3 a -> a
f (Noise3 Seed -> a -> a -> a -> a
g) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 (\Seed
s a
x a
y a
z -> a -> a
f (Seed -> a -> a -> a -> a
g Seed
s a
x a
y a
z))
{-# INLINE map3 #-}
const3 :: a -> Noise3 a
const3 :: forall a. a -> Noise3 a
const3 a
a = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 (\Seed
_ a
_ a
_ a
_ -> a
a)
{-# INLINE const3 #-}
clamp3 :: (Ord a) => a -> a -> Noise3 a -> Noise3 a
clamp3 :: forall a. Ord a => a -> a -> Noise3 a -> Noise3 a
clamp3 a
l a
u (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a -> a -> a
forall a. Ord a => a -> a -> a -> a
clamp a
l a
u (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE clamp3 #-}
instance (Num a) => Num (Noise3 a) where
Noise3 Seed -> a -> a -> a -> a
f + :: Noise3 a -> Noise3 a -> Noise3 a
+ Noise3 Seed -> a -> a -> a -> a
g = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z a -> a -> a
forall a. Num a => a -> a -> a
+ Seed -> a -> a -> a -> a
g Seed
s a
x a
y a
z
{-# INLINE (+) #-}
Noise3 Seed -> a -> a -> a -> a
f * :: Noise3 a -> Noise3 a -> Noise3 a
* Noise3 Seed -> a -> a -> a -> a
g = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z a -> a -> a
forall a. Num a => a -> a -> a
* Seed -> a -> a -> a -> a
g Seed
s a
x a
y a
z
{-# INLINE (*) #-}
abs :: Noise3 a -> Noise3 a
abs (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Num a => a -> a
abs (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE abs #-}
signum :: Noise3 a -> Noise3 a
signum (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Num a => a -> a
signum (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE signum #-}
fromInteger :: Integer -> Noise3 a
fromInteger Integer
i = a -> Noise3 a
forall a. a -> Noise3 a
const3 (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
i)
{-# INLINE fromInteger #-}
negate :: Noise3 a -> Noise3 a
negate (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Num a => a -> a
negate (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE negate #-}
instance (Fractional a) => Fractional (Noise3 a) where
fromRational :: Rational -> Noise3 a
fromRational Rational
r = a -> Noise3 a
forall a. a -> Noise3 a
const3 (Rational -> a
forall a. Fractional a => Rational -> a
fromRational Rational
r)
{-# INLINE fromRational #-}
recip :: Noise3 a -> Noise3 a
recip (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Fractional a => a -> a
recip (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE recip #-}
instance (Floating a) => Floating (Noise3 a) where
pi :: Noise3 a
pi = a -> Noise3 a
forall a. a -> Noise3 a
const3 a
forall a. Floating a => a
pi
{-# INLINE pi #-}
exp :: Noise3 a -> Noise3 a
exp (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
exp (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE exp #-}
log :: Noise3 a -> Noise3 a
log (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
log (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE log #-}
sin :: Noise3 a -> Noise3 a
sin (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
sin (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE sin #-}
cos :: Noise3 a -> Noise3 a
cos (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
cos (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE cos #-}
asin :: Noise3 a -> Noise3 a
asin (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
asin (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE asin #-}
acos :: Noise3 a -> Noise3 a
acos (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
acos (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE acos #-}
atan :: Noise3 a -> Noise3 a
atan (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
atan (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE atan #-}
sinh :: Noise3 a -> Noise3 a
sinh (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
sinh (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE sinh #-}
cosh :: Noise3 a -> Noise3 a
cosh (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
cosh (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE cosh #-}
asinh :: Noise3 a -> Noise3 a
asinh (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
asinh (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE asinh #-}
acosh :: Noise3 a -> Noise3 a
acosh (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
acosh (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE acosh #-}
atanh :: Noise3 a -> Noise3 a
atanh (Noise3 Seed -> a -> a -> a -> a
f) = (Seed -> a -> a -> a -> a) -> Noise3 a
forall a. (Seed -> a -> a -> a -> a) -> Noise3 a
Noise3 ((Seed -> a -> a -> a -> a) -> Noise3 a)
-> (Seed -> a -> a -> a -> a) -> Noise3 a
forall a b. (a -> b) -> a -> b
$ \Seed
s a
x a
y a
z -> a -> a
forall a. Floating a => a -> a
atanh (Seed -> a -> a -> a -> a
f Seed
s a
x a
y a
z)
{-# INLINE atanh #-}