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:  Removing the biggest element from a list -   maybe slow?
      (Felipe Lessa)
   2. Re:  Removing the biggest element from a list -   maybe slow?
      (Chadda? Fouch?)
   3.  Learning about channels (Benjamin Edwards)
   4. Re:  Removing the biggest element from a list -   maybe slow?
      (Daniel Fischer)
   5. Re:  Learning about channels (Daniel Fischer)
   6. Re:  Learning about channels (Benjamin Edwards)


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

Message: 1
Date: Mon, 24 May 2010 21:13:38 -0300
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Removing the biggest element from a
        list -  maybe slow?
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID: <20100525001338.gc14...@kira.casa>
Content-Type: text/plain; charset=us-ascii

On Mon, May 24, 2010 at 04:47:50PM +0200, Daniel Fischer wrote:
> remLargest :: Ord a => [a] -> [a]
> remLargest [] = []
> remLargest [_] = []
> remLargest (x:xs) = go [] x xs
>   where
>     go post _ [] = reverse post
>     go post mx (y:ys)
>         | mx < y    =  mx : reverse post ++ go [] y ys
>         | otherwise = go (y:post) mx ys

Doesn't retain the order of the list:

  removeLargest (x:xs@(_:_)) = go x xs
    where
      go x []                  = []
      go x (x2:xs) | x < x2    = x  : go x2 xs
                   | otherwise = x2 : go x  xs
  removeLargest _ = []

Traverses only once, so it is O(n).

--
Felipe.


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

Message: 2
Date: Tue, 25 May 2010 10:21:01 +0200
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Removing the biggest element from a
        list -  maybe slow?
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <aanlktimhvnxi_9f9wkhmbd-uarbev2vrjuoindusz...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Mon, May 24, 2010 at 4:01 PM, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:
> If you don't need to retain the order, you can efficiently do it with one
> traversal.
>
> withoutLargest [] = []
> withoutLargest (x:xs) = go x xs
>  where
>    go _ [] = []
>    go p (y:ys)
>      | p < y     = p : go y ys
>      | otherwise = y : go p ys
>

And to be explicit (Daniel implied that) this version is also much
more interesting from a memory point of view since it can start
producing the resulting list almost immediately, which means it can be
used as a filter in a lazy pipeline able to handle infinite or just
too big lists.

On the other hand, if you often need to perform this operation
(removal of the maximum) and don't care about the order, there are
much better data structures to do this, particularly the priority
queue. There are some good implementations of this on Hackage.

(NB : Many of those implementations only provide for removing the
minimum, but that only means that you have to change the definition of
minimum so that it be your maximum :
newtype FlipOrd a = FO a
instance (Ord a) => Ord (FO a) where
   compare (FO a) (FO b) = compare b a
)

-- 
Jedaï


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

Message: 3
Date: Tue, 25 May 2010 10:06:48 +0100
From: Benjamin Edwards <edwards.b...@googlemail.com>
Subject: [Haskell-beginners] Learning about channels
To: beginners@haskell.org
Message-ID:
        <aanlktimdtih78cgfskm3j6xuwpgsejxw6g4gojfjt...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

NB: This was posted in fa.haskell  first, I guess it was the wrong forum for
this kind of question as it was left unanswered :)

Hi,

I'm having a few issues getting some toy programs to work whilst I try
to get a better understanding of how to model processes and channels.
I am just trying to use the real base blocks and failing miserably.
Here is an example (yes this is utterly contrived and sill, but I lack
imagination... sue me):

I want my main thread to do the following:

1. make a channel
2. spawn a thread (producer) that will write a series of lists of
integers to the the channel, then exit.
3. spawn another thread that will read from the channel and sum all of
the input. It should exit when both the channel is empty and and the
producer thread has finished writing to it.
4. Main thread should print the sum.

My current code should uses a trick I have seen else where which is to
have the result of "task" running in the thread put into an MVar. So
my condition for the reading thread exiting is to check if the MVar of
the producer thread is not empty and if the channel is empty. If those
two things are true, exit the thread. Unfortunately if somehow seems
able to to get to a stage where the produce thread has finished and
the channel is empty, but is blocking on a read.

I have the following code, but it always blocks indefinitely on a
read. I am sure there is something obviously deficient with it, but I
can't work out what it is. Any help would be greatly appreciated. Of
course, if I'm doing it all wrong, please tell me that too :)

