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