{-# OPTIONS_GHC -XTypeSynonymInstances #-} ------------------------------------------------------------------------------- -- $Id: Components.hs#1 2009/10/01 10:31:09 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Xilinx.Components where import Lava ------------------------------------------------------------------------------- class Combinational m bit => Xilinx m bit where xorcy :: (bit, bit) -> m bit muxcy :: (bit, (bit, bit)) -> m bit ------------------------------------------------------------------------------- instance Xilinx Out Wire where xorcy = xorcy_nl muxcy = muxcy_nl ------------------------------------------------------------------------------- inv_nl :: Wire -> Out Wire inv_nl = unary_gate (Gate Lut1 "inv" Unplaced (1,1) (UnaryGate not)) ------------------------------------------------------------------------------- and2_nl :: (Wire, Wire) -> Out Wire and2_nl = binary_gate (Gate Lut2 "and2" Unplaced (1,1) (BinaryGate (&&))) ------------------------------------------------------------------------------- or2_nl :: (Wire, Wire) -> Out Wire or2_nl = binary_gate (Gate Lut2 "or2" Unplaced (1,1) (BinaryGate (||))) ------------------------------------------------------------------------------- xor2_nl :: (Wire, Wire) -> Out Wire xor2_nl = binary_gate (Gate Lut2 "xor2" Unplaced (1,1) (BinaryGate (/=))) ------------------------------------------------------------------------------- nxor2_nl :: (Wire, Wire) -> Out Wire nxor2_nl = binary_gate (Gate Lut2 "nxor2" Unplaced (1,1) (BinaryGate (==))) ------------------------------------------------------------------------------- xorcy_nl :: (Wire, Wire) -> Out Wire xorcy_nl = binary_gate (Gate (LeafGate ["li", "ci"] ["o"]) "xorcy" Unplaced (1,1) (BinaryGate (/=))) ------------------------------------------------------------------------------- muxcy_nl :: (Wire, (Wire, Wire)) -> Out Wire muxcy_nl (s, (di, ci)) = three_input_gate (Gate (LeafGate ["s", "di", "ci"] ["o"]) "muxcy" Unplaced (1,1) (Gate3 muxcy_behav)) (s, di, ci) ------------------------------------------------------------------------------- muxcy_behav :: Bool -> Bool -> Bool -> Bool muxcy_behav s di ci = if s then ci else di -------------------------------------------------------------------------------