------------------------------------------------------------------------------- -- $Id: Comparator.hs#1 2009/10/01 10:31:09 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Xilinx.Comparator where import Lava import Xilinx import Xilinx.Subtractor ------------------------------------------------------------------------------- -- The comparator returns '1' if b >= a, '0' otherwise. comparator :: Xilinx m bit => ([bit], [bit]) -> m bit comparator (a, b) = do (_, result) <- subtractorNoCarryIn n (a', b') return result where (a', b') = equaliseUnsignedVectors a b n = length a' ------------------------------------------------------------------------------- equaliseUnsignedVectors :: GroundAndPower bit => [bit] -> [bit] -> ([bit], [bit]) equaliseUnsignedVectors x y = if length x == length y then (x, y) else if length x > length y then equaliseUnsignedVectors y x else (x++replicate padding zero, y) where padding = length y - length x ------------------------------------------------------------------------------- comparator_top :: Int -> Int -> Out () comparator_top size1 size2 = do a <- input_vec "a" (size1-1) downto 0 b <- input_vec "b" (size2-1) downto 0 cmp <- comparator (a, b) output_bit "cmp" cmp -------------------------------------------------------------------------------