X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FLinear%2FVector.hs;h=ec6ebcbfba47722110a056e90fb2590f93c8ed7d;hb=e4c2b71137d47045670cba23d420ea10a9e827b5;hp=9774dcd40c8132413ddd541a2a65be8976a462e1;hpb=303c5e7bba583f08e59bc6c848be8e75c1155a3b;p=numerical-analysis.git diff --git a/src/Linear/Vector.hs b/src/Linear/Vector.hs index 9774dcd..ec6ebcb 100644 --- a/src/Linear/Vector.hs +++ b/src/Linear/Vector.hs @@ -7,7 +7,6 @@ module Linear.Vector where -import Data.List (intercalate) import Data.Vector.Fixed ( Dim, Fun(..), @@ -15,17 +14,22 @@ import Data.Vector.Fixed ( N2, N3, N4, + N5, + S, Vector(..), construct, + fromList, inspect, toList, ) import qualified Data.Vector.Fixed as V ( length, ) +import Data.Vector.Fixed.Boxed -import Normed - +type Vec1 = Vec N1 +type Vec4 = Vec N4 +type Vec5 = Vec N5 -- * Low-dimension vector wrappers. -- @@ -34,25 +38,25 @@ import Normed -- constructors, so you can pattern match out the individual -- components. -data D1 a = D1 a +data D1 a = D1 a deriving (Show, Eq) type instance Dim D1 = N1 instance Vector D1 a where inspect (D1 x) (Fun f) = f x construct = Fun D1 -data D2 a = D2 a a +data D2 a = D2 a a deriving (Show, Eq) type instance Dim D2 = N2 instance Vector D2 a where inspect (D2 x y) (Fun f) = f x y construct = Fun D2 -data D3 a = D3 a a a +data D3 a = D3 a a a deriving (Show, Eq) type instance Dim D3 = N3 instance Vector D3 a where inspect (D3 x y z) (Fun f) = f x y z construct = Fun D3 -data D4 a = D4 a a a a +data D4 a = D4 a a a a deriving (Show, Eq) type instance Dim D4 = N4 instance Vector D4 a where inspect (D4 w x y z) (Fun f) = f w x y z @@ -63,7 +67,7 @@ instance Vector D4 a where -- -- Examples: -- --- >>> let v1 = Vec2D 1 2 +-- >>> let v1 = D2 1 2 -- >>> v1 ! 1 -- 2 -- @@ -74,7 +78,7 @@ instance Vector D4 a where -- -- Examples: -- --- >>> let v1 = Vec3D 1 2 3 +-- >>> let v1 = D3 1 2 3 -- >>> v1 !? 2 -- Just 3 -- >>> v1 !? 3 @@ -86,52 +90,17 @@ instance Vector D4 a where | otherwise = Just $ v1 ! idx - - ---instance (RealFloat a, Ord a, Vector v a) => Normed (Vn v a) where - -- | The infinity norm. We don't use V.maximum here because it - -- relies on a type constraint that the vector be non-empty and I - -- don't know how to pattern match it away. - -- - -- Examples: - -- - -- >>> let v1 = make3d (1,5,2) - -- >>> norm_infty v1 - -- 5 - -- --- norm_infty (Vn v1) = realToFrac $ V.foldl max 0 v1 - - -- | Generic p-norms. The usual norm in R^n is (norm_p 2). - -- - -- Examples: - -- - -- >>> let v1 = make2d (3,4) - -- >>> norm_p 1 v1 - -- 7.0 - -- >>> norm_p 2 v1 - -- 5.0 - -- --- norm_p p (Vn v1) = --- realToFrac $ root $ V.sum $ V.map (exponentiate . abs) v1 --- where --- exponentiate = (** (fromIntegral p)) --- root = (** (recip (fromIntegral p))) - - - - - --- | Convenient constructor for 2D vectors. +-- | Remove an element of the given vector. -- -- Examples: -- --- >>> import Roots.Simple --- >>> let h = 0.5 :: Double --- >>> let g1 (Vn (Vec2D x y)) = 1.0 + h*exp(-(x^2))/(1.0 + y^2) --- >>> let g2 (Vn (Vec2D x y)) = 0.5 + h*atan(x^2 + y^2) --- >>> let g u = make2d ((g1 u), (g2 u)) --- >>> let u0 = make2d (1.0, 1.0) --- >>> let eps = 1/(10^9) --- >>> fixed_point g eps u0 --- (1.0728549599342185,1.0820591495686167) +-- >>> let b = D3 1 2 3 +-- >>> delete b 1 :: D2 Int +-- D2 1 3 -- +delete :: (Vector v a, Vector w a, Dim v ~ S (Dim w)) => v a -> Int -> w a +delete v1 idx = + fromList $ (lhalf ++ rhalf') + where + (lhalf, rhalf) = splitAt idx (toList v1) + rhalf' = tail rhalf