Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  hlint and DoIfThenElse (Felipe Almeida Lessa)
   2. Re:  hlint and DoIfThenElse (Daniel Fischer)
   3. Re:  Beginners Digest, Vol 41, Issue 30 (Lee Short)
   4.  List comprehension question (Lee Short)
   5. Re:  List comprehension question (Daniel Fischer)
   6. Re:  Beginners Digest, Vol 41, Issue 30 (Daniel Fischer)
   7.  Precedence of Infix Operators in Do Syntax (Avery Robinson)
   8. Re:  Precedence of Infix Operators in Do Syntax (Brent Yorgey)
   9. Re:  Precedence of Infix Operators in Do Syntax
      (Alexander Bernauer)
  10. Re:  List comprehension question (Alexander Bernauer)


----------------------------------------------------------------------

Message: 1
Date: Tue, 22 Nov 2011 21:04:36 -0200
From: Felipe Almeida Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] hlint and DoIfThenElse
To: Mike Meyer <m...@mired.org>
Cc: beginners@haskell.org
Message-ID:
        <CANd=oggfcqz0enjrausys3hvq9r_kacx_o+2tjqhgzrttam...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Tue, Nov 22, 2011 at 8:58 PM, Mike Meyer <m...@mired.org> wrote:
> You've just pressed one of my language-independent style hot
> buttons. Why on earth are you using an if/then/else here? What's wrong
> with the straightforward:
>
> ? ? ?return "" == results
>
> The expression results in a boolean, and it's even the one you want to
> return. So why not return it?

Minor nitpick since we are on 'begginers' list: you need parenthesis
there, so either

  return ("" == results)

or

  return $ "" == results

otherwise it would get parsed as '(return "") == results'.


Also, note that instead of doing "" ==, you could use 'null', so

  return (null results)


HTH,

-- 
Felipe.



------------------------------

Message: 2
Date: Wed, 23 Nov 2011 00:06:04 +0100
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] hlint and DoIfThenElse
To: beginners@haskell.org
Cc: Lee Short <black...@pro-ns.net>
Message-ID: <201111230006.04959.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="iso-8859-1"

On Tuesday 22 November 2011, 23:46:37, Lee Short wrote:
>  hlint gives me a parse error on a clause using DoIfThenElse, even if I
>  have the language pragma.

hlint probably has its own parser which doesn't yet implement that 
extension.

>  I don't see any hlint options to get around
>  that, are there any?

Just indent the then and else lines a bit more.

> 
>  Is it considered good style to write code like this?
> 
>  if "" == results
>  then return True
>  else return False
> 
>  The obvious way rewrite below just seems clunky to me (though I can see
>  how others might prefer it to the code above).
> 
>  return $ if "" == results
>           then True
>           else False


The obvious rewrite is

    return (null results)

`if condition then True else False' is the same as `condition', which is 
clearer (and shorter).





------------------------------

Message: 3
Date: Tue, 22 Nov 2011 15:21:33 -0800
From: Lee Short <black...@pro-ns.net>
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 41, Issue 30
To: <beginners@haskell.org>
Message-ID: <524915ffb030295799eefa69c5c88...@pro-ns.net>
Content-Type: text/plain; charset=UTF-8; format=flowed


> On Tue, 22 Nov 2011 14:46:37 -0800
> Lee Short <black...@pro-ns.net> wrote:
>
>>  hlint gives me a parse error on a clause using DoIfThenElse, even 
>> if
>> I have the language pragma.  I don't see any hlint options to get
>> around that, are there any?
>>
>>  Is it considered good style to write code like this?
>>
>>  if "" == results
>>  then return True
>>  else return False
>>
>>  The obvious way rewrite below just seems clunky to me (though I can
>> see how others might prefer it to the code above).
>>
>>  return $ if "" == results
>>           then True
>>           else False
>
> You've just pressed one of my language-independent style hot
> buttons. Why on earth are you using an if/then/else here? What's 
> wrong
> with the straightforward:
>
>       return "" == results
>
> The expression results in a boolean, and it's even the one you want 
> to
> return. So why not return it?
>

 That's not my actual code, I was just using it as a simplified example 
 and didn't put a lot of thought into it.  My actual code is

 if delete /= ""
    then if exists
          then deleteFromTable req t key
          else return ()
    else if exists
          then updateTable req t key
          else insertTable req t

 I'd love to hear comments on how to make that more idiomatic, if 
 there's a way.




