Skip to content

Instantly share code, notes, and snippets.

@5outh
Last active May 8, 2018 23:22
Show Gist options
  • Select an option

  • Save 5outh/152034006a231d4ead03f95be6335d34 to your computer and use it in GitHub Desktop.

Select an option

Save 5outh/152034006a231d4ead03f95be6335d34 to your computer and use it in GitHub Desktop.
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Space2d where
import Algorithms.VectorMath
import Data.List
import qualified Data.Map.Strict as M
import Data.Maybe
import Linear.V2
data Space2d a = Space2d
{ spaceSize :: Rational
, getSpace2d :: M.Map (V2 Rational) a
} deriving (Functor)
fromList :: Rational -> [(V2 Rational, a)] -> Space2d a
fromList size = Space2d size . M.fromList
-- | Shim so we don't have to redefine all of the Map operations
liftMap :: (M.Map (V2 Rational) a -> M.Map (V2 Rational) a) -> Space2d a -> Space2d a
liftMap f (Space2d size m) = Space2d size (f m)
neighborIndices :: V2 Rational -> Space2d a -> [V2 Rational]
neighborIndices v (Space2d size _) =
[ v + V2 0 (-size)
, v + V2 0 size
, v + V2 size (-size)
, v + V2 size 0
, v + V2 size size
, v + V2 (-size) (-size)
, v + V2 (-size) 0
, v + V2 (-size) size
]
average :: (Num a, Fractional a) => [a] -> a
average xs = sum xs / genericLength xs
smoothSpace2d :: (Num a, Fractional a) => Space2d a -> Space2d a
smoothSpace2d = spaceFilter average
spaceFilter :: ([a] -> a) -> Space2d a -> Space2d a
spaceFilter f space = liftMap (M.mapWithKey smooth) space
where
smooth k v = f $ mapMaybe (`M.lookup` getSpace2d space) (neighborIndices k space)
nearestMultipleOf :: Rational -> Rational -> Rational
nearestMultipleOf size n = fromIntegral (round (n / size)) * size
@buggymcbugfix
Copy link

I am curious—what does this output?

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment