Skip to content

Instantly share code, notes, and snippets.

@CarstenKoenig
Last active December 19, 2015 16:19
Show Gist options
  • Save CarstenKoenig/5982572 to your computer and use it in GitHub Desktop.
Save CarstenKoenig/5982572 to your computer and use it in GitHub Desktop.
Vec.hs
-- basic implementation of a vector type
-- modeled after the Vec type from Courseras "Coding the Matrix" class
-- | implementation of a sparse-vector representation based on the
-- Courseras "Coding the Matrix" MOOC class
-- this is in no way optimized and is just indended for learning
module Vec where
-- *** I worked with these imports ... you might want others (or not)
import Data.List (intercalate)
import Control.Exception(assert)
import qualified Data.Set as S
import qualified Data.Map as M
-- *** this are the used types for Vec ***
type Dom d = [d]
type Entries f d = M.Map d f
newtype Vec f d = Vec (Dom d, Entries f d)
-- *** PLEASE implement THESE ***
getItem :: (Num f, Ord d) => Vec f d -> d -> f
getItem v i =
assert (inDomain v i) $
undefined
setItem :: (Num f, Ord d) => Vec f d -> d -> f -> Vec f d
setItem v i x =
assert (inDomain v i) $
undefined
vequal :: (Num f, Ord d, Eq f) => Vec f d -> Vec f d -> Bool
vequal v v' =
assert (domain v == domain v') $
undefined
vadd :: (Ord d, Num f) => Vec f d -> Vec f d -> Vec f d
vadd v v' =
assert (domain v == domain v') $
undefined
vdot :: (Ord d, Num f) => Vec f d -> Vec f d -> f
vdot v v' =
assert (domain v == domain v') $
undefined
vscal :: Num f => f -> Vec f d -> Vec f d
vscal s v = undefined
vneg :: Num f => Vec f d -> Vec f d
vneg = undefined
-- *** NO NEED TO MODIFY BELOW HERE ***
-- *** some helpers you might find usefull ***
domain :: Vec f d -> Dom d
domain (Vec (d, _)) = d
entries :: Vec f d -> Entries f d
entries (Vec (_, e)) = e
createVec :: Dom d -> Entries f d -> Vec f d
createVec dom e = Vec (dom, e)
fromList :: Ord d => [(d,f)] -> Vec f d
fromList ixs = createVec dom entries
where entries = M.fromList ixs
dom = M.keys entries
inDomain :: Eq d => Vec f d -> d -> Bool
inDomain = flip elem . domain
nullVec :: Dom d -> Vec f d
nullVec dom = Vec (dom, M.empty)
-- *** Vec should be in some type classes ***
-- NOTE: Num is not fully supported here - only insofar that
-- we get vector addition and substraction with +/- working
instance (Num f, Show f, Ord d) => Show (Vec f d) where
show v = format . map (show . getItem v) $ domain v
where format = wrapInParens . intercalate ", "
wrapInParens s = "(" ++ s ++ ")"
instance (Num f, Ord d, Eq f) => Eq (Vec f d) where
(==) = vequal
instance (Num f, Eq f, Ord d) => Num (Vec f d) where
(+) = vadd
negate = vneg
(*) = undefined
fromInteger n = undefined
abs = undefined
signum = undefined
-- *** Some operators - the naming might be debatable
(.*) :: (Ord d, Num f) => Vec f d -> Vec f d -> f
(.*) = vdot
(|*) :: Num f => f -> Vec f d -> Vec f d
(|*) = vscal
(|!) :: (Num f, Ord d) => Vec f d -> d -> f
(|!) = getItem
(|:) :: (Num f, Ord d) => Vec f d -> (d, f) -> Vec f d
v |: (i, x) = setItem v i x
(|::) :: (Num f, Ord d) => Vec f d -> [(d, f)] -> Vec f d
v |:: ixs = foldl (|:) v ixs
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment