
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)

On 25/07/2013, at 7:09 PM,
Here is a snippet from a real code that could benefit from non-recursive let.
[[A big blob of extremely dense code.]] _Nothing_ is going to make that easy to read. And I say that as someone who loves Haskell and is in *awe* of Oleg. I mean, if the functional rain is pouring down and Oleg says "Hey, sunny!", I normally furl my umbrella... One of the things that I find makes it hard for _me_ to read is the coding style where "do" is sneaked away out of sight. Am I alone in wanting "do" at the _beginning_ of a line so that it stands out? Do real Haskell experts just get used to using "do" so much that they don't feel it's _worth_ making visible? It's a queer thing, I always feel that the advice about keeping function bodies small is patronising nonsense for beginners and that *my* code is perfectly readable no matter how big it is, but end up wishing that *other* people kept *their* functions small. It's not as if my code were bug-free... Must be something in the water. That's relevant though. If your functions are small, you don't get enough "versions" of a variable for non-recursive let to pay off. In this specific example, as a _reader_, a much less competent reader than Oleg, the only problem I can see with using "ast1" and "header1" is that th names are not different *ENOUGH* from "ast1" and "header". I'd like names that go some towards explaining *why* 'ast1' has "_token" and "_period_values" slots that 'ast' doesn't (and for that matter, something a bit longer than 'ast', which doesn't seem to stand for Abstract Syntax Tree here), and *why* 'headers1' shouldn't include "_limit_to" and "_limit_rcvd" slots unless there is a title. All in all, a good example of code where using non-recursive let would have DECREASED readability by one person strange to the code.

On Thu, Jul 25, 2013 at 07:34:55PM +1200, Richard A. O'Keefe wrote:
It's a queer thing, I always feel that the advice about keeping function bodies small is patronising nonsense for beginners and that *my* code is perfectly readable no matter how big it is, but end up wishing that *other* people kept *their* functions small.
For example, breaking this code into smaller functions could make it transparent that 'token' is only used in 'ast1', 'title' is only used in 'headers1' and that the 'mv' that is the argument to 'write_period' is only used in the Nothing branch of the massive case statement. It seems there are a number of straightforward ways to make this code much clearer that do not require non-recursive let. Tom

On 25.07.2013 09:09, oleg@okmij.org wrote:
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)
This is a mouth-full. The ">>= \v -> return (n,v)" can be more elegantly expressed with tuple section (map (\ (n,fld) -> (n,) <$> reflect (fld ast)) fields_header) Maybe even use mapSnd f = (id *** f) and write (map (mapSnd $ \ fld -> reflect (fld ast)) fields_header) and, getting into lambda-killing rush :-) (map (mapSnd $ reflect . ($ ast)) fields_header) (ok, now we overdid it). Also, was not mapM = sequence . map ? And return . f =<< m the same as f <$> m? Then we are at headers0 <- M.fromList <$> do mapM (\ (n,fld) -> (n,) <$> reflect (fld ast)) fields_header Actually, I prefer for-loops: headers0 <- M.fromList <$> do forM fields_header $ \ (n, fld) -> do (n,) <$> reflect $ fld ast Great satisfaction! I killed all long-ranging parentheses! ;-) -- Andreas
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)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

Or fmap in this case =)
On Wed, Jul 31, 2013 at 11:33 AM, Erik Hesselink
On Fri, Jul 26, 2013 at 6:44 PM, Andreas Abel
wrote: mapSnd f = (id *** f)
As a very small aside, this is just `second` from Control.Arrow.
Erik
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 26.07.13 6:44 PM, Andreas Abel wrote:
headers0 <- M.fromList <$> do forM fields_header $ \ (n, fld) -> do (n,) <$> reflect $ fld ast
Ah, I forgot one more 'do' to override the stronger binding of <$>: (n,) <$> do reflect $ fld ast
Great satisfaction! I killed all long-ranging parentheses! ;-)
-- Andreas
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)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/
participants (6)
-
Andreas Abel
-
Edward Kmett
-
Erik Hesselink
-
oleg@okmij.org
-
Richard A. O'Keefe
-
Tom Ellis