------------------------------------------------------------------------------- -- $Id: Col.hs#1 2009/10/01 10:31:09 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Lava.Col where import Lava.Below ------------------------------------------------------------------------------- col :: Monad m => Int -> -- number of elements in col ((a, b) -> m (c, a)) -> -- type of element circuit r (a, [b]) -> -- input to the col m ([c], a) -- output of the col col n r (_, bus) | length bus /= n = error ("col shape error: col " ++ show n ++ " but input bus is size " ++ show (length bus) ++ "\n") col 1 r (a, [b]) = do (c,d) <- r (a, b) return ([c],d) col n r (a, b:bs) = do ((c,cs), d) <- (r `below` (col (n-1) r)) (a, (b, bs)) return (c:cs, d) ------------------------------------------------------------------------------- -- 4-Sided Tile Combinators ------------------------------------------------------------------------------- -- COL r -- a -- ^ -- | -- ----- -- | | -- b ->| r |-> c -- | | -- ----- -- ^ -- | -- a -- ^ -- | -- ----- -- | | -- b ->| r |-> c -- | | -- ----- -- ^ -- | -- a -- ^ -- | -- ----- -- | | -- b ->| r |-> c -- | | -- ----- -- ^ -- | -- a -------------------------------------------------------------------------------