[Haskell-cafe] Proposal: Non-recursive let

oleg at okmij.org oleg at okmij.org
Thu Jul 25 09:09:12 CEST 2013


Here is a snippet from a real code that could benefit from
non-recursive let. The example is notable because it incrementally
constructs not one but two structures (both maps), ast and headers.
The maps are constructed in a bit interleaved fashion, and stuffing
them into the same State would be ungainly. In my real code

-- Add an update record to a buffer file
do_update :: String -> Handle -> Parsed -> [Parsed] -> IO ()
do_update "TAF" h ast asts@(_:_) = do
  rv <- reflect $ get_trange "TRange" ast
  headers0 <- return . M.fromList =<< sequence 
                 (map (\ (n,fld) -> reflect (fld ast) >>= \v -> return (n,v)) 
		      fields_header)
  let headers = M.insert "_report_ranges" (format_two_tstamps rv) headers0
  foldM write_period (rv,headers,(snd rv,snd rv)) asts
  return ()
 where
 write_period (rv,headers,mv) ast = do
  pv@(p_valid_from,p_valid_until) <- reflect $ get_trange "TRange" ast
  check_inside pv rv
  let prevailing = M.lookup "PREVAILING" ast
  (mv,pv) <- case prevailing of
    Just _  -> return (pv,pv)		-- set the major valid period
	     -- Make sure each VAR period occurs later than the prevailing 
	     -- period. If exactly at the same time add 1 min
    Nothing -> case () of
     _ | fst mv < p_valid_from  -> return (mv,pv)
     _ | fst mv == p_valid_from -> return (mv,(p_valid_from + 60,
					      p_valid_until))
     _  -> gthrow . InvalidData . unwords $ [
              "VAR period begins before prevailing:",
	      show ast, "; prevailing TRange", show mv]
  let token      = maybe (M.findWithDefault "" "VAR" ast) id prevailing
  let ast1 = M.insert "_token" token .
               M.insert "_period_valid" (format_two_tstamps pv) .
                 M.unionWith (\_ x -> x) headers $ ast
  let title      = M.member "Title" ast
  let headers1 = if title then headers else
		    M.delete "_limit_to " . M.delete "_limit_recd" $ headers

  write_fields h ast1 fields  

  return (rv,headers1,mv)





More information about the Haskell-Cafe mailing list