
Hi Lev This one compiles with fairly minimal changes The main one is the new_state = ... line near the end has part commented out where there would otherwise be a type error. Also the nest where clause at the end was obscuring a variable binding that you needed, so I've removed the nesting. Pasted from my editor, hopefully, my mail client doesn't mangle the code: module DdrController where {- - DDR controller implements top function drive of original - list of commands . Assuming data is random . - The first version will drive commands from original command list - and adding to each command delta time , corresponding to minimum time - possible to execute -} -- Each command has it's set of attributes type Time = Int data DdrCmd = READ { bank :: Int, col :: Int } | READ_PCH { bank :: Int, col :: Int} | WRITE { bank :: Int, col :: Int} | WRITE_PCH { bank :: Int, col :: Int} | PCH_CMD {bank :: Int} | ACTIVATE {bank :: Int,row :: Int} | PCH_ALL | BST type DdrCommand = (Time,DdrCmd) -- Type of command containing offset -- Using tree to search for bank info data BankStateSingle = Single { bank_id :: Int , last_ras :: Time , last_cas :: Time , last_pch :: Time }; type BankEntry = (Int,BankStateSingle); type BankState = [BankEntry]; -- Check point events data TimingCheckPoint = RAS | CAS | PCH | NONE deriving Show type TimingCondition = (Int,TimingCheckPoint,TimingCheckPoint) -- All possible timing constraints data (Num a,Show a) => TimingParams a = TRP a | TRCD a | TRAS a -- Function to initialize timing params -- Randomly generates -- Create list of entries init_bank_set :: [BankStateSingle] -> BankState init_bank_set ba_list = zip [0..((length ba_list)-1)] ba_list timing_configuration :: [(Int,TimingCheckPoint,TimingCheckPoint)] timing_configuration = [ {-tRCD-}(4,RAS,CAS) , {-tRC-} (10,RAS,RAS),{-tRP-} (2,PCH,RAS)] -- Translation of timing check point cmd2timing_checkpoint :: DdrCmd -> TimingCheckPoint cmd2timing_checkpoint cmd = case cmd of READ _ _ -> CAS READ_PCH _ _ -> CAS WRITE _ _ -> CAS WRITE_PCH _ _-> CAS PCH_CMD _-> PCH ACTIVATE _ _ -> RAS PCH_ALL -> PCH BST -> NONE -- Return method from bank Id to bank selector func bank_timing_update :: Time -> TimingCheckPoint -> BankStateSingle -> BankStateSingle bank_timing_update time chk_point bank_state = new_bank_state where new_bank_state = case chk_point of RAS -> bank_state { last_ras = time } CAS -> bank_state { last_cas = time } PCH -> bank_state { last_pch = time } -- Change entry in list with other one if condition is met --upd_list :: (a -> Bool)->a->[a]->[a] --upd_list = () -- Calculate cmd delay and update bank state -- For each cmd define whether this is RAS,CAS or PCH command -- For each cmd , find bank it refers to -- For bank calculate new timing offset based on last occurrence beginning of arc -- and longest arc to satisfy updateCmdDelay :: DdrCommand -> BankState -> [TimingCondition] -> (DdrCommand,BankState) -- There are separate cases for commands -- PCH_ALL works on all banks and thus could not be issued before precharge -- timing ark is met for all cases updateCmdDelay (time,PCH_ALL) state timing = undefined updateCmdDelay (time,BST) state timing = ((time,BST),state) updateCmdDelay (time,(WRITE wr_bank wr_col)) state timing = -- Get all timing arcs to 'cmd2timing_checkpoint -- Find maximum by folding of delays and -- ((new_time,(WRITE wr_bank wr_col)),new_state) where { --new_state = num2bank wr_bank; new_time = if (earliest_time > time ) then earliest_time else time; new_state = (take ( wr_bank ) state) ++ {- [(wr_bank,curr_bank_state)] ++ -} (drop (wr_bank + 2) state); earliest_time = last_event_occur + (foldl max 0 delays); delays = [ time | (time,_,endpoint) <- timing ]; last_event_occur = case endpoint of { RAS -> last_ras $ snd curr_bank_state ; CAS -> last_cas $ snd curr_bank_state ; PCH -> last_pch $ snd curr_bank_state } ; -- Blabla endpoint = cmd2timing_checkpoint (WRITE wr_bank wr_col); curr_bank_state = head $ filter (\y -> fst y == wr_bank) state -- Update one of mields : last_ras,last_cas,last_pch -- For each bank }