]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Linear/Vector.hs
aa1568bec6c2ff3b8ed0baa724177349fb04e3bb
[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 N1,
13 N4,
14 N5,
15 S,
16 Vector(..),
17 fromList,
18 toList,
19 )
20 import qualified Data.Vector.Fixed as V (
21 length,
22 )
23 import Data.Vector.Fixed.Boxed
24
25 type Vec1 = Vec N1
26 type Vec4 = Vec N4
27 type Vec5 = Vec N5
28
29
30 -- | Unsafe indexing.
31 --
32 -- Examples:
33 --
34 -- >>> import Data.Vector.Fixed (mk2)
35 -- >>> let v1 = mk2 1 2 :: Vec2 Int
36 -- >>> v1 ! 1
37 -- 2
38 --
39 (!) :: (Vector v a) => v a -> Int -> a
40 (!) v1 idx = (toList v1) !! idx
41
42 -- | Safe indexing.
43 --
44 -- Examples:
45 --
46 -- >>> import Data.Vector.Fixed (mk3)
47 -- >>> let v1 = mk3 1 2 3 :: Vec3 Int
48 -- >>> v1 !? 2
49 -- Just 3
50 -- >>> v1 !? 3
51 -- Nothing
52 --
53 (!?) :: (Vector v a) => v a -> Int -> Maybe a
54 (!?) v1 idx
55 | idx < 0 || idx >= V.length v1 = Nothing
56 | otherwise = Just $ v1 ! idx
57
58
59 -- | Remove an element of the given vector.
60 --
61 -- Examples:
62 --
63 -- >>> import Data.Vector.Fixed (mk3)
64 -- >>> let b = mk3 1 2 3 :: Vec3 Int
65 -- >>> delete b 1 :: Vec2 Int
66 -- fromList [1,3]
67 --
68 delete :: (Vector v a, Vector w a, Dim v ~ S (Dim w)) => v a -> Int -> w a
69 delete v1 idx =
70 fromList $ (lhalf ++ rhalf')
71 where
72 (lhalf, rhalf) = splitAt idx (toList v1)
73 rhalf' = tail rhalf