Questions on GHCi 6.10.4 + general questions

Hi I am getting the following message : parse error on input `= Code in question is attached . Another general question on haskell : I am not sure I understand correctly the 'where' clause usage , I'll happily accept comments on the code Thanks, Lev

On Fri, Nov 27, 2009 at 2:44 AM, Lev Broido
Hi I am getting the following message : parse error on input `= Code in question is attached .
On which line is the error occurring? I'm not used to seeing braces used without semi-colons, so the last bit is hard to follow. The 'where' clause after 'new_state' appears to be at the same indentation level as the 'new_state' declaration, which might confuse GHC. But I'm not sure what the rules are once you start throwing the braces around. Antoine

Hi Lev
Where clauses don't use braces so that's first problem.
Also this line near the end has a problem:
curr_bank_state = head . filter (\y -> y == (wr_bank,_) state
What should it be doing?
Best wishes
Stephen
2009/11/27 Lev Broido
Hi I am getting the following message : parse error on input `= Code in question is attached .
Another general question on haskell : I am not sure I understand correctly the 'where' clause usage , I'll happily accept comments on the code
Thanks, Lev
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Fri, Nov 27, 2009 at 10:15 AM, Stephen Tetley
Hi Lev
Where clauses don't use braces so that's first problem.
You are mistaken, where clauses can use braces to avoid having to use layout as all others layout-based constructs in Haskell (do, where, let, case _ of, even the top-level...). But in this case the semicolons are mandatory, since you're explicitly rejecting layout-based rules. That is one problem of this code (use of braces without the semicolons), I didn't check if there were others. -- Jedaï

2009/11/27 Stephen Tetley
Where clauses don't use braces so that's first problem.
Apologies where clauses can have braces - by convention people don't use them. Best wishes Stephen http://www.haskell.org/onlinereport/syntax-iso.html#sect9

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 }

Thank you very match
On Fri, Nov 27, 2009 at 12:09 PM, Stephen Tetley
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
}
participants (4)
-
Antoine Latter
-
Chaddaï Fouché
-
Lev Broido
-
Stephen Tetley