module Main
  where

import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad (forever)
import Data.Map as M

main :: IO ()
main = do oc <- newChan
          counter <- newTVarIO (0 :: Integer)
          p <- forkJoin $ produce oc [1..1000]
          c <- forkJoin $ loop oc p counter
          takeMVar c >>= print

produce :: Chan [Integer] -> [Integer] -> IO ()
produce ch [] = return ()
produce ch xs = do let (hs,ts) = splitAt 100 xs
                   writeChan ch hs
                   produce ch ts

loop :: Chan [Integer] -> MVar () -> TVar Integer -> IO Integer
loop ch p n = do f <- isEmptyMVar p
                 e <- isEmptyChan ch
                 if e && (not f)
                   then atomically (readTVar n)
                   else do xs <- readChan ch
                           atomically $ do x <- readTVar n
                                           writeTVar n (x + sum xs)
                           loop ch p n
forkJoin :: IO a -> IO (MVar a)
forkJoin task = do mv <- newEmptyMVar
                   forkIO (task >>= putMVar mv)
                   return mv
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100525/d8a11c85/attachment-0001.html

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

Message: 4
Date: Tue, 25 May 2010 11:29:40 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Removing the biggest element from a
        list -  maybe slow?
To: beginners@haskell.org
Message-ID: <201005251129.40447.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Tuesday 25 May 2010 10:21:01, Chaddaï Fouché wrote:
> On Mon, May 24, 2010 at 4:01 PM, Daniel Fischer
>
> <daniel.is.fisc...@web.de> wrote:
> > If you don't need to retain the order, you can efficiently do it with
> > one traversal.
> >
> > withoutLargest [] = []
> > withoutLargest (x:xs) = go x xs
> >  where
> >    go _ [] = []
> >    go p (y:ys)
> >      | p < y     = p : go y ys
> >      | otherwise = y : go p ys
>
> And to be explicit (Daniel implied that) this version is also much
> more interesting from a memory point of view since it can start
> producing the resulting list almost immediately, which means it can be
> used as a filter in a lazy pipeline able to handle infinite or just
> too big lists.
>
> On the other hand, if you often need to perform this operation
> (removal of the maximum) and don't care about the order, there are
> much better data structures to do this, particularly the priority
> queue. There are some good implementations of this on Hackage.

Yes. Very much yes.
Unless you need to perform this operation really 
often but never (or almost never) need to insert new values. 
Then sortBy (flip compare) once and repeatedly tail afterwards may be 
even better than a priority queue.

>
> (NB : Many of those implementations only provide for removing the
> minimum, but that only means that you have to change the definition of
> minimum so that it be your maximum :
> newtype FlipOrd a = FO a
> instance (Ord a) => Ord (FO a) where
>    compare (FO a) (FO b) = compare b a
> )




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

Message: 5
Date: Tue, 25 May 2010 12:00:40 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Learning about channels
To: beginners@haskell.org
Message-ID: <201005251200.40948.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Tuesday 25 May 2010 11:06:48, Benjamin Edwards wrote:
> NB: This was posted in fa.haskell  first, I guess it was the wrong forum
> for this kind of question as it was left unanswered :)
>
> Hi,
>
> I'm having a few issues getting some toy programs to work whilst I try
> to get a better understanding of how to model processes and channels.
> I am just trying to use the real base blocks and failing miserably.
> Here is an example (yes this is utterly contrived and sill, but I lack
> imagination... sue me):
>
> I want my main thread to do the following:
>
> 1. make a channel
> 2. spawn a thread (producer) that will write a series of lists of
> integers to the the channel, then exit.
> 3. spawn another thread that will read from the channel and sum all of
> the input. It should exit when both the channel is empty and and the
> producer thread has finished writing to it.
> 4. Main thread should print the sum.
>
> My current code should uses a trick I have seen else where which is to
> have the result of "task" running in the thread put into an MVar.

That's good.

> So my condition for the reading thread exiting is to check if the MVar of
> the producer thread is not empty and if the channel is empty. If those
> two things are true, exit the thread. Unfortunately if somehow seems
> able to to get to a stage where the produce thread has finished and
> the channel is empty, but is blocking on a read.

I think it gets to the state where the channel is empty but the produce 
thread hasn't finished yet.

