|
| 1 | +{-# OPTIONS_HADDOCK show-extensions #-} |
| 2 | + |
| 3 | +{-# LANGUAGE DataKinds #-} |
| 4 | +{-# LANGUAGE KindSignatures #-} |
| 5 | +{-# LANGUAGE DeriveFunctor #-} |
| 6 | +{-# LANGUAGE DeriveFoldable #-} |
| 7 | +{-# LANGUAGE DeriveTraversable #-} |
| 8 | +{-# LANGUAGE TypeOperators #-} |
| 9 | +{-# LANGUAGE TypeFamilies #-} |
| 10 | +{-# LANGUAGE GeneralizedNewtypeDeriving #-} |
| 11 | + |
| 12 | +{-| |
| 13 | +Module : Data.Utils.Volume |
| 14 | +Description : fixed-size volumes |
| 15 | +Copyright : (c) Lars Brünjes, 2016 |
| 16 | +License : MIT |
| 17 | +Maintainer : brunjlar@gmail.com |
| 18 | +Stability : experimental |
| 19 | +Portability : portable |
| 20 | +
|
| 21 | +This module defines fixed-size /volumes/ and some basic typeclass instances and operations for them. |
| 22 | +A 'Volume' is a 'Matrix' with 'Vector' entries, i.e. a three-dimensional array. |
| 23 | +-} |
| 24 | + |
| 25 | +module Data.Utils.Volume |
| 26 | + ( Volume(..) |
| 27 | + , slice |
| 28 | + , vgenerate |
| 29 | + ) where |
| 30 | + |
| 31 | +import GHC.TypeLits |
| 32 | +import Data.MyPrelude |
| 33 | +import Data.Utils.Matrix |
| 34 | +import Data.Utils.Vector |
| 35 | + |
| 36 | +-- | @'Volume' m n d a@ is the type of /volumes/ with @m@ rows, @n@ columns, depth @d@ and entries of type @a@. |
| 37 | +-- |
| 38 | +newtype Volume (m :: Nat) (n :: Nat) (d :: Nat) a = Volume (Matrix m n (Vector d a)) |
| 39 | + deriving (Eq, Show, Functor, Foldable, Traversable, NFData) |
| 40 | + |
| 41 | +instance (KnownNat m, KnownNat n, KnownNat d) => Applicative (Volume m n d) where |
| 42 | + |
| 43 | + pure x = Volume $ pure (pure x) |
| 44 | + |
| 45 | + Volume fs <*> Volume xs = Volume $ (<*>) <$> fs <*> xs |
| 46 | + |
| 47 | +-- | @'slice' v i@ gives the matrix "at depth @i@" of volume @v@ (or 'Nothing' if @i@ is invalid). |
| 48 | +-- |
| 49 | +-- >>> :set -XDataKinds |
| 50 | +-- >>> slice (pure True :: Volume 2 2 3 Bool) 2 |
| 51 | +-- Just (Matrix [[True,True],[True,True]]) |
| 52 | +-- |
| 53 | +-- >>> slice (pure True :: Volume 2 2 3 Bool) 3 |
| 54 | +-- Nothing |
| 55 | +-- |
| 56 | +slice :: Volume m n d a -> Int -> Maybe (Matrix m n a) |
| 57 | +slice (Volume m) i = sequenceA $ (!? i) <$> m |
| 58 | + |
| 59 | +-- | Generates a 'Volume' by applying the given function to each index (row, column, slice). |
| 60 | +-- |
| 61 | +-- >>> :set -XDataKinds |
| 62 | +-- >>> vgenerate id :: Volume 1 2 3 (Int, Int, Int) |
| 63 | +-- Volume (Matrix [[[(0,0,0),(0,0,1),(0,0,2)],[(0,1,0),(0,1,1),(0,1,2)]]]) |
| 64 | +-- |
| 65 | +vgenerate :: (KnownNat m, KnownNat n, KnownNat d) => ((Int, Int, Int) -> a) -> Volume m n d a |
| 66 | +vgenerate f = Volume $ mgenerate (\(i, j) -> generate (\k -> f (i, j, k))) |
0 commit comments