pure-noise-0.1.0.1: Performant, modern noise generation for Haskell with minimal dependencies. Based on FastNoiseLite.
MaintainerJeremy Nuttall <jeremy@jeremy-nuttall.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageGHC2021

Numeric.Noise

Description

 
Synopsis

Noise functions

Noise functions

data Noise2 a Source #

Instances

Instances details
Floating a => Floating (Noise2 a) Source # 
Instance details

Defined in Numeric.Noise.Internal

Methods

pi :: Noise2 a #

exp :: Noise2 a -> Noise2 a #

log :: Noise2 a -> Noise2 a #

sqrt :: Noise2 a -> Noise2 a #

(**) :: Noise2 a -> Noise2 a -> Noise2 a #

logBase :: Noise2 a -> Noise2 a -> Noise2 a #

sin :: Noise2 a -> Noise2 a #

cos :: Noise2 a -> Noise2 a #

tan :: Noise2 a -> Noise2 a #

asin :: Noise2 a -> Noise2 a #

acos :: Noise2 a -> Noise2 a #

atan :: Noise2 a -> Noise2 a #

sinh :: Noise2 a -> Noise2 a #

cosh :: Noise2 a -> Noise2 a #

tanh :: Noise2 a -> Noise2 a #

asinh :: Noise2 a -> Noise2 a #

acosh :: Noise2 a -> Noise2 a #

atanh :: Noise2 a -> Noise2 a #

log1p :: Noise2 a -> Noise2 a #

expm1 :: Noise2 a -> Noise2 a #

log1pexp :: Noise2 a -> Noise2 a #

log1mexp :: Noise2 a -> Noise2 a #

Num a => Num (Noise2 a) Source # 
Instance details

Defined in Numeric.Noise.Internal

Methods

(+) :: Noise2 a -> Noise2 a -> Noise2 a #

(-) :: Noise2 a -> Noise2 a -> Noise2 a #

(*) :: Noise2 a -> Noise2 a -> Noise2 a #

negate :: Noise2 a -> Noise2 a #

abs :: Noise2 a -> Noise2 a #

signum :: Noise2 a -> Noise2 a #

fromInteger :: Integer -> Noise2 a #

Fractional a => Fractional (Noise2 a) Source # 
Instance details

Defined in Numeric.Noise.Internal

Methods

(/) :: Noise2 a -> Noise2 a -> Noise2 a #

recip :: Noise2 a -> Noise2 a #

fromRational :: Rational -> Noise2 a #

data Noise3 a Source #

Instances

Instances details
Floating a => Floating (Noise3 a) Source # 
Instance details

Defined in Numeric.Noise.Internal

Methods

pi :: Noise3 a #

exp :: Noise3 a -> Noise3 a #

log :: Noise3 a -> Noise3 a #

sqrt :: Noise3 a -> Noise3 a #

(**) :: Noise3 a -> Noise3 a -> Noise3 a #

logBase :: Noise3 a -> Noise3 a -> Noise3 a #

sin :: Noise3 a -> Noise3 a #

cos :: Noise3 a -> Noise3 a #

tan :: Noise3 a -> Noise3 a #

asin :: Noise3 a -> Noise3 a #

acos :: Noise3 a -> Noise3 a #

atan :: Noise3 a -> Noise3 a #

sinh :: Noise3 a -> Noise3 a #

cosh :: Noise3 a -> Noise3 a #

tanh :: Noise3 a -> Noise3 a #

asinh :: Noise3 a -> Noise3 a #

acosh :: Noise3 a -> Noise3 a #

atanh :: Noise3 a -> Noise3 a #

log1p :: Noise3 a -> Noise3 a #

expm1 :: Noise3 a -> Noise3 a #

log1pexp :: Noise3 a -> Noise3 a #

log1mexp :: Noise3 a -> Noise3 a #

Num a => Num (Noise3 a) Source # 
Instance details

Defined in Numeric.Noise.Internal

Methods

(+) :: Noise3 a -> Noise3 a -> Noise3 a #

