\section{Vectors} \begin{verbatim} This module exports the type Vec. A constructor and destructor for this type are exposed. Vec is made an instance of Eq,Ord,Num and Fractional; meaning functions defined over these types are made available for Vec. e.g. sum (a::[Vec]) \end{verbatim} > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > module ZEBEDDE.Core.Vector > ( Vec(unVec), > vec, > apply, > apply2, > magnitude, > testVectorHs) where Create vector type. > newtype Vec = Vec { > unVec :: (Double,Double,Double) > } deriving (Eq) > vec = Vec \begin{verbatim} We do not export the newtype Vec datatype because we wish to restrict patern matching incase its structure changes later on. Instead we export the constructor vec, whch cannot be pattern matched. \end{verbatim}\\ Apply a function to each element of a vector > apply f (Vec (a,b,c)) = Vec (f a,f b,f c) \begin{verbatim} Transform a function taking two doubles and returning a double, into a function taking two vectors and returning a vector \end{verbatim} > apply2 :: (Double -> Double -> Double) -> (Vec -> Vec -> Vec) > apply2 f (Vec (x,y,z)) (Vec (a,b,c)) = Vec (f x a,f y b, f z c) Define magnetude of vector > magnitude (Vec (a,b,c)) = sqrt (a^2+b^2+c^2) Order vectors by their magnitude > instance Ord Vec where > (<=) a b = (magnitude a) <= (magnitude b) Method to add, subtract and multiply vectors, \\ also extends some standard functions on the integers to vectors. > instance Num Vec where > fromInteger a = let a' = fromInteger a in vec (a',a',a') > -- creates a vector whoes > -- elements are all the given integer, expressed as doubles. > (+) = apply2 (+) > (-) = apply2 (-) > (*) = apply2 (*) -- so can e.g. multiply a vector by a scalar simply using (*) > abs = apply abs -- absolute value of each element of the vector as a vector. > signum = apply signum -- signum of each element of the vector as a vector. Create fractional vectors of rational numbers. \begin{verbatim} While we store Vec as a tripple of type Double, here the actual tripple is made to be a rational number by element-wise division. \end{verbatim} > instance Fractional Vec where > fromRational a = apply (+(fromRational a)) 0 -- can now opperate on rational scalars, e.g. division by a scalar > (/) = apply2 (/) > testVectorHs = Vec (0.5,0.5,0.5) == 1/2