------------------------------------------------------------------------------- -- $Id: Elaborate.hs#1 2009/10/01 10:31:09 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Lava.Elaborate where import Lava.Primitives import Lava.Instance ------------------------------------------------------------------------------- elaborate :: (Int, Int, [Port], [InstanceTree], IODriverArray) -> (Int, Int, [Port], [Instance], IODriverArray) elaborate (netCount, instCount, ports, instTree, dl) = (netCount, instCount, ports, instances, dl) where instances = concat (map (elaborateInstTree (-1,-1)) instTree) ------------------------------------------------------------------------------- elaborateInstTree :: (Int, Int) -> InstanceTree -> [Instance] elaborateInstTree (dx', dy') (LeftOf t1 t2) = concat lhs ++ concat rhs where lhs = map (elaborateInstTree (dx, dy)) t1 (w,h) = sizeOf (concat lhs) rhs = map (elaborateInstTree (dx+w, dy)) t2 dx = 0 `max` dx' dy = 0 `max` dy' elaborateInstTree (dx', dy') (Below t1 t2) = concat lhs ++ concat rhs where lhs = map (elaborateInstTree (dx, dy)) t1 (w,h) = sizeOf (concat lhs) rhs = map (elaborateInstTree (dx, dy+h)) t2 dx = 0 `max` dx' dy = 0 `max` dy' elaborateInstTree (-1, -1) (Inst inst) = [inst] elaborateInstTree (dx, dy) (Inst (instNr, Gate kind name Unplaced size behav, i, o)) = [(instNr, Gate kind name (At (dx, dy)) size behav, i, o)] elaborateInstTree (dx, dy) (Inst (instNr, Gate kind name (At (x,y)) size behav, i, o)) = [(instNr, Gate kind name (At (x+dx, y+dy)) size behav, i, o)] elaborateInstTree (dx, dy) (Inst (instNr, g@(Gate kind name NoPlacement size behav), i, o)) = [(instNr, g, i, o)] ------------------------------------------------------------------------------- sizeOf :: [Instance] -> (Int, Int) sizeOf instances = (w, h) where poses = map gatePos [p | (_, p, _, _) <- instances] xs = [x | At (x,y) <- poses] ys = [y | At (x,y) <- poses] w = if xs == [] then 0 else 1 + maximum xs h = if ys == [] then 0 else 1 + maximum ys ------------------------------------------------------------------------------- footprint :: Instance -> (Int, Int) footprint (_, primitive, _, _) = gateSize primitive -------------------------------------------------------------------------------