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: question on layout (Maur??cio)
   2. Re:  Re: question on layout (Daniel Fischer)
   3. Re:  map increases length of list (Aai)
   4.  Re: question on layout (Maur??cio)
   5. Re:  map increases length of list (Brent Yorgey)
   6. Re:  Modifications inside a Reader? (Brent Yorgey)
   7. Re:  Modifications inside a Reader? (Brian Troutwine)
   8. Re:  Re: question on layout (George Huber)
   9. Re:  Re: question on layout (Brent Yorgey)


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

Message: 1
Date: Thu, 18 Jun 2009 11:43:06 -0300
From: Maur??cio <briqueabra...@yahoo.com>
Subject: [Haskell-beginners] Re: question on layout
To: beginners@haskell.org
Message-ID: <h1djpq$s9...@ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

> (1) what was the driving force behind using white-space to denote code 
> blocks?  From a beginners perspective (especially coming from a strong C 
> / C++ background) this seems to add to the learning curve for the 
> language, and can add a good deal of frustration.

This seems to be personal. Most people in the list seems to
find layout easier to write and read (although we could make
a case that those who don't just leave Haskell).

I wasn't able to write anything in Haskell until I read the
Haskell 98 report and learned how to use braces and semicolons
(and this was my last attempt before just leaving the language).
After you learn it, using layout becomes a lot easier, and the
whole language makes a lot more sense.

If you wan't to start a page in Haskell wiki with a reference
to layout-free Haskell syntax I would be happy to contribute.

Best,
Maurício



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

Message: 2
Date: Thu, 18 Jun 2009 16:55:53 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: question on layout
To: beginners@haskell.org
Message-ID: <200906181655.53197.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Donnerstag 18 Juni 2009 16:43:06 schrieb Maurí­cio:
> If you want to start a page in Haskell wiki with a reference
> to layout-free Haskell syntax I would be happy to contribute.
>
> Best,
> Maurício

Since you have some experience with it, why don't you start the page to lead 
newbies from 
C++-land in? You hopefully remember a few things that were especially hard to 
learn for 
you, that could probably help a lot.


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

Message: 3
Date: Thu, 18 Jun 2009 17:32:26 +0200
From: Aai <brady...@xs4all.nl>
Subject: Re: [Haskell-beginners] map increases length of list
To: beginners@haskell.org
Message-ID: <4a3a5e0a.4070...@xs4all.nl>
Content-Type: text/plain; charset=ISO-8859-15

Check this out:

Prelude> [0,60..330]::[Double]
[0.0,60.0,120.0,180.0,240.0,300.0,360.0]

Prelude> [0,60..329]::[Double]
[0.0,60.0,120.0,180.0,240.0,300.0]

It looks like the decision the step to the next value in case of flt.
point enumeration depends on >= enumWith / 2. But that should be
answered by those who know from under the hood.

-- 
Met vriendelijke groet,
=@@i



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

Message: 4
Date: Thu, 18 Jun 2009 14:20:39 -0300
From: Maur??cio <briqueabra...@yahoo.com>
Subject: [Haskell-beginners] Re: question on layout
To: beginners@haskell.org
Message-ID: <h1dt17$ug...@ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

>> If you want to start a page in Haskell wiki with a reference
>> to layout-free Haskell syntax I would be happy to contribute.

> Since you have some experience with it, why don't you start
 > the page to lead newbies from C++-land in? You hopefully
 > remember a few things that were especially hard to learn for
> you, that could probably help a lot.

I tought about that, but you're the first one to actually agree
with me about that :) Now I would not like to start something I
know I won't take care of, since I do take care of other stuff.
But I can add stuff if somebody else does. Note that it would
be great if instead of just a layout free reference we had
a full common language version of the technical Haskell 98
specification. If you are learning Haskell, doing that can be
really great as a learning tool:

http://haskell.org/onlinereport

Many words and explanations seen there are important to
understand today version of Haskell, and most are not well
explained by tutorials. You won't find about "kinds" in most
tutorials, for instance, and they are really important.


Here is a small reference (improvised, not checked, and 'classes'
and their instances are important and missing):

