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