------------------------------

Message: 4
Date: Tue, 22 Nov 2011 16:08:26 -0800
From: Lee Short <black...@pro-ns.net>
Subject: [Haskell-beginners] List comprehension question
To: <beginners@haskell.org>
Message-ID: <1a6357e5e4aa11d70dbb4f99faae3...@pro-ns.net>
Content-Type: text/plain; charset=UTF-8; format=flowed

 So hlint suggests that I convert the line

 checked = if ival==input   then [("checked","checked")]  else []

 to

 checked = [("checked","checked") | ival==input]

 I'm not really sure why this works.  Is there some implicit list being 
 filtered by ival==input?  What's going on?

 thanks
 Lee




------------------------------

Message: 5
Date: Wed, 23 Nov 2011 01:22:55 +0100
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] List comprehension question
To: beginners@haskell.org
Cc: Lee Short <black...@pro-ns.net>
Message-ID: <201111230122.55769.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="iso-8859-1"

On Wednesday 23 November 2011, 01:08:26, Lee Short wrote:
>  So hlint suggests that I convert the line
> 
>  checked = if ival==input   then [("checked","checked")]  else []
> 
>  to
> 
>  checked = [("checked","checked") | ival==input]
> 
>  I'm not really sure why this works.  Is there some implicit list being
>  filtered by ival==input?  What's going on?

A list comprehension

[expression | condition]

desugars to

if condition then [expression] else []

IMO, that's one of the places where hlint doesn't suggest an improvement.



------------------------------

Message: 6
Date: Wed, 23 Nov 2011 01:35:00 +0100
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 41, Issue 30
To: beginners@haskell.org
Cc: Lee Short <black...@pro-ns.net>
Message-ID: <201111230135.00884.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="iso-8859-1"

On Wednesday 23 November 2011, 00:21:33, Lee Short wrote:
>  That's not my actual code, I was just using it as a simplified example

Glad to read that.

>  and didn't put a lot of thought into it.  My actual code is
> 
>  if delete /= ""
>     then if exists
>           then deleteFromTable req t key
>           else return ()
>     else if exists
>           then updateTable req t key
>           else insertTable req t
> 
>  I'd love to hear comments on how to make that more idiomatic, if 
>  there's a way.

Hmm, harder, much harder.

You can replace the

    if exists
      then deleteFromTable req t key
      else return ()

with

    when exists (deleteFromTable req t key)

and instead of comparing to "", you can use null, so

if null delete
  then if exists
         then updateTable req t key
         else insertTable req t
  else when exists (deleteFromTable req t key)

I would recommend the when. Concerning the null vs. /= "", I prefer null, 
but I'm not religious about it.




------------------------------

Message: 7
Date: Tue, 22 Nov 2011 23:03:51 -0500
From: Avery Robinson <av...@averyrobinson.name>
Subject: [Haskell-beginners] Precedence of Infix Operators in Do
        Syntax
To: beginners@haskell.org
Message-ID:
        <ca+6vedlku5tkwggytj3koy9lrwmhoxvecpn_-z3i305ijqr...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hello,

I was reading this block of code from
http://jasani.org/2008/02/18/command-line-haskell-and-error-handling-examples/

main = do
  m <- hGetContents stdin
  nums <- mapM readM . lines $ m
  print (sum nums)
  `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))

readM :: (Monad m, Read a) => String -> m a
readM s | [x] <- parse = return x
        | otherwise    = fail $ "Failed to parse \"" ++ s ++ "\" as a
number."
  where
    parse = [x | (x,_) <- reads s]

I don't understand how line 5 works. I thought that the do notation there
would be the same as:

main = hGetContents stdin >>= \m ->
       mapM readM . lines $ m >>= \nums ->
       print (sum nums) >>
       `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))

But I don't understand how that makes any sense with that infix `catch`. It
looks like catch doesn't even have a first argument. Please enlighten me.

Thanks.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111122/b5ee87d7/attachment-0001.htm>

------------------------------

Message: 8
Date: Wed, 23 Nov 2011 01:51:43 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Precedence of Infix Operators in Do
        Syntax
