]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Linear/Vector.hs
src/Linear/Vector.hs: add a Vec0 type.
[numerical-analysis.git] / src / Linear / Vector.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE NoImplicitPrelude #-}
5 {-# LANGUAGE NoMonomorphismRestriction #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
7 {-# LANGUAGE TypeFamilies #-}
8
9 module Linear.Vector (
10 module Data.Vector.Fixed.Boxed,
11 Vec0,
12 Vec1,
13 (!?),
14 delete,
15 element_sum )
16 where
17
18 import qualified Algebra.Additive as Additive ( C )
19 import qualified Algebra.Ring as Ring ( C )
20 import Data.Vector.Fixed (
21 Dim,
22 N1,
23 S,
24 Vector(..),
25 Z,
26 fromList,
27 toList )
28 import Data.Vector.Fixed (
29 (!),
30 foldl,
31 length )
32 import Data.Vector.Fixed.Boxed (
33 Vec,
34 Vec2,
35 Vec3,
36 Vec4,
37 Vec5 )
38 import NumericPrelude hiding ( abs, length, foldl )
39
40 type Vec0 = Vec Z
41 type Vec1 = Vec N1
42
43
44
45 -- | Safe indexing.
46 --
47 -- Examples:
48 --
49 -- >>> import Data.Vector.Fixed (mk3)
50 -- >>> let v1 = mk3 1 2 3 :: Vec3 Int
51 -- >>> v1 !? 2
52 -- Just 3
53 -- >>> v1 !? 3
54 -- Nothing
55 --
56 (!?) :: (Vector v a) => v a -> Int -> Maybe a
57 (!?) v1 idx
58 | idx < 0 || idx >= length v1 = Nothing
59 | otherwise = Just $ v1 ! idx
60
61
62 -- | Remove an element of the given vector.
63 --
64 -- Examples:
65 --
66 -- >>> import Data.Vector.Fixed (mk3)
67 -- >>> let b = mk3 1 2 3 :: Vec3 Int
68 -- >>> delete b 1 :: Vec2 Int
69 -- fromList [1,3]
70 --
71 delete :: (Vector v a,
72 Vector w a,
73 Dim v ~ S (Dim w))
74 => v a
75 -> Int
76 -> w a
77 delete v1 idx =
78 fromList (lhalf ++ rhalf')
79 where
80 (lhalf, rhalf) = splitAt idx (toList v1)
81 rhalf' = tail rhalf
82
83
84 -- | We provide our own sum because sum relies on a Num instance
85 -- from the Prelude that we don't have.
86 --
87 -- Examples:
88 --
89 -- >>> import Data.Vector.Fixed (mk3)
90 -- >>> let b = mk3 1 2 3 :: Vec3 Int
91 -- >>> element_sum b
92 -- 6
93 --
94 element_sum :: (Additive.C a, Ring.C a, Vector v a) => v a -> a
95 element_sum = foldl (+) (fromInteger 0)