(-) :: Noise3 a -> Noise3 a -> Noise3 a #

(*) :: Noise3 a -> Noise3 a -> Noise3 a #

negate :: Noise3 a -> Noise3 a #

abs :: Noise3 a -> Noise3 a #

signum :: Noise3 a -> Noise3 a #

fromInteger :: Integer -> Noise3 a #

Fractional a => Fractional (Noise3 a) Source # 
Instance details

Defined in Numeric.Noise.Internal

Methods

(/) :: Noise3 a -> Noise3 a -> Noise3 a #

recip :: Noise3 a -> Noise3 a #

fromRational :: Rational -> Noise3 a #

noise2At :: Noise2 a -> Seed -> a -> a -> a Source #

noise3At :: Noise3 a -> Seed -> a -> a -> a -> a Source #

2D Noise

3D Noise

Noise manipulation

Math utility functions

clamp Source #

Arguments

:: Ord a 
=> a

lower bound

-> a

upper bound

-> a

value

-> a 

clamp2 :: Ord a => a -> a -> Noise2 a -> Noise2 a Source #

clamp3 :: Ord a => a -> a -> Noise3 a -> Noise3 a Source #

cubicInterp :: Num a => a -> a -> a -> a -> a -> a Source #

cubic interpolation

hermiteInterp :: Num a => a -> a Source #

hermite interpolation

lerp Source #

Arguments

:: Num a 
=> a

start

-> a

end

-> a

parameter in range [0, 1]

-> a 

monotonic lerp

quinticInterp :: Num a => a -> a Source #

quintic interpolation

Fractal Brownian Motion

Cellular noise configuration

data CellularConfig a Source #

Instances

Instances details
Generic (CellularConfig a) Source # 
Instance details

Defined in Numeric.Noise.Cellular

Associated Types

type Rep (CellularConfig a) :: Type -> Type #

Show a => Show (CellularConfig a) Source # 
Instance details

Defined in Numeric.Noise.Cellular

type Rep (CellularConfig a) Source # 
Instance details

Defined in Numeric.Noise.Cellular

type Rep (CellularConfig a) = D1 ('MetaData "CellularConfig" "Numeric.Noise.Cellular" "pure-noise-0.1.0.1-1DAIMG369CFHKouqQm7cYB" 'False) (C1 ('MetaCons "CellularConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "cellularDistanceFn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CellularDistanceFn) :*: (S1 ('MetaSel ('Just "cellularJitter") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "cellularResult") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CellularResult))))

data CellularDistanceFn Source #

Instances

Instances details
Bounded CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

Enum CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

Generic CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

Associated Types

type Rep CellularDistanceFn :: Type -> Type #

Read CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

Show CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

Eq CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

Ord CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

type Rep CellularDistanceFn Source # 
Instance details

Defined in Numeric.Noise.Cellular

type Rep CellularDistanceFn = D1 ('MetaData "CellularDistanceFn" "Numeric.Noise.Cellular" "pure-noise-0.1.0.1-1DAIMG369CFHKouqQm7cYB" 'False) ((C1 ('MetaCons "DistEuclidean" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistEuclideanSq" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DistManhattan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistHybrid" 'PrefixI 'False) (U1 :: Type -> Type)))

data CellularResult Source #

Instances

Instances details
Bounded CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

Enum CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

Generic CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

Associated Types

type Rep CellularResult :: Type -> Type #

Read CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

Show CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

Eq CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

Ord CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

type Rep CellularResult Source # 
Instance details

Defined in Numeric.Noise.Cellular

type Rep CellularResult = D1 ('MetaData "CellularResult" "Numeric.Noise.Cellular" "pure-noise-0.1.0.1-1DAIMG369CFHKouqQm7cYB" 'False) ((C1 ('MetaCons "CellValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Distance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Distance2" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Distance2Add" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Distance2Sub" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Distance2Mul" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Distance2Div" 'PrefixI 'False) (U1 :: Type -> Type))))