------------------------------------------------------------------------------- --- $Id: Netlist.hs#4 2010/09/24 12:10:22 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Lava.Netlist (module Lava.Components, module Lava.Netlist) where import Control.Monad.State import Lava.Components import Data.Array.Unboxed -- * The Lava Netlist representation ------------------------------------------------------------------------------- data Dir = To | Downto deriving (Eq, Show) data NetType = BitType | BitVec Int Dir Int deriving (Eq, Show) data PortDirection = InputPort | OutputPort deriving (Eq, Show) ------------------------------------------------------------------------------- data PortDeclaration = Port String PortDirection NetType [Int] deriving (Eq, Show) ------------------------------------------------------------------------------- data Position = NoPlacement | Unplaced | Placed deriving (Eq, Show) ------------------------------------------------------------------------------- data Layout = Beside (Int, Int) Layout Layout | Below (Int, Int) Layout Layout | Overlay (Int, Int) Layout Layout | Tile (Int, Int) Int -- (w,h) instNr | EmptyLayout deriving (Eq, Show) ------------------------------------------------------------------------------- sizeOfLayout :: Layout -> (Int, Int) sizeOfLayout (Beside wh _ _) = wh sizeOfLayout (Below wh _ _) = wh sizeOfLayout (Overlay wh _ _) = wh sizeOfLayout (Tile wh _) = wh sizeOfLayout EmptyLayout = (0, 0) ------------------------------------------------------------------------------- data XilinxArchitecture = Virtex2 | Virtex4 | Virtex5 | Virtex6 deriving (Eq, Show) ------------------------------------------------------------------------------- data Instance = Instance {component :: Component, componentName :: String, instanceNumber :: Int, position :: Position, componentSize :: Maybe (Int,Int)} deriving (Eq, Show) ------------------------------------------------------------------------------- data Netlist = Netlist {ports :: [PortDeclaration], instances :: [Instance], netCount :: Int, instCount :: Int, layout :: [Layout], layoutNesting :: Int, computedShifts :: (Array Int Int, Array Int Int), xilinxArchitecture :: XilinxArchitecture } ------------------------------------------------------------------------------- getNetCount :: Out Int getNetCount = do state <- get return (netCount state) ------------------------------------------------------------------------------- getInstCount :: Out Int getInstCount = do state <- get return (instCount state) ------------------------------------------------------------------------------- addLayout :: Layout -> Out () addLayout newLayoutElement = do state <- get let currentLayout = layout state put (state {layout = newLayoutElement : currentLayout}) ------------------------------------------------------------------------------- incrementLayoutNesting :: Out () incrementLayoutNesting = do state <- get put state{layoutNesting = layoutNesting state + 1} ------------------------------------------------------------------------------- decrementLayoutNesting :: Out () decrementLayoutNesting = do state <- get put state{layoutNesting = layoutNesting state - 1} ------------------------------------------------------------------------------- type Out a = State Netlist a ------------------------------------------------------------------------------- type Bit = Int -------------------------------------------------------------------------------