]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Linear/Vector.hs
aba9e5fb2d28d3d5ae43665ca95353f3cc8b6fd5
[numerical-analysis.git] / src / Linear / Vector.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TypeFamilies #-}
6
7 module Linear.Vector
8 where
9
10 import Data.Vector.Fixed (
11 Dim,
12 Fun(..),
13 N1,
14 N2,
15 N3,
16 N4,
17 Vector(..),
18 construct,
19 inspect,
20 toList,
21 )
22 import qualified Data.Vector.Fixed as V (
23 length,
24 )
25
26
27 -- * Low-dimension vector wrappers.
28 --
29 -- These wrappers are instances of 'Vector', so they inherit all of
30 -- the userful instances defined above. But, they use fixed
31 -- constructors, so you can pattern match out the individual
32 -- components.
33
34 data D1 a = D1 a
35 type instance Dim D1 = N1
36 instance Vector D1 a where
37 inspect (D1 x) (Fun f) = f x
38 construct = Fun D1
39
40 data D2 a = D2 a a
41 type instance Dim D2 = N2
42 instance Vector D2 a where
43 inspect (D2 x y) (Fun f) = f x y
44 construct = Fun D2
45
46 data D3 a = D3 a a a
47 type instance Dim D3 = N3
48 instance Vector D3 a where
49 inspect (D3 x y z) (Fun f) = f x y z
50 construct = Fun D3
51
52 data D4 a = D4 a a a a
53 type instance Dim D4 = N4
54 instance Vector D4 a where
55 inspect (D4 w x y z) (Fun f) = f w x y z
56 construct = Fun D4
57
58
59 -- | Unsafe indexing.
60 --
61 -- Examples:
62 --
63 -- >>> let v1 = D2 1 2
64 -- >>> v1 ! 1
65 -- 2
66 --
67 (!) :: (Vector v a) => v a -> Int -> a
68 (!) v1 idx = (toList v1) !! idx
69
70 -- | Safe indexing.
71 --
72 -- Examples:
73 --
74 -- >>> let v1 = D3 1 2 3
75 -- >>> v1 !? 2
76 -- Just 3
77 -- >>> v1 !? 3
78 -- Nothing
79 --
80 (!?) :: (Vector v a) => v a -> Int -> Maybe a
81 (!?) v1 idx
82 | idx < 0 || idx >= V.length v1 = Nothing
83 | otherwise = Just $ v1 ! idx