>
> I have the following code, but it always blocks indefinitely on a
> read. I am sure there is something obviously deficient with it, but I
> can't work out what it is. Any help would be greatly appreciated. Of
> course, if I'm doing it all wrong, please tell me that too :)
>
> module Main
>   where
>
> import Control.Concurrent
> import Control.Concurrent.STM
> import Control.Monad (forever)
> import Data.Map as M
>
> main :: IO ()
> main = do oc <- newChan
>           counter <- newTVarIO (0 :: Integer)
>           p <- forkJoin $ produce oc [1..1000]
>           c <- forkJoin $ loop oc p counter
>           takeMVar c >>= print
>
> produce :: Chan [Integer] -> [Integer] -> IO ()
> produce ch [] = return ()
> produce ch xs = do let (hs,ts) = splitAt 100 xs
>                    writeChan ch hs
>                    produce ch ts
>
> loop :: Chan [Integer] -> MVar () -> TVar Integer -> IO Integer
> loop ch p n = do f <- isEmptyMVar p
>                  e <- isEmptyChan ch
>                  if e && (not f)
>                    then atomically (readTVar n)

Sorry for the ugly layout:


                   else do
                     if e then yield
                        else
                        do xs <- readChan ch
                           atomically $ do x <- readTVar n
                                           writeTVar n (x 
+ sum xs)
                     loop ch p n

The point is, if the channel is empty, but the producer has not yet 
finished, don't try to read from the channel (that wouldn't work then), but 
give the producer the chance to produce the next chunk.
Since thread-switching happens on allocation, don't just jump to the next 
iteration of the loop, but tell the thread manager "I have nothing to do at 
the moment, you can let somebody else run for a while".

I have encountered cases where yield didn't work reliably (no idea whether 
that was my fault or the compiler's, but "threadDelay 0" instead of yield 
worked reliably).


>                    else do xs <- readChan ch
>                            atomically $ do x <- readTVar n
>                                            writeTVar n (x + sum xs)
>                            loop ch p n



> forkJoin :: IO a -> IO (MVar a)
> forkJoin task = do mv <- newEmptyMVar
>                    forkIO (task >>= putMVar mv)
>                    return mv



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

Message: 6
Date: Tue, 25 May 2010 11:33:21 +0100
From: Benjamin Edwards <edwards.b...@googlemail.com>
Subject: Re: [Haskell-beginners] Learning about channels
To: beginners@haskell.org
Message-ID:
        <aanlktinw_bcbowif-zmly1satmjy4auexbccwqe8k...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On 25 May 2010 11:00, Daniel Fischer <daniel.is.fisc...@web.de> wrote:

> Sorry for the ugly layout:
>
>
>                    else do
>                     if e then yield
>                         else
>                        do xs <- readChan ch
>                            atomically $ do x <- readTVar n
>                                            writeTVar n (x + sum xs)
>                     loop ch p n
>
> The point is, if the channel is empty, but the producer has not yet
> finished, don't try to read from the channel (that wouldn't work then), but
> give the producer the chance to produce the next chunk.
> Since thread-switching happens on allocation, don't just jump to the next
> iteration of the loop, but tell the thread manager "I have nothing to do at
> the moment, you can let somebody else run for a while".
>
> I have encountered cases where yield didn't work reliably (no idea whether
> that was my fault or the compiler's, but "threadDelay 0" instead of yield
> worked reliably).
>
> This is where I was getting it all  horribly wrong. I assumed that while
the loop thread blocked, the other thread would happily carry on producing
work. Is there anything I can read to get a better understanding of how the
haskell runtime manages these switches? Or is it the OS that takes care of
this..?

Here is my new function, with the a call to yield inserted :)

loop :: Chan [Integer] -> MVar () -> TVar Integer -> IO Integer
loop ch p n = do f <- isEmptyMVar p
                 e <- isEmptyChan ch
                 if not f
                   then atomically (readTVar n)
                   else
                     if e then yield >> loop ch p n

                          else do xs <- readChan ch
                                  atomically $ do x <- readTVar n
                                                  writeTVar n (x + sum xs)
                                  loop ch p n

Thanks for your help!

Ben
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100525/3aed13eb/attachment.html

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

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


End of Beginners Digest, Vol 23, Issue 38
*****************************************

Reply via email to