]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Linear/Vector.hs
Add Vec1, Vec4, Vec5 aliases.
[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 N5,
18 S,
19 Vector(..),
20 construct,
21 fromList,
22 inspect,
23 toList,
24 )
25 import qualified Data.Vector.Fixed as V (
26 length,
27 )
28 import Data.Vector.Fixed.Boxed
29
30 type Vec1 = Vec N1
31 type Vec4 = Vec N4
32 type Vec5 = Vec N5
33
34 -- * Low-dimension vector wrappers.
35 --
36 -- These wrappers are instances of 'Vector', so they inherit all of
37 -- the userful instances defined above. But, they use fixed
38 -- constructors, so you can pattern match out the individual
39 -- components.
40
41 data D1 a = D1 a deriving (Show, Eq)
42 type instance Dim D1 = N1
43 instance Vector D1 a where
44 inspect (D1 x) (Fun f) = f x
45 construct = Fun D1
46
47 data D2 a = D2 a a deriving (Show, Eq)
48 type instance Dim D2 = N2
49 instance Vector D2 a where
50 inspect (D2 x y) (Fun f) = f x y
51 construct = Fun D2
52
53 data D3 a = D3 a a a deriving (Show, Eq)
54 type instance Dim D3 = N3
55 instance Vector D3 a where
56 inspect (D3 x y z) (Fun f) = f x y z
57 construct = Fun D3
58
59 data D4 a = D4 a a a a deriving (Show, Eq)
60 type instance Dim D4 = N4
61 instance Vector D4 a where
62 inspect (D4 w x y z) (Fun f) = f w x y z
63 construct = Fun D4
64
65
66 -- | Unsafe indexing.
67 --
68 -- Examples:
69 --
70 -- >>> let v1 = D2 1 2
71 -- >>> v1 ! 1
72 -- 2
73 --
74 (!) :: (Vector v a) => v a -> Int -> a
75 (!) v1 idx = (toList v1) !! idx
76
77 -- | Safe indexing.
78 --
79 -- Examples:
80 --
81 -- >>> let v1 = D3 1 2 3
82 -- >>> v1 !? 2
83 -- Just 3
84 -- >>> v1 !? 3
85 -- Nothing
86 --
87 (!?) :: (Vector v a) => v a -> Int -> Maybe a
88 (!?) v1 idx
89 | idx < 0 || idx >= V.length v1 = Nothing
90 | otherwise = Just $ v1 ! idx
91
92
93 -- | Remove an element of the given vector.
94 --
95 -- Examples:
96 --
97 -- >>> let b = D3 1 2 3
98 -- >>> delete b 1 :: D2 Int
99 -- D2 1 3
100 --
101 delete :: (Vector v a, Vector w a, Dim v ~ S (Dim w)) => v a -> Int -> w a
102 delete v1 idx =
103 fromList $ (lhalf ++ rhalf')
104 where
105 (lhalf, rhalf) = splitAt idx (toList v1)
106 rhalf' = tail rhalf