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