[Haskell-cafe] Code critique - Was [Maybe Int] sans Nothings

Alexander Solla alex.solla at gmail.com
Wed May 25 04:42:10 CEST 2011


My comments are in-line, marked off with >>>

On Tue, May 24, 2011 at 4:09 PM, michael rice <nowgate at yahoo.com> wrote:

> The input file: http://dl.dropbox.com/u/27842656/psalms
>
> The Markov chain exercise from "The Practice of Programming",
> Kermighan/Pike. Sample runs at the end.
>
> Michael
>
> ============================
>
> import System.Environment(getArgs)
> import System.Random
> import Control.Applicative
> import Control.Monad.Reader
> import Control.Monad.State
> import Data.Maybe
> import Data.Map
>
> type Prefix = (String,String)
> type GeneratorState1 = State ((Map Prefix [String]),Prefix,[String])
> type GeneratorState2 = StateT (Prefix,StdGen) (Reader (Map Prefix
> [String]))
>
> non_word = "\n"
>
> f key new old = new ++ old
>
>
>>> I don't see what f is for, since it doesn't do anything with the key.


> buildMap :: GeneratorState1 (Map Prefix [String])
> buildMap = do (mp,(pfx1,pfx2),words) <- get
>               if (Prelude.null words)
>                 then {- No more words. Return final map (adding non_word
> for final prefix). -}
>                   return (insertWithKey' f (pfx1,pfx2) [non_word] mp)
>                 else do {- Add word to map at prefix & continue. -}
>                   put (insertWithKey' f (pfx1,pfx2) [head words] mp,
> (pfx2,(head words)), tail words)
>                   buildMap
>
> >>> I'm not a fan of explicit if-then-else's, but my preferred alternative
won't win much either.  (see
http://osdir.com/ml/haskell-cafe@haskell.org/2011-05/msg00612.html for an
example of what I'm talking about)


> generate :: GeneratorState2 (Maybe String)
> generate = do ((pfx1,pfx2),gen) <- get
>               mp <- ask
>               let suffixList = mp ! (pfx1,pfx2)
>

>>> I'm not sure how you're guaranteed that mp ! (pfx1, pfx2) exists, at
first glance.  "lookup" uses Maybe semantics, in the case there is no
result.


>               let (index,newGen) = randomR (0, (length suffixList)-1) gen
>

>>> I might use a function like:
>>> listRange :: [a] -> (Int, Int)
>>> listRange list = (0,  (length $ l) - 1)
>>> This is a common enough pattern to abstract away.


              let word = suffixList !! index
>               if (word == non_word)
>                 then
>                   return Nothing
>                 else do
>                   put ((pfx2,word),newGen)
>                   return (Just word)
>
> rInt :: String -> Int
> rInt = read
>
>

>>> rInt is fair enough, but you can also have the same effect with an
explicit type signature ((read n) :: Int)  I tend to prefer the latter,
personally.


> main = do (seed:nwords:_) <- (Prelude.map rInt) <$> getArgs
>           contents <- getContents
>           putStrLn $ unwords $ catMaybes $ runReader (evalStateT (sequence
> $ replicate nwords generate) ((non_word,non_word),mkStdGen seed))
>                                                      (evalState buildMap
> (singleton (non_word,non_word) [], (non_word,non_word), words contents))
>
> >>> Nice use of functor application.


> {-
> [michael at hostname ~]$ ghc --make markov.hs
> [1 of 1] Compiling Main             ( markov.hs, markov.o )
> Linking markov ...
> [michael at hostname ~]$ cat psalms | ./markov 111 100
> Blessed is the LORD, in thine own cause: remember how the foolish people
> have blasphemed thy name. In the courts of the righteous: The LORD taketh
> pleasure in the desert. And he led them with the wicked, and with the whole
> earth, is mount Zion, on the sides of thine only. O God, and was troubled: I
> complained, and my God. My times are in thy praise. Blessed be God, which is
> full of the LORD is good: for his wondrous works. Now also when I am small
> and despised: yet do I put my trust: how say ye to
> [michael at hostname ~]$ cat psalms | ./markov 666 100
> Blessed is the LORD, and cried unto thee, Thy face, LORD, will I remember
> thee from the beginning: and every one that is weaned of his heart to any
> wicked transgressors. Selah. They return at evening: they make ready their
> arrow upon the people; and thou hast destroyed all them that fight against
> them that trust in thee: and let my tongue cleave to the heavens by his
> power for ever; and thy lovingkindnesses; for they have laid a snare before
> them: and that my ways were directed to keep thy word. Mine eyes fail while
> I have said that
> [michael at hostname ~]$
>
> --- On *Tue, 5/24/11, Alexander Solla <alex.solla at gmail.com>* wrote:
>
>
> From: Alexander Solla <alex.solla at gmail.com>
> Subject: Re: [Haskell-cafe] [Maybe Int] sans Nothings
> To: "Haskell Cafe" <haskell-cafe at haskell.org>
> Date: Tuesday, May 24, 2011, 5:01 PM
>
>
> > Personally, I find non-functional values without Eq instances to be
> > degenerate.  So I really do not mind superfluous Eq constraints.  I
> > would not hesitate to use filter ((/=) Nothing) in a function whose type
> > has no free type variables.  It's just a bit of plumbing inside of a
> > more complex function.
>
> Sometimes it seems to be better to not allow Eq on Float and Double.
> Since most algebraic laws do not hold for those types, it is more often
> an error than an intention to compare two Float values. And how to
> compare (IO a) values?
>
>
> Floats, Doubles, and IO are all "degenerate" types, for the reasons you
> outline.  (Admittedly, Float and Double have Eq instances, but invalid Eq
> semantics)  Notice how their value semantics each depend on the machine your
> runtime runs on, as opposed to merely the runtime.  Bottom is another one of
> these degenerate types, since comparisons on arbitrary values are
> undecidable.
>
> Also, by thinking about function types, you often
> get interesting use cases. Thus I would not assume too quickly that a
> type will always be instantiated by types other than a function type.
> Thus I would stick to (filter isJust) and use this consistently for
> monomorphic and polymorphic types.
>
>
> I am not suggesting (filter ((/=) Nothing)) /over/ (filter isJust).
>  Obviously, once one is aware of a  better tool, one should use it.  But I
> am suggesting that for simple cases which are unlikely to change in any
> substantive way, we should probably just use the tools we already know of,
> as opposed to searching for the "right" one.  Both might involve costs.
>  There is a cost involved in going to Google, thinking up a search term,
> finding that Data.Maybe has relevant functions, picking the right one.  It
> takes less time to write "filter ..." than to type "haskell removing nothing
> from list", for example.  When dealing with known unknowns, there is a
> balance to be made, and it is not easy.
>
> Michael's choice to ask the list imposed costs.  (Not that we mind, we're
> all volunteers, after all).  But it probably took 10 minutes to get the
> first reply.  He could have written a bit of code that worked correctly,
> given the context of his problem, in 20 seconds.  Then again, he probably
> worked on a different bit of code until somebody sent a solution, so we
> probably only have to account for the time spent in context switching, for
> everyone involved.
>
>
> -----Inline Attachment Follows-----
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org <http://mc/compose?to=Haskell-Cafe@haskell.org>
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110524/eece1da4/attachment-0001.htm>


More information about the Haskell-Cafe mailing list