* How to write modules. Today, all Haskell compilers
needs you to write only one module per file:

module Name.OtherName (export_list) where {

declarations separate by ';'

}

declarations may be imports (and those come first than
all others):

import ModuleName.SubModule qualified as W ;
import OtherModule ;
etc.

export_list lists all names you want to be seen by other
modules that import Name.OtherName. (This requires further
details.) If you are writing module Main, which all
applications are required to have, you need to export at
least 'main'.

* 'do' notation

do { x ; y'<- y ; z' <- z y' ; a }

expands to

x >> y >>= \y' -> z y' >>= \z' -> a

Also, using layout,

do
      a <- x
      let b = a
      y b
      z

expands to

do {a <- x ; let {b = a} in do {y b >> z}}

and then to

x >>= \a -> let {b=a} in y b >> z



* Using '::'

You can declare types for names using :: like:

a :: IO ()
b :: Integer

(Needs a lot of further details.)

These appear in declarations list of modules:

module Bla (ble) where {
   import SomeModule ; ble :: Integer ; ble = 3
}


* Using 'data'

You can declare data types as:

data DataName = Constructor1 Integer | Cons2 String
     | Cons3 Integer String DataName


* Using '=' and pattern matching

A somewhat general usage of '=' can be seen as (using
that data type from previous item):

f :: SomeType -> DataName -> Bool

  ;

f (Constructor a b) c = case c of {
     Constructor1 i
          | h i -> True
          | True -> False where { h :: Integer -> Bool ; h = (>= 10) }

       ;

     Cons2 s | matches s -> True | otherwise -> False

       ;

     Cons3 j _ = j >= k

} where { k :: Integer ; k = 5 }


* Using 'let' and 'where'

'let' is different from 'where'. You can do:

a = (let {b=5} in b + b) + (let {b=6;c=7} in b + c)

but not

a = (b + b where {b=5}) etc. (WRONG!!)

'where' is part of '=':

a = b 9
   where {b :: Integer -> String ; b 10 = "Equals ten." ; b _ = "Does not equal 
ten."}


* Lazy evaluation:

b :: Integer -> String ;

b 10 = "Ten" ;

b 9 = "Nine" ;

func :: (Integer -> String) -> String ;

func f = "Prefix" ++ f 8


Here, 'take 2 (func b)' (or 'take 2 $ func b')
would evaluate to "Pr" dispite 'b 8' beeing undefined,
because 'f 8' is not necessary to evaluate just the first
two characters of that string.

Hope this gives you some help, and contains only a few errors.

Best,
Maurício



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

Message: 5
Date: Thu, 18 Jun 2009 14:17:31 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] map increases length of list
To: beginners@haskell.org
Message-ID: <20090618181731.ga4...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Thu, Jun 18, 2009 at 05:32:26PM +0200, Aai wrote:
> Check this out:
> 
> Prelude> [0,60..330]::[Double]
> [0.0,60.0,120.0,180.0,240.0,300.0,360.0]
> 
> Prelude> [0,60..329]::[Double]
> [0.0,60.0,120.0,180.0,240.0,300.0]
> 
> It looks like the decision the step to the next value in case of flt.
> point enumeration depends on >= enumWith / 2. But that should be
> answered by those who know from under the hood.

That is correct.  The reason for this is because of the inaccuracy of
floating point numbers.  For example, consider

  [0.1,0.2..10.0]

which clearly ought to contain 100 numbers, every tenth from 0.1
through 10.0 inclusive. But 0.1 cannot be represented exactly in
binary, so adding 0.1 to itself 100 times might very well give a
result like 10.0000000002.  Should this be included in the range, or
not?  After all, it's bigger than 10.0...but it would be quite
surprising if the 10.0000000002 were left out.  Hence the last number
is included even if it is up to 1/2 of a step over the end value of
the range.  But this can also be surprising at times (as the original
poster found out!).  What to do?

The answer is: don't use list enumerations for floating point
numbers!!  It is nonsensical.  Alternative options include:

  * use Rational instead of Double, which IS exact
  * use Integers for the enumeration, and then convert to Double

and so on.

-Brent


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

Message: 6
Date: Thu, 18 Jun 2009 14:25:53 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Modifications inside a Reader?
To: beginners@haskell.org
Message-ID: <20090618182553.gb4...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Wed, Jun 17, 2009 at 08:32:53PM -0700, Brian Troutwine wrote:
> Hello all.
> 
> I'm writing a UDP echo server, full source given below. The current
> implementation echoes back the "payload" of every incoming message but
> I would prefer that only unique payloads be echoed back. To that end
> I've started in with Data.BloomFilter but am not sure how to update it
> accordingly. I imagine that Reader is probably the wrong monad to be
> using though I'm unsure how I might modify my program to use State.
> Could someone lead me along a bit?
> 
> Also, any general comments on the style of my program?

Looks nice.  Changing your program to use 'State' instead of 'Reader'
(which is indeed the wrong monad if you want to update) should be a
piece of cake!

> type Echo = StateT Globals IO

Now you should use 'gets' instead of 'asks':

> run :: Echo ()
> run = forever $ do
>   s <- gets socketG
>   ...

Then you'll probably want a little utility function for updating the
Bloom filter, like this:

> modifyBloom :: (Bloom Bytestring -> Bloom Bytestring) -> Echo ()
> modifyBloom f = modify (\s -> s { bloomF = f (bloomF s) })

('modify' is another State method; the ugliness and repetition in
evidence above is because of the unwieldy record-update syntax, which
is exactly why you want a helper function =).

Now you can use 'modifyBloom f' as an Echo () action which applies the
transformation f to the current Bloom filter.  And that's all!

-Brent


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

Message: 7
Date: Thu, 18 Jun 2009 20:58:47 -0700
From: Brian Troutwine <goofyheadedp...@gmail.com>
Subject: Re: [Haskell-beginners] Modifications inside a Reader?
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <971980cc0906182058u604d92frd66fdfdf3760e...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thanks so much! I've taken your suggestions, expanded on them and come
up with the code below. It is no no longer an echo server, but instead
is pretty close to the in-memory priority queue daemon I need. Anyway,
it's included below for completness' sake.

If anyone has comments (or questions, at this point) I'd be happy to hear them.

Brian

--

{-# LANGUAGE OverloadedStrings #-}
import Prelude hiding (putStrLn, catch, show, print)
import Network.Socket hiding (send, sendTo, recv, recvFrom)
import Network.Socket.ByteString
import Data.ByteString.Char8 hiding (head, singleton, empty)
import Control.Monad.State.Strict
import Control.Monad (forever)
import Control.Exception (bracket)
import Data.BloomFilter
import Data.BloomFilter.Easy
import Data.BloomFilter.Hash (cheapHashes)
import Data.PSQueue

type PrioQueue = PSQ ByteString Int
data Globals = Globals {
      socketG :: Socket
    , bloomF  :: !(Bloom ByteString)
    , prioQ   :: !(PrioQueue)
    }

type Echo = StateT Globals IO

run :: Echo ()
run = forever $ do
  sock <- gets socketG
  (msg, addr) <- liftIO $ recvFrom sock 1024
  let [op, priority, _category, payload] = split ':' msg
  bloom <- gets bloomF
  pQ    <- gets prioQ
  liftIO $ putStrLn op
  case op of
    "Get" ->
        case findMin pQ of
          Nothing -> return () -- Client will just timeout.
          Just qData -> liftIO $ sendTo sock (key qData) addr >> return ()
    "Put" ->
        case elemB payload bloom of
          True  -> return ()
          False -> modifyBloom (insertB payload)
                   >> modifyPrioQ (insert payload pri)
            where
              pri = (read . unpack) priority
    _ -> return () -- Client will just timeout.

modifyBloom :: (Bloom ByteString -> Bloom ByteString) -> Echo ()
modifyBloom f = modify (\s -> s { bloomF = f (bloomF s) })

modifyPrioQ :: (PrioQueue -> PrioQueue) -> Echo ()
modifyPrioQ f = modify (\s -> s { prioQ = f (prioQ s) })

main :: IO ()
main = bracket build disconnect loop
  where
    disconnect = sClose . socketG
    loop st    = runStateT run st >> return ()

build :: IO Globals
build = do
  addrinfos <- getAddrInfo
               (Just (defaultHints {addrFlags = [AI_PASSIVE]}))
               Nothing (Just "1514")
  let serveraddr = head addrinfos
  sock <- socket (addrFamily serveraddr) Datagram defaultProtocol
  bindSocket sock (addrAddress serveraddr)
  return $ Globals sock (emptyB (cheapHashes 10) 16777216) empty

On Thu, Jun 18, 2009 at 11:25 AM, Brent Yorgey<byor...@seas.upenn.edu> wrote:
> On Wed, Jun 17, 2009 at 08:32:53PM -0700, Brian Troutwine wrote:
>> Hello all.
>>
>> I'm writing a UDP echo server, full source given below. The current
>> implementation echoes back the "payload" of every incoming message but
>> I would prefer that only unique payloads be echoed back. To that end
>> I've started in with Data.BloomFilter but am not sure how to update it
>> accordingly. I imagine that Reader is probably the wrong monad to be
>> using though I'm unsure how I might modify my program to use State.
>> Could someone lead me along a bit?
>>
>> Also, any general comments on the style of my program?
>
> Looks nice.  Changing your program to use 'State' instead of 'Reader'
> (which is indeed the wrong monad if you want to update) should be a
> piece of cake!
>
>> type Echo = StateT Globals IO
>
> Now you should use 'gets' instead of 'asks':
>
>> run :: Echo ()
>> run = forever $ do
>>   s <- gets socketG
>>   ...
>
> Then you'll probably want a little utility function for updating the
> Bloom filter, like this:
>
>> modifyBloom :: (Bloom Bytestring -> Bloom Bytestring) -> Echo ()
>> modifyBloom f = modify (\s -> s { bloomF = f (bloomF s) })
>
> ('modify' is another State method; the ugliness and repetition in
> evidence above is because of the unwieldy record-update syntax, which
> is exactly why you want a helper function =).
>
> Now you can use 'modifyBloom f' as an Echo () action which applies the
> transformation f to the current Bloom filter.  And that's all!
>
> -Brent
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 8
Date: Sat, 20 Jun 2009 11:44:09 -0400
From: George Huber <geohu...@verizon.net>
Subject: Re: [Haskell-beginners] Re: question on layout
To: beginn...@haskell.org.
Message-ID: <4a3d03c9.8040...@verizon.net>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Maurí­cio wrote:
> Also, using layout,
>
> do
>      a <- x
>      let b = a
>      y b
>      z
>
> expands to
>
> do {a <- x ; let {b = a} in do {y b >> z}}
>
I'm curious as to where the second `do' came from?

> and then to
>
> x >>= \a -> let {b=a} in y b >> z
>



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

Message: 9
Date: Sat, 20 Jun 2009 12:05:36 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Re: question on layout
To: beginners@haskell.org
Message-ID: <20090620160536.ga32...@seas.upenn.edu>
Content-Type: text/plain; charset=iso-8859-1

On Sat, Jun 20, 2009 at 11:44:09AM -0400, George Huber wrote:
> Maurí­cio wrote:
>> Also, using layout,
>>
>> do
>>      a <- x
>>      let b = a
>>      y b
>>      z
>>
>> expands to
>>
>> do {a <- x ; let {b = a} in do {y b >> z}}
>>
> I'm curious as to where the second `do' came from?

Well, the above translation isn't quite correct, the second 'do'
wouldn't come until later.  The point is that 'do { let x = y; foo }'
translates to 'let x = y in do { foo }'.  So

do
  a <- x
  let b = a
  y b
  z

gets translated as follows:

  do { a <- x ; let b = a ; y b ; z }

(that's just inserting braces and semicolons using layout), and then

  x >>= \a -> do { let b = a ; y b ; z }

  x >>= \a -> let b = a in do { y b ; z }

  x >>= \a -> let b = a in yb >> do { z }

  x >>= \a -> let b = a in yb >> z


-Brent


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

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


End of Beginners Digest, Vol 12, Issue 9
****************************************

Reply via email to