{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE RecordWildCards #-}
module Numeric.Noise.Cellular (
CellularConfig (..),
defaultCellularConfig,
CellularDistanceFn (..),
CellularResult (..),
noise2,
noise2BaseWith,
) where
import Data.Bits
import Data.Foldable
import Data.Vector.Unboxed qualified as U
import GHC.Generics (Generic)
import Numeric.Noise.Internal
import Numeric.Noise.Internal.Math
data CellularConfig a = CellularConfig
{ forall a. CellularConfig a -> CellularDistanceFn
cellularDistanceFn :: !CellularDistanceFn
, forall a. CellularConfig a -> a
cellularJitter :: !a
, forall a. CellularConfig a -> CellularResult
cellularResult :: !CellularResult
}
deriving ((forall x. CellularConfig a -> Rep (CellularConfig a) x)
-> (forall x. Rep (CellularConfig a) x -> CellularConfig a)
-> Generic (CellularConfig a)
forall x. Rep (CellularConfig a) x -> CellularConfig a
forall x. CellularConfig a -> Rep (CellularConfig a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CellularConfig a) x -> CellularConfig a
forall a x. CellularConfig a -> Rep (CellularConfig a) x
$cfrom :: forall a x. CellularConfig a -> Rep (CellularConfig a) x
from :: forall x. CellularConfig a -> Rep (CellularConfig a) x
$cto :: forall a x. Rep (CellularConfig a) x -> CellularConfig a
to :: forall x. Rep (CellularConfig a) x -> CellularConfig a
Generic, Int -> CellularConfig a -> ShowS
[CellularConfig a] -> ShowS
CellularConfig a -> String
(Int -> CellularConfig a -> ShowS)
-> (CellularConfig a -> String)
-> ([CellularConfig a] -> ShowS)
-> Show (CellularConfig a)
forall a. Show a => Int -> CellularConfig a -> ShowS
forall a. Show a => [CellularConfig a] -> ShowS
forall a. Show a => CellularConfig a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CellularConfig a -> ShowS
showsPrec :: Int -> CellularConfig a -> ShowS
$cshow :: forall a. Show a => CellularConfig a -> String
show :: CellularConfig a -> String
$cshowList :: forall a. Show a => [CellularConfig a] -> ShowS
showList :: [CellularConfig a] -> ShowS
Show)
defaultCellularConfig :: (RealFrac a) => CellularConfig a
defaultCellularConfig :: forall a. RealFrac a => CellularConfig a
defaultCellularConfig =
CellularConfig
{ cellularDistanceFn :: CellularDistanceFn
cellularDistanceFn = CellularDistanceFn
DistEuclidean
, cellularJitter :: a
cellularJitter = a
1
, cellularResult :: CellularResult
cellularResult = CellularResult
CellValue
}
data CellularDistanceFn
= DistEuclidean
| DistEuclideanSq
| DistManhattan
| DistHybrid
deriving ((forall x. CellularDistanceFn -> Rep CellularDistanceFn x)
-> (forall x. Rep CellularDistanceFn x -> CellularDistanceFn)
-> Generic CellularDistanceFn
forall x. Rep CellularDistanceFn x -> CellularDistanceFn
forall x. CellularDistanceFn -> Rep CellularDistanceFn x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CellularDistanceFn -> Rep CellularDistanceFn x
from :: forall x. CellularDistanceFn -> Rep CellularDistanceFn x
$cto :: forall x. Rep CellularDistanceFn x -> CellularDistanceFn
to :: forall x. Rep CellularDistanceFn x -> CellularDistanceFn
Generic, ReadPrec [CellularDistanceFn]
ReadPrec CellularDistanceFn
Int -> ReadS CellularDistanceFn
ReadS [CellularDistanceFn]
(Int -> ReadS CellularDistanceFn)
-> ReadS [CellularDistanceFn]
-> ReadPrec CellularDistanceFn
-> ReadPrec [CellularDistanceFn]
-> Read CellularDistanceFn
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CellularDistanceFn
readsPrec :: Int -> ReadS CellularDistanceFn
$creadList :: ReadS [CellularDistanceFn]
readList :: ReadS [CellularDistanceFn]
$creadPrec :: ReadPrec CellularDistanceFn
readPrec :: ReadPrec CellularDistanceFn
$creadListPrec :: ReadPrec [CellularDistanceFn]
readListPrec :: ReadPrec [CellularDistanceFn]
Read, Int -> CellularDistanceFn -> ShowS
[CellularDistanceFn] -> ShowS
CellularDistanceFn -> String
(Int -> CellularDistanceFn -> ShowS)
-> (CellularDistanceFn -> String)
-> ([CellularDistanceFn] -> ShowS)
-> Show CellularDistanceFn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CellularDistanceFn -> ShowS
showsPrec :: Int -> CellularDistanceFn -> ShowS
$cshow :: CellularDistanceFn -> String
show :: CellularDistanceFn -> String
$cshowList :: [CellularDistanceFn] -> ShowS
showList :: [CellularDistanceFn] -> ShowS
Show, CellularDistanceFn -> CellularDistanceFn -> Bool
(CellularDistanceFn -> CellularDistanceFn -> Bool)
-> (CellularDistanceFn -> CellularDistanceFn -> Bool)
-> Eq CellularDistanceFn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CellularDistanceFn -> CellularDistanceFn -> Bool
== :: CellularDistanceFn -> CellularDistanceFn -> Bool
$c/= :: CellularDistanceFn -> CellularDistanceFn -> Bool
/= :: CellularDistanceFn -> CellularDistanceFn -> Bool
Eq, Eq CellularDistanceFn
Eq CellularDistanceFn =>
(CellularDistanceFn -> CellularDistanceFn -> Ordering)
-> (CellularDistanceFn -> CellularDistanceFn -> Bool)
-> (CellularDistanceFn -> CellularDistanceFn -> Bool)
-> (CellularDistanceFn -> CellularDistanceFn -> Bool)
-> (CellularDistanceFn -> CellularDistanceFn -> Bool)
-> (CellularDistanceFn -> CellularDistanceFn -> CellularDistanceFn)
-> (CellularDistanceFn -> CellularDistanceFn -> CellularDistanceFn)
-> Ord CellularDistanceFn
CellularDistanceFn -> CellularDistanceFn -> Bool
CellularDistanceFn -> CellularDistanceFn -> Ordering
CellularDistanceFn -> CellularDistanceFn -> CellularDistanceFn
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CellularDistanceFn -> CellularDistanceFn -> Ordering
compare :: CellularDistanceFn -> CellularDistanceFn -> Ordering
$c< :: CellularDistanceFn -> CellularDistanceFn -> Bool
< :: CellularDistanceFn -> CellularDistanceFn -> Bool
$c<= :: CellularDistanceFn -> CellularDistanceFn -> Bool
<= :: CellularDistanceFn -> CellularDistanceFn -> Bool
$c> :: CellularDistanceFn -> CellularDistanceFn -> Bool
> :: CellularDistanceFn -> CellularDistanceFn -> Bool
$c>= :: CellularDistanceFn -> CellularDistanceFn -> Bool
>= :: CellularDistanceFn -> CellularDistanceFn -> Bool
$cmax :: CellularDistanceFn -> CellularDistanceFn -> CellularDistanceFn
max :: CellularDistanceFn -> CellularDistanceFn -> CellularDistanceFn
$cmin :: CellularDistanceFn -> CellularDistanceFn -> CellularDistanceFn
min :: CellularDistanceFn -> CellularDistanceFn -> CellularDistanceFn
Ord, Int -> CellularDistanceFn
CellularDistanceFn -> Int
CellularDistanceFn -> [CellularDistanceFn]
CellularDistanceFn -> CellularDistanceFn
CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
CellularDistanceFn
-> CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
(CellularDistanceFn -> CellularDistanceFn)
-> (CellularDistanceFn -> CellularDistanceFn)
-> (Int -> CellularDistanceFn)
-> (CellularDistanceFn -> Int)
-> (CellularDistanceFn -> [CellularDistanceFn])
-> (CellularDistanceFn
-> CellularDistanceFn -> [CellularDistanceFn])
-> (CellularDistanceFn
-> CellularDistanceFn -> [CellularDistanceFn])
-> (CellularDistanceFn
-> CellularDistanceFn
-> CellularDistanceFn
-> [CellularDistanceFn])
-> Enum CellularDistanceFn
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: CellularDistanceFn -> CellularDistanceFn
succ :: CellularDistanceFn -> CellularDistanceFn
$cpred :: CellularDistanceFn -> CellularDistanceFn
pred :: CellularDistanceFn -> CellularDistanceFn
$ctoEnum :: Int -> CellularDistanceFn
toEnum :: Int -> CellularDistanceFn
$cfromEnum :: CellularDistanceFn -> Int
fromEnum :: CellularDistanceFn -> Int
$cenumFrom :: CellularDistanceFn -> [CellularDistanceFn]
enumFrom :: CellularDistanceFn -> [CellularDistanceFn]
$cenumFromThen :: CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
enumFromThen :: CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
$cenumFromTo :: CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
enumFromTo :: CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
$cenumFromThenTo :: CellularDistanceFn
-> CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
enumFromThenTo :: CellularDistanceFn
-> CellularDistanceFn -> CellularDistanceFn -> [CellularDistanceFn]
Enum, CellularDistanceFn
CellularDistanceFn
-> CellularDistanceFn -> Bounded CellularDistanceFn
forall a. a -> a -> Bounded a
$cminBound :: CellularDistanceFn
minBound :: CellularDistanceFn
$cmaxBound :: CellularDistanceFn
maxBound :: CellularDistanceFn
Bounded)
data CellularResult
= CellValue
| Distance
| Distance2
| Distance2Add
| Distance2Sub
| Distance2Mul
| Distance2Div
deriving ((forall x. CellularResult -> Rep CellularResult x)
-> (forall x. Rep CellularResult x -> CellularResult)
-> Generic CellularResult
forall x. Rep CellularResult x -> CellularResult
forall x. CellularResult -> Rep CellularResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CellularResult -> Rep CellularResult x
from :: forall x. CellularResult -> Rep CellularResult x
$cto :: forall x. Rep CellularResult x -> CellularResult
to :: forall x. Rep CellularResult x -> CellularResult
Generic, ReadPrec [CellularResult]
ReadPrec CellularResult
Int -> ReadS CellularResult
ReadS [CellularResult]
(Int -> ReadS CellularResult)
-> ReadS [CellularResult]
-> ReadPrec CellularResult
-> ReadPrec [CellularResult]
-> Read CellularResult
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CellularResult
readsPrec :: Int -> ReadS CellularResult
$creadList :: ReadS [CellularResult]
readList :: ReadS [CellularResult]
$creadPrec :: ReadPrec CellularResult
readPrec :: ReadPrec CellularResult
$creadListPrec :: ReadPrec [CellularResult]
readListPrec :: ReadPrec [CellularResult]
Read, Int -> CellularResult -> ShowS
[CellularResult] -> ShowS
CellularResult -> String
(Int -> CellularResult -> ShowS)
-> (CellularResult -> String)
-> ([CellularResult] -> ShowS)
-> Show CellularResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CellularResult -> ShowS
showsPrec :: Int -> CellularResult -> ShowS
$cshow :: CellularResult -> String
show :: CellularResult -> String
$cshowList :: [CellularResult] -> ShowS
showList :: [CellularResult] -> ShowS
Show, CellularResult -> CellularResult -> Bool
(CellularResult -> CellularResult -> Bool)
-> (CellularResult -> CellularResult -> Bool) -> Eq CellularResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CellularResult -> CellularResult -> Bool
== :: CellularResult -> CellularResult -> Bool
$c/= :: CellularResult -> CellularResult -> Bool
/= :: CellularResult -> CellularResult -> Bool
Eq, Eq CellularResult
Eq CellularResult =>
(CellularResult -> CellularResult -> Ordering)
-> (CellularResult -> CellularResult -> Bool)
-> (CellularResult -> CellularResult -> Bool)
-> (CellularResult -> CellularResult -> Bool)
-> (CellularResult -> CellularResult -> Bool)
-> (CellularResult -> CellularResult -> CellularResult)
-> (CellularResult -> CellularResult -> CellularResult)
-> Ord CellularResult
CellularResult -> CellularResult -> Bool
CellularResult -> CellularResult -> Ordering
CellularResult -> CellularResult -> CellularResult
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CellularResult -> CellularResult -> Ordering
compare :: CellularResult -> CellularResult -> Ordering
$c< :: CellularResult -> CellularResult -> Bool
< :: CellularResult -> CellularResult -> Bool
$c<= :: CellularResult -> CellularResult -> Bool
<= :: CellularResult -> CellularResult -> Bool
$c> :: CellularResult -> CellularResult -> Bool
> :: CellularResult -> CellularResult -> Bool
$c>= :: CellularResult -> CellularResult -> Bool
>= :: CellularResult -> CellularResult -> Bool
$cmax :: CellularResult -> CellularResult -> CellularResult
max :: CellularResult -> CellularResult -> CellularResult
$cmin :: CellularResult -> CellularResult -> CellularResult
min :: CellularResult -> CellularResult -> CellularResult
Ord, Int -> CellularResult
CellularResult -> Int
CellularResult -> [CellularResult]
CellularResult -> CellularResult
CellularResult -> CellularResult -> [CellularResult]
CellularResult
-> CellularResult -> CellularResult -> [CellularResult]
(CellularResult -> CellularResult)
-> (CellularResult -> CellularResult)
-> (Int -> CellularResult)
-> (CellularResult -> Int)
-> (CellularResult -> [CellularResult])
-> (CellularResult -> CellularResult -> [CellularResult])
-> (CellularResult -> CellularResult -> [CellularResult])
-> (CellularResult
-> CellularResult -> CellularResult -> [CellularResult])
-> Enum CellularResult
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: CellularResult -> CellularResult
succ :: CellularResult -> CellularResult
$cpred :: CellularResult -> CellularResult
pred :: CellularResult -> CellularResult
$ctoEnum :: Int -> CellularResult
toEnum :: Int -> CellularResult
$cfromEnum :: CellularResult -> Int
fromEnum :: CellularResult -> Int
$cenumFrom :: CellularResult -> [CellularResult]
enumFrom :: CellularResult -> [CellularResult]
$cenumFromThen :: CellularResult -> CellularResult -> [CellularResult]
enumFromThen :: CellularResult -> CellularResult -> [CellularResult]
$cenumFromTo :: CellularResult -> CellularResult -> [CellularResult]
enumFromTo :: CellularResult -> CellularResult -> [CellularResult]
$cenumFromThenTo :: CellularResult
-> CellularResult -> CellularResult -> [CellularResult]
enumFromThenTo :: CellularResult
-> CellularResult -> CellularResult -> [CellularResult]
Enum, CellularResult
CellularResult -> CellularResult -> Bounded CellularResult
forall a. a -> a -> Bounded a
$cminBound :: CellularResult
minBound :: CellularResult
$cmaxBound :: CellularResult
maxBound :: CellularResult
Bounded)
distance :: (RealFrac a) => CellularDistanceFn -> a -> a -> a
distance :: forall a. RealFrac a => CellularDistanceFn -> a -> a -> a
distance = \case
CellularDistanceFn
DistEuclidean -> \ !a
x !a
y -> a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y a -> a -> a
forall a. Num a => a -> a -> a
* a
y
CellularDistanceFn
DistEuclideanSq -> \ !a
x !a
y -> a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y a -> a -> a
forall a. Num a => a -> a -> a
* a
y
CellularDistanceFn
DistManhattan -> \ !a
x !a
y -> a -> a
forall a. Num a => a -> a
abs a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a. Num a => a -> a
abs a
y
CellularDistanceFn
DistHybrid -> \ !a
x !a
y -> a -> a
forall a. Num a => a -> a
abs a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a. Num a => a -> a
abs a
y a -> a -> a
forall a. Num a => a -> a -> a
+ (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y a -> a -> a
forall a. Num a => a -> a -> a
* a
y)
{-# INLINE distance #-}
normDist :: (Floating a) => CellularDistanceFn -> a -> a
normDist :: forall a. Floating a => CellularDistanceFn -> a -> a
normDist = \case
CellularDistanceFn
DistEuclidean -> a -> a
forall a. Floating a => a -> a
sqrt
CellularDistanceFn
_ -> a -> a
forall a. a -> a
id
{-# INLINE normDist #-}
noise2 :: (RealFrac a, Floating a) => CellularConfig a -> Noise2 a
noise2 :: forall a. (RealFrac a, Floating a) => CellularConfig a -> Noise2 a
noise2 CellularConfig{a
CellularResult
CellularDistanceFn
cellularDistanceFn :: forall a. CellularConfig a -> CellularDistanceFn
cellularJitter :: forall a. CellularConfig a -> a
cellularResult :: forall a. CellularConfig a -> CellularResult
cellularDistanceFn :: CellularDistanceFn
cellularJitter :: a
cellularResult :: CellularResult
..} =
let !jitter :: a
jitter = a
cellularJitter a -> a -> a
forall a. Num a => a -> a -> a
* a
0.43701595
!dist :: a -> a -> a
dist = CellularDistanceFn -> a -> a -> a
forall a. RealFrac a => CellularDistanceFn -> a -> a -> a
distance CellularDistanceFn
cellularDistanceFn
!norm :: a -> a
norm = CellularDistanceFn -> a -> a
forall a. Floating a => CellularDistanceFn -> a -> a
normDist CellularDistanceFn
cellularDistanceFn
coeff :: a
coeff = a
1 a -> a -> a
forall a. Fractional a => a -> a -> a
/ (Hash -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bounded a => a
maxBound @Hash) a -> a -> a
forall a. Num a => a -> a -> a
+ a
1)
in (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
seed a
x a
y ->
let (!Hash
hash, !a
d0u, !a
d1u) = a -> (a -> a -> a) -> Seed -> a -> a -> (Hash, a, a)
forall a.
RealFrac a =>
a -> (a -> a -> a) -> Seed -> a -> a -> (Hash, a, a)
noise2BaseWith a
jitter a -> a -> a
dist Seed
seed a
x a
y
!d0 :: a
d0 = a -> a
norm a
d0u
!d1 :: a
d1 = a -> a
norm a
d1u
in case CellularResult
cellularResult of
CellularResult
CellValue -> Hash -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Hash
hash a -> a -> a
forall a. Num a => a -> a -> a
* a
coeff
CellularResult
Distance -> a
d0 a -> a -> a
forall a. Num a => a -> a -> a
- a
1
CellularResult
Distance2 -> a
d1 a -> a -> a
forall a. Num a => a -> a -> a
- a
1
CellularResult
Distance2Add -> (a
d1 a -> a -> a
forall a. Num a => a -> a -> a
+ a
d0) a -> a -> a
forall a. Num a => a -> a -> a
* a
0.5 a -> a -> a
forall a. Num a => a -> a -> a
- a
1
CellularResult
Distance2Sub -> a
d1 a -> a -> a
forall a. Num a => a -> a -> a
- a
d0 a -> a -> a
forall a. Num a => a -> a -> a
- a
1
CellularResult
Distance2Mul -> a
d1 a -> a -> a
forall a. Num a => a -> a -> a
* a
d0 a -> a -> a
forall a. Num a => a -> a -> a
* a
0.5 a -> a -> a
forall a. Num a => a -> a -> a
- a
1
CellularResult
Distance2Div -> a
d0 a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
d1 a -> a -> a
forall a. Num a => a -> a -> a
- a
1
{-# INLINE noise2 #-}
noise2BaseWith
:: (RealFrac a)
=> a
-> (a -> a -> a)
-> Seed
-> a
-> a
-> (Hash, a, a)
noise2BaseWith :: forall a.
RealFrac a =>
a -> (a -> a -> a) -> Seed -> a -> a -> (Hash, a, a)
noise2BaseWith !a
jitter !a -> a -> a
dist !Seed
seed !a
x !a
y =
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' @[]
(Hash, a, a) -> (Hash, a) -> (Hash, a, a)
forall {c} {a}. Ord c => (a, c, c) -> (a, c) -> (a, c, c)
minmax
(Hash
0, a
forall a. Fractional a => a
infinity, a
forall a. Fractional a => a
infinity)
[Hash -> Hash -> (Hash, a)
pointDist (Hash
rx Hash -> Hash -> Hash
forall a. Num a => a -> a -> a
+ Hash
xi) (Hash
ry Hash -> Hash -> Hash
forall a. Num a => a -> a -> a
+ Hash
yi) | !Hash
xi <- [-Hash
1 .. Hash
Item [Hash]
1], !Hash
yi <- [-Hash
1 .. Hash
Item [Hash]
1]]
where
!rx :: Hash
rx = a -> Hash
forall b. Integral b => a -> b
forall a b. (RealFrac a, Integral b) => a -> b
round a
x
!ry :: Hash
ry = a -> Hash
forall b. Integral b => a -> b
forall a b. (RealFrac a, Integral b) => a -> b
round a
y
minmax :: (a, c, c) -> (a, c) -> (a, c, c)
minmax (!a
c, !c
d0, !c
d1) (!a
h, !c
d)
| c
d c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
d0 = (a
h, c
d, c
d1')
| Bool
otherwise = (a
c, c
d0, c
d1')
where
!d1' :: c
d1' = c -> c -> c
forall a. Ord a => a -> a -> a
max (c -> c -> c
forall a. Ord a => a -> a -> a
min c
d1 c
d) c
d0
pointDist :: Hash -> Hash -> (Hash, a)
pointDist !Hash
xi !Hash
yi =
let !px :: a
px = Hash -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Hash
xi a -> a -> a
forall a. Num a => a -> a -> a
- a
x
!py :: a
py = Hash -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Hash
yi a -> a -> a
forall a. Num a => a -> a -> a
- a
y
!h :: Hash
h = Seed -> Hash -> Hash -> Hash
hash2 Seed
seed (Hash
primeX Hash -> Hash -> Hash
forall a. Num a => a -> a -> a
* Hash
xi) (Hash
primeY Hash -> Hash -> Hash
forall a. Num a => a -> a -> a
* Hash
yi)
!i :: Hash
i = Hash
h Hash -> Hash -> Hash
forall a. Bits a => a -> a -> a
.&. Hash
510
!rvx :: Float
rvx = Vector Float
randVecs2d Vector Float -> Int -> Float
forall a. Unbox a => Vector a -> Int -> a
`U.unsafeIndex` Hash -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Hash
i
!rvy :: Float
rvy = Vector Float
randVecs2d Vector Float -> Int -> Float
forall a. Unbox a => Vector a -> Int -> a
`U.unsafeIndex` (Hash -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Hash
i Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. Int
1)
!d :: a
d = a -> a -> a
dist (a
px a -> a -> a
forall a. Num a => a -> a -> a
+ Float -> a
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rvx a -> a -> a
forall a. Num a => a -> a -> a
* a
jitter) (a
py a -> a -> a
forall a. Num a => a -> a -> a
+ Float -> a
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rvy a -> a -> a
forall a. Num a => a -> a -> a
* a
jitter)
in (Hash
h, a
d)
{-# INLINE noise2BaseWith #-}
randVecs2d :: U.Vector Float
randVecs2d :: Vector Float
randVecs2d =
[-Float
0.2700222198,-Float
0.9628540911,Float
Item (Vector Float)
0.3863092627,-Float
0.9223693152,Float
Item (Vector Float)
0.04444859006,-Float
0.999011673,-Float
0.5992523158,-Float
0.8005602176
,-Float
0.7819280288,Float
Item (Vector Float)
0.6233687174,Float
Item (Vector Float)
0.9464672271,Float
Item (Vector Float)
0.3227999196,-Float
0.6514146797,-Float
0.7587218957,Float
Item (Vector Float)
0.9378472289,Float
Item (Vector Float)
0.347048376
,-Float
0.8497875957,-Float
0.5271252623,-Float
0.879042592,Float
Item (Vector Float)
0.4767432447,-Float
0.892300288,-Float
0.4514423508,-Float
0.379844434,-Float
0.9250503802
,-Float
0.9951650832,Float
Item (Vector Float)
0.0982163789,Float
Item (Vector Float)
0.7724397808,-Float
0.6350880136,Float
Item (Vector Float)
0.7573283322,-Float
0.6530343002,-Float
0.9928004525,-Float
0.119780055
,-Float
0.0532665713,Float
Item (Vector Float)
0.9985803285,Float
Item (Vector Float)
0.9754253726,-Float
0.2203300762,-Float
0.7665018163,Float
Item (Vector Float)
0.6422421394,Float
Item (Vector Float)
0.991636706,Float
Item (Vector Float)
0.1290606184
,-Float
0.994696838,Float
Item (Vector Float)
0.1028503788,-Float
0.5379205513,-Float
0.84299554,Float
Item (Vector Float)
0.5022815471,-Float
0.8647041387,Float
Item (Vector Float)
0.4559821461,-Float
0.8899889226
,-Float
0.8659131224,-Float
0.5001944266,Float
Item (Vector Float)
0.0879458407,-Float
0.9961252577,-Float
0.5051684983,Float
Item (Vector Float)
0.8630207346,Float
Item (Vector Float)
0.7753185226,-Float
0.6315704146
,-Float
0.6921944612,Float
Item (Vector Float)
0.7217110418,-Float
0.5191659449,-Float
0.8546734591,Float
Item (Vector Float)
0.8978622882,-Float
0.4402764035,-Float
0.1706774107,Float
Item (Vector Float)
0.9853269617
,-Float
0.9353430106,-Float
0.3537420705,-Float
0.9992404798,Float
Item (Vector Float)
0.03896746794,-Float
0.2882064021,-Float
0.9575683108,-Float
0.9663811329,Float
Item (Vector Float)
0.2571137995
,-Float
0.8759714238,-Float
0.4823630009,-Float
0.8303123018,-Float
0.5572983775,Float
Item (Vector Float)
0.05110133755,-Float
0.9986934731,-Float
0.8558373281,-Float
0.5172450752
,Float
Item (Vector Float)
0.09887025282,Float
Item (Vector Float)
0.9951003332,Float
Item (Vector Float)
0.9189016087,Float
Item (Vector Float)
0.3944867976,-Float
0.2439375892,-Float
0.9697909324,-Float
0.8121409387,-Float
0.5834613061
,-Float
0.9910431363,Float
Item (Vector Float)
0.1335421355,Float
Item (Vector Float)
0.8492423985,-Float
0.5280031709,-Float
0.9717838994,-Float
0.2358729591,Float
Item (Vector Float)
0.9949457207,Float
Item (Vector Float)
0.1004142068
,Float
Item (Vector Float)
0.6241065508,-Float
0.7813392434,Float
Item (Vector Float)
0.662910307,Float
Item (Vector Float)
0.7486988212,-Float
0.7197418176,Float
Item (Vector Float)
0.6942418282,-Float
0.8143370775,-Float
0.5803922158
,Float
Item (Vector Float)
0.104521054,-Float
0.9945226741,-Float
0.1065926113,-Float
0.9943027784,Float
Item (Vector Float)
0.445799684,-Float
0.8951327509,Float
Item (Vector Float)
0.105547406,Float
Item (Vector Float)
0.9944142724
,-Float
0.992790267,Float
Item (Vector Float)
0.1198644477,-Float
0.8334366408,Float
Item (Vector Float)
0.552615025,Float
Item (Vector Float)
0.9115561563,-Float
0.4111755999,Float
Item (Vector Float)
0.8285544909,-Float
0.5599084351
,Float
Item (Vector Float)
0.7217097654,-Float
0.6921957921,Float
Item (Vector Float)
0.4940492677,-Float
0.8694339084,-Float
0.3652321272,-Float
0.9309164803,-Float
0.9696606758,Float
Item (Vector Float)
0.2444548501
,Float
Item (Vector Float)
0.08925509731,-Float
0.996008799,Float
Item (Vector Float)
0.5354071276,-Float
0.8445941083,-Float
0.1053576186,Float
Item (Vector Float)
0.9944343981,-Float
0.9890284586,Float
Item (Vector Float)
0.1477251101
,Float
Item (Vector Float)
0.004856104961,Float
Item (Vector Float)
0.9999882091,Float
Item (Vector Float)
0.9885598478,Float
Item (Vector Float)
0.1508291331,Float
Item (Vector Float)
0.9286129562,-Float
0.3710498316,-Float
0.5832393863,-Float
0.8123003252
,Float
Item (Vector Float)
0.3015207509,Float
Item (Vector Float)
0.9534596146,-Float
0.9575110528,Float
Item (Vector Float)
0.2883965738,Float
Item (Vector Float)
0.9715802154,-Float
0.2367105511,Float
Item (Vector Float)
0.229981792,Float
Item (Vector Float)
0.9731949318
,Float
Item (Vector Float)
0.955763816,-Float
0.2941352207,Float
Item (Vector Float)
0.740956116,Float
Item (Vector Float)
0.6715534485,-Float
0.9971513787,-Float
0.07542630764,Float
Item (Vector Float)
0.6905710663,-Float
0.7232645452
,-Float
0.290713703,-Float
0.9568100872,Float
Item (Vector Float)
0.5912777791,-Float
0.8064679708,-Float
0.9454592212,-Float
0.325740481,Float
Item (Vector Float)
0.6664455681,Float
Item (Vector Float)
0.74555369
,Float
Item (Vector Float)
0.6236134912,Float
Item (Vector Float)
0.7817328275,Float
Item (Vector Float)
0.9126993851,-Float
0.4086316587,-Float
0.8191762011,Float
Item (Vector Float)
0.5735419353,-Float
0.8812745759,-Float
0.4726046147
,Float
Item (Vector Float)
0.9953313627,Float
Item (Vector Float)
0.09651672651,Float
Item (Vector Float)
0.9855650846,-Float
0.1692969699,-Float
0.8495980887,Float
Item (Vector Float)
0.5274306472,Float
Item (Vector Float)
0.6174853946,-Float
0.7865823463
,Float
Item (Vector Float)
0.8508156371,Float
Item (Vector Float)
0.52546432,Float
Item (Vector Float)
0.9985032451,-Float
0.05469249926,Float
Item (Vector Float)
0.1971371563,-Float
0.9803759185,Float
Item (Vector Float)
0.6607855748,-Float
0.7505747292
,-Float
0.03097494063,Float
Item (Vector Float)
0.9995201614,-Float
0.6731660801,Float
Item (Vector Float)
0.739491331,-Float
0.7195018362,-Float
0.6944905383,Float
Item (Vector Float)
0.9727511689,Float
Item (Vector Float)
0.2318515979
,Float
Item (Vector Float)
0.9997059088,-Float
0.0242506907,Float
Item (Vector Float)
0.4421787429,-Float
0.8969269532,Float
Item (Vector Float)
0.9981350961,-Float
0.061043673,-Float
0.9173660799,-Float
0.3980445648
,-Float
0.8150056635,-Float
0.5794529907,-Float
0.8789331304,Float
Item (Vector Float)
0.4769450202,Float
Item (Vector Float)
0.0158605829,Float
Item (Vector Float)
0.999874213,-Float
0.8095464474,Float
Item (Vector Float)
0.5870558317
,-Float
0.9165898907,-Float
0.3998286786,-Float
0.8023542565,Float
Item (Vector Float)
0.5968480938,-Float
0.5176737917,Float
Item (Vector Float)
0.8555780767,-Float
0.8154407307,-Float
0.5788405779
,Float
Item (Vector Float)
0.4022010347,-Float
0.9155513791,-Float
0.9052556868,-Float
0.4248672045,Float
Item (Vector Float)
0.7317445619,Float
Item (Vector Float)
0.6815789728,-Float
0.5647632201,-Float
0.8252529947
,-Float
0.8403276335,-Float
0.5420788397,-Float
0.9314281527,Float
Item (Vector Float)
0.363925262,Float
Item (Vector Float)
0.5238198472,Float
Item (Vector Float)
0.8518290719,Float
Item (Vector Float)
0.7432803869,-Float
0.6689800195
,-Float
0.985371561,-Float
0.1704197369,Float
Item (Vector Float)
0.4601468731,Float
Item (Vector Float)
0.88784281,Float
Item (Vector Float)
0.825855404,Float
Item (Vector Float)
0.5638819483,Float
Item (Vector Float)
0.6182366099,Float
Item (Vector Float)
0.7859920446
,Float
Item (Vector Float)
0.8331502863,-Float
0.553046653,Float
Item (Vector Float)
0.1500307506,Float
Item (Vector Float)
0.9886813308,-Float
0.662330369,-Float
0.7492119075,-Float
0.668598664,Float
Item (Vector Float)
0.743623444
,Float
Item (Vector Float)
0.7025606278,Float
Item (Vector Float)
0.7116238924,-Float
0.5419389763,-Float
0.8404178401,-Float
0.3388616456,Float
Item (Vector Float)
0.9408362159,Float
Item (Vector Float)
0.8331530315,Float
Item (Vector Float)
0.5530425174
,-Float
0.2989720662,-Float
0.9542618632,Float
Item (Vector Float)
0.2638522993,Float
Item (Vector Float)
0.9645630949,Float
Item (Vector Float)
0.124108739,-Float
0.9922686234,-Float
0.7282649308,-Float
0.6852956957
,Float
Item (Vector Float)
0.6962500149,Float
Item (Vector Float)
0.7177993569,-Float
0.9183535368,Float
Item (Vector Float)
0.3957610156,-Float
0.6326102274,-Float
0.7744703352,-Float
0.9331891859,-Float
0.359385508
,-Float
0.1153779357,-Float
0.9933216659,Float
Item (Vector Float)
0.9514974788,-Float
0.3076565421,-Float
0.08987977445,-Float
0.9959526224,Float
Item (Vector Float)
0.6678496916,Float
Item (Vector Float)
0.7442961705
,Float
Item (Vector Float)
0.7952400393,-Float
0.6062947138,-Float
0.6462007402,-Float
0.7631674805,-Float
0.2733598753,Float
Item (Vector Float)
0.9619118351,Float
Item (Vector Float)
0.9669590226,-Float
0.254931851
,-Float
0.9792894595,Float
Item (Vector Float)
0.2024651934,-Float
0.5369502995,-Float
0.8436138784,-Float
0.270036471,-Float
0.9628500944,-Float
0.6400277131,Float
Item (Vector Float)
0.7683518247
,-Float
0.7854537493,-Float
0.6189203566,Float
Item (Vector Float)
0.06005905383,-Float
0.9981948257,-Float
0.02455770378,Float
Item (Vector Float)
0.9996984141,-Float
0.65983623,Float
Item (Vector Float)
0.751409442
,-Float
0.6253894466,-Float
0.7803127835,-Float
0.6210408851,-Float
0.7837781695,Float
Item (Vector Float)
0.8348888491,Float
Item (Vector Float)
0.5504185768,-Float
0.1592275245,Float
Item (Vector Float)
0.9872419133
,Float
Item (Vector Float)
0.8367622488,Float
Item (Vector Float)
0.5475663786,-Float
0.8675753916,-Float
0.4973056806,-Float
0.2022662628,-Float
0.9793305667,Float
Item (Vector Float)
0.9399189937,Float
Item (Vector Float)
0.3413975472
,Float
Item (Vector Float)
0.9877404807,-Float
0.1561049093,-Float
0.9034455656,Float
Item (Vector Float)
0.4287028224,Float
Item (Vector Float)
0.1269804218,-Float
0.9919052235,-Float
0.3819600854,Float
Item (Vector Float)
0.924178821
,Float
Item (Vector Float)
0.9754625894,Float
Item (Vector Float)
0.2201652486,-Float
0.3204015856,-Float
0.9472818081,-Float
0.9874760884,Float
Item (Vector Float)
0.1577687387,Float
Item (Vector Float)
0.02535348474,-Float
0.9996785487
,Float
Item (Vector Float)
0.4835130794,-Float
0.8753371362,-Float
0.2850799925,-Float
0.9585037287,-Float
0.06805516006,-Float
0.99768156,-Float
0.7885244045,-Float
0.6150034663
,Float
Item (Vector Float)
0.3185392127,-Float
0.9479096845,Float
Item (Vector Float)
0.8880043089,Float
Item (Vector Float)
0.4598351306,Float
Item (Vector Float)
0.6476921488,-Float
0.7619021462,Float
Item (Vector Float)
0.9820241299,Float
Item (Vector Float)
0.1887554194
,Float
Item (Vector Float)
0.9357275128,-Float
0.3527237187,-Float
0.8894895414,Float
Item (Vector Float)
0.4569555293,Float
Item (Vector Float)
0.7922791302,Float
Item (Vector Float)
0.6101588153,Float
Item (Vector Float)
0.7483818261,Float
Item (Vector Float)
0.6632681526
,-Float
0.7288929755,-Float
0.6846276581,Float
Item (Vector Float)
0.8729032783,-Float
0.4878932944,Float
Item (Vector Float)
0.8288345784,Float
Item (Vector Float)
0.5594937369,Float
Item (Vector Float)
0.08074567077,Float
Item (Vector Float)
0.9967347374
,Float
Item (Vector Float)
0.9799148216,-Float
0.1994165048,-Float
0.580730673,-Float
0.8140957471,-Float
0.4700049791,-Float
0.8826637636,Float
Item (Vector Float)
0.2409492979,Float
Item (Vector Float)
0.9705377045
,Float
Item (Vector Float)
0.9437816757,-Float
0.3305694308,-Float
0.8927998638,-Float
0.4504535528,-Float
0.8069622304,Float
Item (Vector Float)
0.5906030467,Float
Item (Vector Float)
0.06258973166,Float
Item (Vector Float)
0.9980393407
,-Float
0.9312597469,Float
Item (Vector Float)
0.3643559849,Float
Item (Vector Float)
0.5777449785,Float
Item (Vector Float)
0.8162173362,-Float
0.3360095855,-Float
0.941858566,Float
Item (Vector Float)
0.697932075,-Float
0.7161639607
,-Float
0.002008157227,-Float
0.9999979837,-Float
0.1827294312,-Float
0.9831632392,-Float
0.6523911722,Float
Item (Vector Float)
0.7578824173,-Float
0.4302626911,-Float
0.9027037258
,-Float
0.9985126289,-Float
0.05452091251,-Float
0.01028102172,-Float
0.9999471489,-Float
0.4946071129,Float
Item (Vector Float)
0.8691166802,-Float
0.2999350194,Float
Item (Vector Float)
0.9539596344
,Float
Item (Vector Float)
0.8165471961,Float
Item (Vector Float)
0.5772786819,Float
Item (Vector Float)
0.2697460475,Float
Item (Vector Float)
0.962931498,-Float
0.7306287391,-Float
0.6827749597,-Float
0.7590952064,-Float
0.6509796216
,-Float
0.907053853,Float
Item (Vector Float)
0.4210146171,-Float
0.5104861064,-Float
0.8598860013,Float
Item (Vector Float)
0.8613350597,Float
Item (Vector Float)
0.5080373165,Float
Item (Vector Float)
0.5007881595,-Float
0.8655698812
,-Float
0.654158152,Float
Item (Vector Float)
0.7563577938,-Float
0.8382755311,-Float
0.545246856,Float
Item (Vector Float)
0.6940070834,Float
Item (Vector Float)
0.7199681717,Float
Item (Vector Float)
0.06950936031,Float
Item (Vector Float)
0.9975812994
,Float
Item (Vector Float)
0.1702942185,-Float
0.9853932612,Float
Item (Vector Float)
0.2695973274,Float
Item (Vector Float)
0.9629731466,Float
Item (Vector Float)
0.5519612192,-Float
0.8338697815,Float
Item (Vector Float)
0.225657487,-Float
0.9742067022
,Float
Item (Vector Float)
0.4215262855,-Float
0.9068161835,Float
Item (Vector Float)
0.4881873305,-Float
0.8727388672,-Float
0.3683854996,-Float
0.9296731273,-Float
0.9825390578,Float
Item (Vector Float)
0.1860564427
,Float
Item (Vector Float)
0.81256471,Float
Item (Vector Float)
0.5828709909,Float
Item (Vector Float)
0.3196460933,-Float
0.9475370046,Float
Item (Vector Float)
0.9570913859,Float
Item (Vector Float)
0.2897862643,-Float
0.6876655497,-Float
0.7260276109
,-Float
0.9988770922,-Float
0.047376731,-Float
0.1250179027,Float
Item (Vector Float)
0.992154486,-Float
0.8280133617,Float
Item (Vector Float)
0.560708367,Float
Item (Vector Float)
0.9324863769,-Float
0.3612051451
,Float
Item (Vector Float)
0.6394653183,Float
Item (Vector Float)
0.7688199442,-Float
0.01623847064,-Float
0.9998681473,-Float
0.9955014666,-Float
0.09474613458,-Float
0.81453315,Float
Item (Vector Float)
0.580117012
,Float
Item (Vector Float)
0.4037327978,-Float
0.9148769469,Float
Item (Vector Float)
0.9944263371,Float
Item (Vector Float)
0.1054336766,-Float
0.1624711654,Float
Item (Vector Float)
0.9867132919,-Float
0.9949487814,-Float
0.100383875
,-Float
0.6995302564,Float
Item (Vector Float)
0.7146029809,Float
Item (Vector Float)
0.5263414922,-Float
0.85027327,-Float
0.5395221479,Float
Item (Vector Float)
0.841971408,Float
Item (Vector Float)
0.6579370318,Float
Item (Vector Float)
0.7530729462
,Float
Item (Vector Float)
0.01426758847,-Float
0.9998982128,-Float
0.6734383991,Float
Item (Vector Float)
0.7392433447,Float
Item (Vector Float)
0.639412098,-Float
0.7688642071,Float
Item (Vector Float)
0.9211571421,Float
Item (Vector Float)
0.3891908523
,-Float
0.146637214,-Float
0.9891903394,-Float
0.782318098,Float
Item (Vector Float)
0.6228791163,-Float
0.5039610839,-Float
0.8637263605,-Float
0.7743120191,-Float
0.6328039957
]