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.Cellular

Description

 
Synopsis

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))))

2D Noise

noise2BaseWith Source #

Arguments

:: RealFrac a 
=> a

cellular jitter

-> (a -> a -> a)

distance function

-> Seed 
-> a

x

-> a

y

-> (Hash, a, a) 

Calculate 2D cellular noise values at a given point using the given distance function