Skip to content

Commit 7b41fae

Browse files
committed
"volumes"
1 parent 31e488d commit 7b41fae

File tree

6 files changed

+73
-2
lines changed

6 files changed

+73
-2
lines changed

.gitignore

+2
Original file line numberDiff line numberDiff line change
@@ -2,3 +2,5 @@
22
.stack-work/
33
dist/
44
tags
5+
src/highlight.js
6+
src/style.css

neural.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,7 @@ library
6767
, Data.Utils.Statistics
6868
, Data.Utils.Traversable
6969
, Data.Utils.Vector
70+
, Data.Utils.Volume
7071
other-modules:
7172
ghc-options: -Wall -fexcess-precision -optc-O3 -optc-ffast-math
7273
build-depends: base >= 4.7 && < 5

src/Data/Utils.hs

+2
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ module Data.Utils
2323
, module Data.Utils.Statistics
2424
, module Data.Utils.Traversable
2525
, module Data.Utils.Vector
26+
, module Data.Utils.Volume
2627
) where
2728

2829
import Data.Utils.Analytic
@@ -35,3 +36,4 @@ import Data.Utils.Stack
3536
import Data.Utils.Statistics
3637
import Data.Utils.Traversable
3738
import Data.Utils.Vector
39+
import Data.Utils.Volume

src/Data/Utils/Matrix.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ row (Matrix rows) = (rows !?)
8282
column :: Matrix m n a -> Int -> Maybe (Vector m a)
8383
column (Matrix rows) j = sequenceA $ (!? j) <$> rows
8484

85-
-- | Generates a matrix by applying the given function to each index (row, column).
85+
-- | Generates a 'Matrix' by applying the given function to each index (row, column).
8686
--
8787
-- >>> :set -XDataKinds
8888
-- >>> mgenerate id :: Matrix 3 2 (Int, Int)

src/Data/Utils/Vector.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,7 @@ nil = Vector V.empty
109109
cons :: forall a n. a -> Vector n a -> Vector (n + 1) a
110110
cons x (Vector xs) = withNatOp (%+) (Proxy :: Proxy n) (Proxy :: Proxy 1) $ Vector $ V.cons x xs
111111

112-
-- | Generates a vector by applying the given function to each index.
112+
-- | Generates a 'Vector' by applying the given function to each index.
113113
--
114114
-- >>> :set -XDataKinds
115115
-- >>> generate id :: Vector 3 Int

src/Data/Utils/Volume.hs

+66
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
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

Comments
 (0)