Skip to content

Instantly share code, notes, and snippets.

@acowley
Created September 30, 2013 19:39
Show Gist options
  • Save acowley/6769022 to your computer and use it in GitHub Desktop.
Save acowley/6769022 to your computer and use it in GitHub Desktop.
Image indexing for 2D or 3D images of various color depths.
{-# LANGUAGE TypeFamilies, DataKinds, ScopedTypeVariables,
MultiParamTypeClasses, TemplateHaskell, GADTs,
FlexibleContexts #-}
import Data.Proxy
import Data.Singletons
import qualified Data.Foldable as F
import Linear (V2(..), V3(..))
data Mat (d::Dimension) (c::Channel) e
data Channel = RGB | BGR | Grayscale | HSV | YUV
data Dimension = TwoD | ThreeD
genSingletons [''Channel]
numChannels' :: Channel -> Int
numChannels' Grayscale = 1
numChannels' _ = 3
numChannels :: forall c. SingI c => Proxy (c::Channel) -> Int
numChannels _ = numChannels' . fromSing $ (sing::Sing c)
type family IndexType (d::Dimension) :: * -> *
type instance IndexType TwoD = V2
type instance IndexType ThreeD = V3
type family Elem (c::Channel) e :: *
type instance Elem c e = Int -- for testing
rawArrayLookup :: Mat d c e -> Int -> Elem c e
rawArrayLookup _ i = i
-- Note: You need to compute offsets using actual image stride, not a
-- product of indices.
index :: forall d c e. (SingI c, F.Foldable (IndexType d))
=> Mat d c e -> IndexType d Int -> Elem c e
index m i = rawArrayLookup m (F.product i * nc)
where nc = numChannels (Proxy::Proxy c)
main :: IO ()
main = do putStrLn "Looking at pixel (2,3)"
print $ index (undefined::Mat TwoD RGB Float) (V2 2 3)
putStrLn "Lookint at pixel (2,2,2)"
print $ index (undefined::Mat ThreeD Grayscale Int) (V3 2 2 2)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment