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: defining 'init' in terms of 'foldr' (Heinrich Apfelmus)
   2. Re:  defining 'init' in terms of 'foldr' (Daniel Fischer)
   3.  The main thread and waiting for other threads (Thomas Friedrich)
   4. Re:  The main thread and waiting for other threads
      (Daniel Fischer)
   5. Re:  The main thread and waiting for other threads
      (Rafael Gustavo da Cunha Pereira Pinto)
   6. Re:  The main thread and waiting for other threads (Quentin Moser)
   7.  International Summer School on Advances in Programming
      Languages (precedes ICFP'09) (Janis Voigtlaender)


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

Message: 1
Date: Tue, 12 May 2009 13:31:32 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: defining 'init' in terms of 'foldr'
To: beginners@haskell.org
Message-ID: <gubmmi$r4...@ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1

Michael Mossey wrote:
> In S. Thompson's book, problem 9.13 asks us to define 'init' in terms of
> foldr. I was baffled at first because I didn't see a natural way to do
> this. It would look something like
> 
> init xs = foldr f initialValue xs
> 
> where f would cons on each character except the rightmost.
> 
> f <when passed rightmost char> b = []
> f <when passed any other char a> b = a : b
> 
> How does f "know" when it is passed the first character? initialValue
> has to signal this somehow. On #haskell, one person suggested doing it
> with some post-processing:
> 
> init xs = snd $ foldr f (True,[]) xs
>   where f _  (True,_)  = (False,[])
>         f a  (False,b) = (False,a:b)
> 
> I had an idea. If the initial value is the entire list, then its length
> can function as the "signal" that we are dealing with the rightmost
> char. This requires no post-processing:
> 
> init xs = foldr f xs xs
>    where f a b | length b == length xs = []
>                | otherwise = a:b
> 
> These seem contrived. I wonder if there is a more natural solution that
> Thompson had in mind. Any comments?

It is best to see  foldr f b  as an operation that takes a list

  x0 : x1 : x2 : ... : []

and replaces every (:) with  f  and the [] with  b :

  x0 `f` x1 `f` x2 `f` ... `f` b

See also

  http://en.wikipedia.org/wiki/Fold_(higher-order_function)

for Cale's nice pictures.


It is then clear that we have to choose  b  to signal the end of the
list. Furthermore,  b  should be the same as  init [] . Unfortunately,
this expression is a run-time error, but this is a fault of the type
signature

  init :: [a] -> [a]

which should really be

  init' :: [a] -> Maybe [a]

to make it clear that some lists like the empty one simply don't have an
initial segment. And this version has a natural implementation in terms
of  foldr :

  init' = foldr f Nothing
     where
     f _ Nothing   = Just []
     f x (Just xs) = Just (x:xs)

Of course, we need some post-processing to obtain the original  init
from this, but I think that it's very natural.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



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

Message: 2
Date: Tue, 12 May 2009 14:27:30 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] defining 'init' in terms of 'foldr'
To: beginners@haskell.org
Message-ID: <200905121427.30834.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Montag 11 Mai 2009 16:13:36 schrieb Michael Mossey:
> In S. Thompson's book, problem 9.13 asks us to define 'init' in terms of
> foldr.

Check the thread starting at 
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009562.html
That contains several interesting approaches, though I don't think any of those 
was lazy 
enough to deal with infinite lists.

> I was baffled at first because I didn't see a natural way to do this.
> It would look something like
>
> init xs = foldr f initialValue xs

Since

*FoldInit> init []
*** Exception: Prelude.init: empty list

initialValue has to be (error "Prelude.init: empty list") if you don't do any 
post-
processing. But then
init [1] = f 1 (error "...")
must be [], so f can't inspect its second argument (or it would return _|_ 
instead of []), 
but then you can't make init [1] = f 1 (error "...") return [] and also 
init [1,2] = f 1 (f 2 (error "...")) return [1].

So some post-processing is necessary.

>
> where f would cons on each character except the rightmost.
>
> f <when passed rightmost char> b = []
> f <when passed any other char a> b = a : b
>
> How does f "know" when it is passed the first character? initialValue has
> to signal this somehow. On #haskell, one person suggested doing it with
> some post-processing:
>
> init xs = snd $ foldr f (True,[]) xs
>    where f _  (True,_)  = (False,[])
>          f a  (False,b) = (False,a:b)

That gives init [] = [], which is not correct.
The starting value must be (True, error "...").
It doesn't work on infinite lists, and will produce a stack overflow on 
sufficiently long 
lists. The problem is that pattern matching is strict, so to determine which 
brach to take 
in

f 1 (init [2 .. n])

we must know whether the first component of init [2 .. n] is True or False. So 
we must 
look at f 2 (init [3 .. n]), same problem there... Before *anything* of the 
overall result 
can be determined, the whole list has to be traversed.

We can fix these issues by making it lazier:

vinit = snd . foldr f (True, error "Prelude.init: empty list")
      where
        f x y = (False, if fst y then [] else x:snd y)

Here, the first component of f's result is determined before looking at f's 
arguments, 
thus to determine which branch to take in the second component, all that has to 
be done is 
check if y comes from an application of f or the initial value.
Works for infinite lists, errors on empty lists, specs fulfilled.


>
> I had an idea. If the initial value is the entire list, then its length can
> function as the "signal" that we are dealing with the rightmost char. This
> requires no post-processing:
>
> init xs = foldr f xs xs
>     where f a b | length b == length xs = []
>
>                 | otherwise = a:b
>

That gives init [] = [], doesn't work on infinite lists and is badly 
inefficient.
To fix at least two of these issues, you must do some post-processing, but that 
would lead 
again to something like above.

> These seem contrived. I wonder if there is a more natural solution that
> Thompson had in mind. Any comments?
>
> -Mike
>



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

Message: 3
Date: Tue, 12 May 2009 12:27:06 -0400
From: Thomas Friedrich <i...@suud.de>
Subject: [Haskell-beginners] The main thread and waiting for other
        threads
To: beginners@haskell.org
Message-ID: <4a09a35a.3020...@suud.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi everyone,

I have a problem with the following example in the Real World Haskell 
book, which aims to develop a module for controlling different threads. See,

http://book.realworldhaskell.org/read/concurrent-and-multicore-programming.html

in the chapter "The main thread and waiting for other threads".

-- file: ch24/NiceFork.hs
import Control.Concurrent
import Control.Exception (Exception, try)
import qualified Data.Map as M

data ThreadStatus = Running
                  | Finished         -- terminated normally
                  | Threw Exception  -- killed by uncaught exception
                    deriving (Eq, Show)

-- | Create a new thread manager.
newManager :: IO ThreadManager

-- | Create a new managed thread.
forkManaged :: ThreadManager -> IO () -> IO ThreadId

-- | Immediately return the status of a managed thread.
getStatus :: ThreadManager -> ThreadId -> IO (Maybe ThreadStatus)

-- | Block until a specific managed thread terminates.
waitFor :: ThreadManager -> ThreadId -> IO (Maybe ThreadStatus)

-- | Block until all managed threads terminate.
waitAll :: ThreadManager -> IO ()

When I run this through ghci I get the following failure:

[1 of 1] Compiling NiceFork         ( NiceFork.hs, interpreted )

NiceFork.hs:17:26:
    Class `Exception' used as a type
    In the type `Exception'
    In the data type declaration for `ThreadStatus'
Failed, modules loaded: none.


Any idea on how to solve this?  Exception is a class not a type, so what 
to put there instead?

Cheers,
Thomas




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

Message: 4
Date: Tue, 12 May 2009 23:57:15 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] The main thread and waiting for other
        threads
To: beginners@haskell.org
Message-ID: <200905122357.16244.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Dienstag 12 Mai 2009 18:27:06 schrieb Thomas Friedrich:
> Hi everyone,
>
> I have a problem with the following example in the Real World Haskell
> book, which aims to develop a module for controlling different threads.
> See,
>
> http://book.realworldhaskell.org/read/concurrent-and-multicore-programming.
>html
>
> in the chapter "The main thread and waiting for other threads".
> When I run this through ghci I get the following failure:
>
> [1 of 1] Compiling NiceFork         ( NiceFork.hs, interpreted )
>
> NiceFork.hs:17:26:
>     Class `Exception' used as a type
>     In the type `Exception'
>     In the data type declaration for `ThreadStatus'
> Failed, modules loaded: none.
>

The book was written in the times of GHC 6.8.*, when Exception was a type.
In GHC 6.10, it became a class because it was considered a bad idea to catch 
general 
exceptions, one should use adequate handlers for specific exceptions instead.
Of course, that broke some code out there.

>
> Any idea on how to solve this?  Exception is a class not a type, so what
> to put there instead?

For those who want to catch general exceptions, there is

data SomeException = forall e . Exception e => SomeException e

in Control.Exception, which should be roughly equivalent to the old Exception 
type.
So replace Exception with SomeException in ThreadStatus, perhaps insert a few 
calls to 
toException in the appropriate places (the compiler will help you find them) 
and it should 
work.

>
> Cheers,
> Thomas
>

Cheers,
Daniel




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

Message: 5
Date: Tue, 12 May 2009 19:04:31 -0300
From: Rafael Gustavo da Cunha Pereira Pinto
        <rafaelgcpp.li...@gmail.com>
Subject: Re: [Haskell-beginners] The main thread and waiting for other
        threads
To: Thomas Friedrich <i...@suud.de>
Cc: beginners@haskell.org
Message-ID:
        <351ff25e0905121504u4b5763ffrde45c7ee76d27...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

The problem is that Exception is a class. You should use SomeException,
which is a type!




On Tue, May 12, 2009 at 13:27, Thomas Friedrich <i...@suud.de> wrote:

> Hi everyone,
>
> I have a problem with the following example in the Real World Haskell book,
> which aims to develop a module for controlling different threads. See,
>
>
> http://book.realworldhaskell.org/read/concurrent-and-multicore-programming.html
>
> in the chapter "The main thread and waiting for other threads".
>
> -- file: ch24/NiceFork.hs
> import Control.Concurrent
> import Control.Exception (Exception, try)
> import qualified Data.Map as M
>
> data ThreadStatus = Running
>                 | Finished         -- terminated normally
>                 | Threw Exception  -- killed by uncaught exception
>                   deriving (Eq, Show)
>
> -- | Create a new thread manager.
> newManager :: IO ThreadManager
>
> -- | Create a new managed thread.
> forkManaged :: ThreadManager -> IO () -> IO ThreadId
>
> -- | Immediately return the status of a managed thread.
> getStatus :: ThreadManager -> ThreadId -> IO (Maybe ThreadStatus)
>
> -- | Block until a specific managed thread terminates.
> waitFor :: ThreadManager -> ThreadId -> IO (Maybe ThreadStatus)
>
> -- | Block until all managed threads terminate.
> waitAll :: ThreadManager -> IO ()
>
> When I run this through ghci I get the following failure:
>
> [1 of 1] Compiling NiceFork         ( NiceFork.hs, interpreted )
>
> NiceFork.hs:17:26:
>   Class `Exception' used as a type
>   In the type `Exception'
>   In the data type declaration for `ThreadStatus'
> Failed, modules loaded: none.
>
>
> Any idea on how to solve this?  Exception is a class not a type, so what to
> put there instead?
>
> Cheers,
> Thomas
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090512/013e3853/attachment-0001.html

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

Message: 6
Date: Wed, 13 May 2009 08:47:41 +0200
From: Quentin Moser <quentin.mo...@unifr.ch>
Subject: Re: [Haskell-beginners] The main thread and waiting for other
        threads
To: beginners@haskell.org
Message-ID: <20090513084741.76120...@unifr.ch>
Content-Type: text/plain; charset=US-ASCII

As Daniel Fischer already wrote, this is due to an API change in GHC
6.10. But the old exceptions interface is still available as
Control.OldException; you can simply import that instead of
Control.Exception.

On Tue, 12 May 2009 12:27:06 -0400
Thomas Friedrich <i...@suud.de> wrote:

> Hi everyone,
> 
> I have a problem with the following example in the Real World Haskell 
> book, which aims to develop a module for controlling different
> threads. See,
> 
> http://book.realworldhaskell.org/read/concurrent-and-multicore-programming.html
> 
> in the chapter "The main thread and waiting for other threads".
> 
> -- file: ch24/NiceFork.hs
> import Control.Concurrent
> import Control.Exception (Exception, try)
> import qualified Data.Map as M
> 
> data ThreadStatus = Running
>                   | Finished         -- terminated normally
>                   | Threw Exception  -- killed by uncaught exception
>                     deriving (Eq, Show)
> 
> -- | Create a new thread manager.
> newManager :: IO ThreadManager
> 
> -- | Create a new managed thread.
> forkManaged :: ThreadManager -> IO () -> IO ThreadId
> 
> -- | Immediately return the status of a managed thread.
> getStatus :: ThreadManager -> ThreadId -> IO (Maybe ThreadStatus)
> 
> -- | Block until a specific managed thread terminates.
> waitFor :: ThreadManager -> ThreadId -> IO (Maybe ThreadStatus)
> 
> -- | Block until all managed threads terminate.
> waitAll :: ThreadManager -> IO ()
> 
> When I run this through ghci I get the following failure:
> 
> [1 of 1] Compiling NiceFork         ( NiceFork.hs, interpreted )
> 
> NiceFork.hs:17:26:
>     Class `Exception' used as a type
>     In the type `Exception'
>     In the data type declaration for `ThreadStatus'
> Failed, modules loaded: none.
> 
> 
> Any idea on how to solve this?  Exception is a class not a type, so
> what to put there instead?
> 
> Cheers,
> Thomas
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

Message: 7
Date: Wed, 13 May 2009 10:45:26 +0200
From: Janis Voigtlaender <vo...@tcs.inf.tu-dresden.de>
Subject: [Haskell-beginners] International Summer School on Advances
        in Programming Languages (precedes ICFP'09)
To: beginners@haskell.org
Message-ID: <4a0a88a6.2090...@tcs.inf.tu-dresden.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Potential participants of the below summer school should pre-register
their interest now. The organizers need that information to go ahead
with the planning.

=====================================================================

   International Summer School on Advances in Programming Languages
                        25th-28th August, 2009
             Heriot-Watt University, Edinburgh, Scotland
               http://www.macs.hw.ac.uk/~greg/ISS-AiPL


Overview
~~~~~~~~

This four-day residential International Summer School on Advances in
Programming Languages has a major theme of Concurrency, Distribution,
and Multicore. Intended primarily for postgraduate research students,
the School offers lectures and practical sessions on an engaging blend
of cutting edge theoretical and practical techniques from
international experts.

The Summer School is supported by the Scottish Informatics and
Computer Science Alliance (http://www.sicsa.ac.uk/), a Scottish
Funding Council Research Pool. Participants from SICSA member
institutions may attend at no cost.

Confirmed Topics/Speakers

* Static and dynamic languages,
   Prof Philip Wadler, University of Edinburgh
* Compiler technology for data-parallel languages,
   Dr Sven-Bodo Scholz, University of Hertfordshire
* New applications of parametricity,
   Dr Janis Voigtlaender, Technical University of Dresden
* Automatic vectorising compilation,
   Dr Paul Cockshott, University of Glasgow
* Foundational aspects of size analysis,
   Prof Marko van Eekelen / Dr Olha Shakaravska, Radboud University Nijmegen
* Context oriented programming,
   Dr Pascal Costanza, Vrije Universiteit Brussels
* Multi-core programming,
   Dr Phil Trinder, Heriot-Watt University
* Multi-core compilation,
   Dr Alastair Donaldson, Codeplay Software Ltd
* Principles and Applications of Refinement Types,
   Dr Andrew D. Gordon, Microsoft Research, Cambridge
* Resource aware programming in Hume,
   Prof Greg Michaelson, Heriot-Watt University / Prof Kevin Hammond, 
University of St Andrews
* Haskell concurrency & parallelism,
   Dr Satnam Singh, Microsoft Research, Cambridge


Location
~~~~~~~~

The Summer School is at Heriot-Watt University's Riccarton campus, set
in pleasant parkland to the west of Edinburgh, with easy access to the
airport, city and central Scotland
(http://www.hw.ac.uk/welcome/directions.htm).

The Summer School immediately precedes the 2009 International
Conference on Functional Programming
(http://www.cs.nott.ac.uk/~gmh/icfp09.html) and takes place during the
Edinburgh International Festival (http://www.eif.co.uk/) , and the
associated Edinburgh Festival Fringe (http://www.edfringe.com/) and
Edinburgh International Book Festival (http://www.edbookfest.co.uk/)


Steering Committee
~~~~~~~~~~~~~~~~~~

Prof Prof Greg Michaelson, Heriot-Watt University (Convenor), 
<g.michael...@hw.ac.uk>
Prof Kevin Hammond, University of St Andrews
Dr Patricia Johann, University of Strathclyde
Prof Philip Wadler, University of Edinburgh


Fee
~~~

Full rate: £400; (free for SICSA students)
Includes: four nights single room, en-suite accommodation with
breakfast, lunch and dinner, plus coffee breaks and session materials.

Day rate: £200; (free for SICSA students)
Includes: lunch, coffee breaks, session materials


Registration of Interest
~~~~~~~~~~~~~~~~~~~~~~~~

If you are interested in attending the International Summer School,
please complete the form available from
(http://www.macs.hw.ac.uk/~greg/ISS-AiPL/ISS-AiPL%20register.doc) or
below, and return it to: <iss-aipl-regis...@macs.hw.ac.uk>


**********
International Summer School on Advances in Programming Languages
25th-28th August, 2009
Heriot-Watt University, Edinburgh, Scotland

Registration of Interest

Name:
Address:
Email:
Phone:
SICSA Uni: Yes / No
Rate: Full / Day
Accessibility requirements:
Dietary requirements:

Return to: iss-aipl-regis...@macs.hw.ac.uk
**********




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

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


End of Beginners Digest, Vol 11, Issue 11
*****************************************

Reply via email to