{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Linear.Vector where import Data.List (intercalate) import Data.Vector.Fixed ( Dim, Fun(..), N1, N2, N3, N4, Vector(..), construct, inspect, toList, ) import qualified Data.Vector.Fixed as V ( length, ) import Normed -- * Low-dimension vector wrappers. -- -- These wrappers are instances of 'Vector', so they inherit all of -- the userful instances defined above. But, they use fixed -- constructors, so you can pattern match out the individual -- components. data D1 a = D1 a 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 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 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 type instance Dim D4 = N4 instance Vector D4 a where inspect (D4 w x y z) (Fun f) = f w x y z construct = Fun D4 -- | Unsafe indexing. -- -- Examples: -- -- >>> let v1 = Vec2D 1 2 -- >>> v1 ! 1 -- 2 -- (!) :: (Vector v a) => v a -> Int -> a (!) v1 idx = (toList v1) !! idx -- | Safe indexing. -- -- Examples: -- -- >>> let v1 = Vec3D 1 2 3 -- >>> v1 !? 2 -- Just 3 -- >>> v1 !? 3 -- Nothing -- (!?) :: (Vector v a) => v a -> Int -> Maybe a (!?) v1 idx | idx < 0 || idx >= V.length v1 = Nothing | 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. -- -- 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) --