To: beginners@haskell.org
Message-ID: <20111123065143.ga5...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Tue, Nov 22, 2011 at 11:03:51PM -0500, Avery Robinson wrote:
> Hello,
> 
> I was reading this block of code from
> http://jasani.org/2008/02/18/command-line-haskell-and-error-handling-examples/
> 
> main = do
>   m <- hGetContents stdin
>   nums <- mapM readM . lines $ m
>   print (sum nums)
>   `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))
> 
> readM :: (Monad m, Read a) => String -> m a
> readM s | [x] <- parse = return x
>         | otherwise    = fail $ "Failed to parse \"" ++ s ++ "\" as a
> number."
>   where
>     parse = [x | (x,_) <- reads s]
> 
> I don't understand how line 5 works. I thought that the do notation there
> would be the same as:
> 
> main = hGetContents stdin >>= \m ->
>        mapM readM . lines $ m >>= \nums ->
>        print (sum nums) >>
>        `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++
>        show e))

Some experimentation shows that in fact, the first argument of `catch` is the
*entire* do-block.  That is, it is the same as

main = (do
  m <- hGetContents stdin
  nums <- mapM readM . lines $ m
  print (sum nums)
  )
  `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))

However, I don't understand why.  I would have thought it invalid.

Perversely, indenting the `catch` by one more space results in a valid
program with different behavior (since it only applies to the print).

-Brent



------------------------------

Message: 9
Date: Wed, 23 Nov 2011 11:15:59 +0100
From: Alexander Bernauer <alex-hask...@copton.net>
Subject: Re: [Haskell-beginners] Precedence of Infix Operators in Do
        Syntax
To: beginners@haskell.org
Message-ID: <20111123101559.GC7634@apus>
Content-Type: text/plain; charset="us-ascii"

Hi

On Tue, Nov 22, 2011 at 11:03:51PM -0500, Avery Robinson wrote:
> main = do
>   m <- hGetContents stdin
>   nums <- mapM readM . lines $ m
>   print (sum nums)
>   `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))

Using Hammar's naive do-notation desugarer [1] your example code
becomes:
---8<---
main
  = hGetContents stdin >>=
      \ m -> mapM readM . lines $ m >>= \ nums -> print (sum nums)
      `catch`
      (\ e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))
--->8---

Comparing this with "ghc -ddump-ds" (cleaned up by removing _xyz
suffixes and type annotations)
---8<---
Main.main =
  System.IO.Error.catch
    (>>=
       (GHC.IO.Handle.Text.hGetContents GHC.IO.Handle.FD.stdin)
       (\ m ->
          >>=
            (GHC.Base.$
               (GHC.Base..
                  (mapM readM)
                  Data.List.lines)
               m)
            (\ nums ->
               print_aAV (sum_aAU nums))))
    (\ e ->
       System.IO.hPutStrLn
         GHC.IO.Handle.FD.stderr
         (GHC.Base.++
            (GHC.Base.unpackCString# "couldn't sum lines: ")
            (show e)))
--->8---
confirms this. But why is that?

The section on do expressions of the Haskell report [2] explains that in
the end a do block is just an expression.

And section 3.4 [3] states that "e1 op e2 = (op) e1 e2", which in our
case translates to "e1 `catch` e2 = catch e1 e2" where e1 is the
preceeding do block and e2 is the lambda expression.

So, the line starting with `catch` is not part of the do block any more.

Greetings

Alex

[1] https://gist.github.com/1341505
[2] http://www.haskell.org/onlinereport/exps.html#sect3.14
[3] http://www.haskell.org/onlinereport/exps.html#sect3.4
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: Digital signature
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111123/986a8a20/attachment-0001.pgp>

------------------------------

Message: 10
Date: Wed, 23 Nov 2011 11:41:12 +0100
From: Alexander Bernauer <alex-hask...@copton.net>
Subject: Re: [Haskell-beginners] List comprehension question
To: Lee Short <black...@pro-ns.net>
Cc: beginners@haskell.org
Message-ID: <20111123104111.GD7634@apus>
Content-Type: text/plain; charset="us-ascii"

Hi

Daniel already gave you an answer. The details on how list comprehension
is desugared can be found in section 3.11 of the Haskell report [1].

I am just mentioning this because I really want to encourage people to
read the language standard when hitting such a question.

Not saying one shouldn't post questions here. But it typically saves
_you_ a lot of time to just read the answer up. And if the standard is
well written - which it IMO is for Haskell - you even get a complete,
concise and unambigous answer which extands your knowledge of the
language.

Greetings

Alex

[1] http://www.haskell.org/onlinereport/exps.html#sect3.11
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: Digital signature
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111123/0db34c0c/attachment.pgp>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 41, Issue 31
*****************************************

Reply via email to