{-# LANGUAGE DoRec #-} ------------------------------------------------------------------------------- --- $Id: Col.hs#2 2010/09/29 17:00:28 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Lava.Col (col) where import Lava.Netlist import Lava.Combinators ------------------------------------------------------------------------------- -- | Place four sided tile comoponents in a colum col :: ((a, b) -> Out (c, a)) -- ^ type of element circuit r -> (a, [b]) -- ^ input to the col -> Out ([c], a) -- ^ output of the col col r (a, [b]) = do (c,d) <- r (a, b) return ([c],d) col r (a, b:bs) = do rec {((c,d0), (cs,d)) <- par2 r (col r) ((a, b), (d0, bs))} return (c:cs, d) ------------------------------------------------------------------------------- -- 4-Sided Tile Combinators ------------------------------------------------------------------------------- -- COL r -- a -- ^ -- | -- ----- -- | | -- b ->| r |-> c -- | | -- ----- -- ^ -- | -- a -- ^ -- | -- ----- -- | | -- b ->| r |-> c -- | | -- ----- -- ^ -- | -- a -- ^ -- | -- ----- -- | | -- b ->| r |-> c -- | | -- ----- -- ^ -- | -- a -------------------------------------------------------------------------------