[Haskell-cafe] Doubting Haskell

Chaddaï Fouché chaddai.fouche at gmail.com
Tue Mar 4 17:30:00 EST 2008


2008/3/4, Alan Carter <alangcarter at gmail.com>:
>  I've written up some reflections on my newbie experience together with
>  both versions, which might be helpful to people interested in
>  popularizing Haskell, at:
>
>  http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/

This is truly interesting, any learning experience is enlightening, we
truly do need to lower this barrier of admittance of which you speak.

On another subject, there are still point in your code that could be
clearer or done with less              cruft :

maxOfHistogram stats = snd (foldl (\(cA, vA) (cB, vB) -> if (vA > vB)
                                                            then (cA, vA)
                                                            else (cB, vB))
                                  (0, 0)
                                  stats)

can become :

maxofHistogram stats = foldl' max 0 (map snd stats)

("foldl' max 0" could be replaced by "maximum" but there wouldn't be a
default 0 anymore)

more importantly, you can replace this kind of code :
  vA <- varCreate []
  vB <- varCreate []
  -- ...
  vL <- varCreate []
  vM <- varCreate []
  vN <- varCreate []
  vO <- varCreate []

by :
  [vA, vB, vC, vD, vE, vF, vG, vH, vI, vJ, vK, vL, vM, vN, vO] <-
    replicateM 15 (varCreate [])

(true also for the "dA <- textEntry statusFrame [text := "0",
alignment := AlignRight]" sequence)

I'm not sure that functions like getdTotal couldn't be improved, I
wonder if a small Map for the elements of d wouldn't make the code
much better and offer other opportunities for abstractions. As it is,
enumeration like :

             [[label "Total Entries",   widget (getdTotal d)]
             ,[label "Valid Entries",   widget (getdValid d)]
             -- ...
             ,[label "MDMA",            widget (getdMdma d)]
             ,[label "Caffeine",        widget (getdCaffeine d)]]

could be slightly reduced by :
let bindLabelAndWidget (lbl,getter) = [label lbl, widget (getter d)]
in map bindLabelAndWidget [("Total Entries", getdTotal), ("Valid
Entries", getdValid)
  ,(...)]

And little thing like :
mapM_ (\f -> do repaint f) knownFrames
becoming :
mapM_ repaint knownFrames


I also do concur that a flag or a warning to signal mixed tabulations
and space would be a _very_ good idea !

-- 
Jedaï


More information about the Haskell-Cafe mailing list