{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, ScopedTypeVariables, FlexibleContexts, KindSignatures, FunctionalDependencies #-} module Vec(Vec(..) ,VecMap(..) ,vfold ,VecAbs(..) ,VecRef(..) ,VecSet(..) ,VecLen(..) ) where import Data import Type import Control.Monad -- Note: 'r' is always the outer type constructor wrt. 'v'. -- And 'm' is outer wrt. 'r'. class Vec (v :: * -> *) class (Vec v, Data m r) => VecLen m r v t where vlen :: r (v t) -> m (r Tint) class (Vec v, Data m r) => VecMap m r v | r -> v, r -> m where vmap :: (r a -> m (r b)) -> r (v a) -> m (r (v b)) -- Fold drives evaluation (vref), while map can be postponed through -- loop fusion. vfold :: (Vec v, Data m r, Ring m r Tint, Order m r Tint, VecLen m r v e, VecRef m r v, While m r (Tint,a)) => (r e -> r a -> m (r a)) -> r a -> r (v e) -> m (r a) vfold body init vec = do liftM (snd . uncons) $ while pred update init' where init' = cons zero init pred ia = do let (i,a) = uncons ia l <- vlen vec lt i l update ia = do let (i,a) = uncons ia e <- vref vec i a' <- body e a i' <- add i one return $ cons i' a' -- I like the Feldspar explicit index model - with for loops and -- indexable vectors - as opposed to abstract containers with only -- map, fold defined. -- Abstract vectors are implemented as index functions. class (Vec v, Data m r) => VecAbs m r v | r -> v, r -> m where vec :: r Tint -> (r Tint -> m (r t)) -> m (r (v t)) class (Vec v, Data m r) => VecRef m r v | r -> v, r -> m where vref :: r (v t) -> r Tint -> m (r t) -- I'm not convinced yet about mutable operations, but at least it -- seems that this would give access to a whole lot more algorithms. class (Vec v, Data m r) => VecSet m r v | r -> v, r -> m where vset :: r (v t) -> r Tint -> r t -> m (r (v t))