------------------------------------------------------------------------------- --- $Id: LUTGates.hs#2 2010/09/21 13:51:11 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Lava.LUTGates where import Control.Monad.State import Lava.Netlist ------------------------------------------------------------------------------- unaryLUT :: (Bool -> Bool) -> String -> Bit -> Out Bit unaryLUT gateOperation comment i0 = do state <- get let insts = instances state oNet = netCount state instNr = instCount state placement = if layoutNesting state > 0 then At (0,0) else Unplaced cSize = if layoutNesting state > 0 then Just (1,1) else Nothing newInst = Instance (Lut1 opBits i0 oNet comment) "lut1" instNr placement cSize put (state{instances = newInst:insts, netCount = oNet+1, instCount = instNr +1}) return oNet where opBits = map boolToInt [gateOperation False, gateOperation True] ------------------------------------------------------------------------------- boolToInt :: Bool -> Int boolToInt False = 0 boolToInt True = 1 ------------------------------------------------------------------------------- binaryLUT :: (Bool -> Bool -> Bool) -> String -> (Bit, Bit) -> Out Bit binaryLUT gateOperation comment (i0, i1) = do state <- get let insts = instances state oNet = netCount state instNr = instCount state placement = if layoutNesting state > 0 then At (0, 0) else Unplaced cSize = if layoutNesting state > 0 then Just (1,1) else Nothing newInst = Instance (Lut2 opBits i0 i1 oNet comment) "lut2" instNr placement cSize put (state{instances = newInst:insts, netCount = oNet+1, instCount = instNr +1}) return oNet where opBits = map boolToInt [gateOperation False False, gateOperation True False, gateOperation False True, gateOperation True True] -------------------------------------------------------------------------------