Re: What does unsafePerformIO do to the stack

2008-02-01 Thread Bernd Brassel
Thanks for your answer Simon.

Simon Marlow wrote:
> Bernd Brassel wrote:
>> Consider the following program:
>>
>> module Stack where
>>
>> import System.IO.Unsafe
>>
>> main = print (sim (replicate 1299959 ()))
>>
>> sim [] = True
>> sim (_:xs) = goodStack (sim xs)
>>
>> goodStack x = fromJust (Just x)  --no stack overflow
>> badStack  x = unsafePerformIO (return x) --stack overflow
>>
>> fromJust (Just x) = x
> 
> goodStack == id, and GHC even with no optimisation will transform it
> into id, and inline it into sim.  So with goodStack, sim ends up being
> tail-recursive.  With badStack, sim is no longer tail recursive
> (unsafePerformIO is not inlined), so it runs out of stack.  Simple!

Is it really that simple? I guess that in a lazy language we have to
look a bit closer to see what is tail recursive and what is not. If I
understand you correctly, you say that if goodStack was not inlined you
would have a bad stack as well, right? But look at what it would be
doing. In a lazy language the call to sim would go to the heap and
whatever goodStack does to the stack is already done before sim is
restarted. And the same could be true with the unsafePerformIO-return
combination. What is the reason to hold anything on the stack for this
after the call to unsafe is finished?

I have tried the example with badStack in one other compiler and two
interpreters. None of them has any problem running the example. For one
of the interpreters I could exactly measure that the stack is constant
the whole time. And I know that no optimisation or inlining is going on
for that interpreter. Just try the example with hugs. It easily runs
through while replacing badStack with the function

pushStack True = True

immediately runs out of memory. (With this function, the example is
indeed not tail recursive and your argument is valid.)
So there is definitely something that unsafePerformIO does to the stack
in the ghc that is special to that compiler.


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Second Call for Papers TFP 2008, The Netherlands

2008-02-01 Thread Peter Achten

2ND CALL FOR PAPERS
TRENDS IN FUNCTIONAL PROGRAMMING 2008
RADBOUD UNIVERSITY NIJMEGEN, THE NETHERLANDS
MAY 26-28, 2008
INVITED SPEAKER: PROF. HENK BARENDREGT
http://www.st.cs.ru.nl/AFP_TFP_2008/

The symposium on Trends in Functional Programming (TFP) is an
international forum for researchers with interests in all aspects of
functional programming languages, focusing on providing a broad view
of current and future trends in Functional Programming. It aspires to
be a lively environment for presenting the latest research results
through acceptance by extended abstracts and full papers. A formal
post-symposium refereeing process selects the best articles presented
at the symposium for publication in a high-profile volume.

TFP 2008 is hosted by the Radboud University Nijmegen, The Netherlands,
and will be held in the rural setting of Center Parcs “Het Heijderbos”,
Heijen (in the vicinity of Nijmegen), The Netherlands.

TFP 2008 is co-located with the 6th Int’l. Summer School on Advanced
Functional Programming (AFP’08), which is held immediately before TFP’08.


SCOPE OF THE SYMPOSIUM
The symposium recognizes that new trends may arise through various
routes. As part of the Symposium's focus on trends we therefore identify
the following five article categories. High-quality articles are
solicited in any of these categories:

Research: leading-edge, previously unpublished research.
Position: on what new trends should or should not be.
Project: descriptions of recently started new projects.
Evaluation: what lessons can be drawn from a finished project.
Overview: summarizing work with respect to a trendy subject.

Articles must be original and not submitted for simultaneous publication
to any other forum. They may consider any aspect of functional
programming: theoretical, implementation-oriented, or more
experience-oriented. Applications of functional programming techniques
to other languages are also within the scope of the symposium.

Contributions on the following subject areas are particularly welcomed:
* Dependently Typed Functional Programming
* Validation and Verification of Functional Programs
* Debugging for Functional Languages
* Functional Programming and Security
* Functional Programming and Mobility
* Functional Programming to Animate/Prototype/Implement Systems from
Formal or Semi-Formal Specifications
* Functional Languages for Telecommunications Applications
* Functional Languages for Embedded Systems
* Functional Programming Applied to Global Computing
* Functional GRIDs
* Functional Programming Ideas in Imperative or Object-Oriented
Settings (and the converse)
* Interoperability with Imperative Programming Languages
* Novel Memory Management Techniques
* Parallel/Concurrent Functional Languages
* Program Transformation Techniques
* Empirical Performance Studies
* Abstract/Virtual Machines and Compilers for Functional Languages
* New Implementation Strategies
* Any new emerging trend in the functional programming area

If you are in doubt on whether your article is within the scope of TFP,
please contact the TFP 2008 program chairs, Peter Achten and Pieter
Koopman, at [EMAIL PROTECTED]


SUBMISSION AND DRAFT PROCEEDINGS
Acceptance of articles for presentation at the symposium is based on the
review of full papers (15 pages) and extended abstracts (at least 3 pages)
by the program committee. TFP encourages PhD students to submit papers. PhD
students may request the program committee to provide extensive feedback
on their full papers at the time of submission. Full papers describing
work accepted for presentation must be completed before the symposium for
publication in the draft proceedings and on-line. Further details can be
found at the TFP 2008 website http://www.st.cs.ru.nl/AFP_TFP_2008/.


POST-SYMPOSIUM REFEREEING AND PUBLICATION
In addition to the draft symposium proceedings, we continue the TFP
tradition of publishing a high-quality subset of contributions in the
Intellect series on Trends in Functional Programming.


IMPORTANT DATES (ALL 2008)
Paper Submission: March 3
Notification of Acceptance: March 31
Early Registration Deadline: April 14
Late Registration Deadline: May 5
Camera Ready Symposium: May 5
TFP Symposium: May 26-28
Post Symposium Paper Submission: June 20
Notification of Acceptance: September 7
Camera Ready Revised Paper: September 21


PROGRAMME COMMITTEE
Peter Achten (co-chair) Radboud Univ. Nijmegen, NL
Andrew Butterfield Trinity College, IE
Manuel Chakravarty Univ. of New South Wales, AU
John Clements Cal Poly State Univ., USA
Matthias Felleisen Northeastern Univ., USA
Jurriaan Hage Utrecht Univ., NL
Michael Hanus Christian-Albrechts Univ. zu Kiel, DE
Ralf Hinze Univ. of Oxford, UK
Graham Hutton Univ. of Nottingham, UK
Johan Jeuring Utrecht Univ., NL
Pieter Koopman (co-chair) Radboud Univ. Nijmegen, NL
Shriram Krishnamurthi Brown Univ., USA
Hans-Wolfgang Loidl Ludwig-Maximilians Univ.München, DE
Rita Loogen Philipps-Univ. Marburg, DE
Greg Michaelson Heriot-Watt Univ., 

Re: Is GHC 6.8.2 on solaris 32 bits or 64 bits

2008-02-01 Thread Simon Marlow

hsing-chou chen wrote:

Thank you for porting GHC 6.8.2 to solaris, I am assigned a

job to make sure GHC run 64 bits on solaris. Is your

solaris port 64 bits. Or it only 32 BITS. I know 32 bits

GHC can still run on 64 bits solaris. However company want

to run really 64 bits GHC on solaris. Thanks a lot if you


You want to look at the porting instructions:

http://hackage.haskell.org/trac/ghc/wiki/Building/Porting

Start from GHC 6.6.1 (6.8.2 doesn't bootstrap from .hc files yet).

This won't be easy, you'll need to know details of the processor 
architecture, and be prepared to learn about GHC internals.  But it'll be 
fun, if you like that sort of thing :)


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: What does unsafePerformIO do to the stack

2008-02-01 Thread Simon Marlow

Bernd Brassel wrote:

Consider the following program:

module Stack where

import System.IO.Unsafe

main = print (sim (replicate 1299959 ()))

sim [] = True
sim (_:xs) = goodStack (sim xs)

goodStack x = fromJust (Just x)  --no stack overflow
badStack  x = unsafePerformIO (return x) --stack overflow

fromJust (Just x) = x


goodStack == id, and GHC even with no optimisation will transform it into 
id, and inline it into sim.  So with goodStack, sim ends up being 
tail-recursive.  With badStack, sim is no longer tail recursive 
(unsafePerformIO is not inlined), so it runs out of stack.  Simple!



Is this behaviour necessary? Is there any work around, e.g., employing
the foreign function interface?


There's unsafeInlinePerformIO (sometimes called inlinePerformIO), which is 
usable in certain cases, but be very careful.  From Data.ByteString.Internal:


{-# INLINE inlinePerformIO #-}
inlinePerformIO :: IO a -> a
#if defined(__GLASGOW_HASKELL__)
inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r
#else
inlinePerformIO = unsafePerformIO
#endif

But even this might not give you tail recursion, depending on the context.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bootstrapping for Leopard

2008-02-01 Thread Simon Marlow

Matthias Kilian wrote:

On Wed, Jan 30, 2008 at 08:13:01PM +1100, Manuel M T Chakravarty wrote:



[...]
This is due to a change of the configure stage that AFAIK was made to  
easy building on windows.  Instead, of using shell commands/scripts  
(as GHC did previously) to obtain some configuration information (here  
the file path at which the top of the GHC build tree is located), the  
build system now uses small Haskell programs/scripts.  This makes the  
build more portable ** if there is already a Haskell compiler on the  
system **.


But it just doesn't make sense at all. You need a good set of shell
commands at all, since they're used by configure as well as in
Makefiles. I really can't believe that simple stuff like this doesn't
work on windos:

--- aclocal.m4.orig Mon Dec 10 19:11:31 2007
+++ aclocal.m4  Sun Jan 20 17:10:07 2008
@@ -1098,20 +1098,14 @@ AC_REQUIRE([AC_PROG_CC])
 AC_DEFUN([FP_FIND_ROOT],[
 AC_MSG_CHECKING(for path to top of build tree)
 
-dnl This would be

-dnl make -C utils/pwd clean && make -C utils/pwd
-dnl except we don't want to have to know what make is called. Sigh.
-if test ! -f utils/pwd/pwd && test ! -f utils/pwd/pwd.exe; then
-  cd utils/pwd
-  rm -f *.o
-  rm -f *.hi
-  rm -f pwd
-  rm -f pwd.exe
-  $WithGhc -v0 --make pwd -o pwd
-  cd ../..
-fi
-
-hardtop=`utils/pwd/pwd forwardslash`
+case $HostPlatform in
+*cygwin32|*mingw32)
+   hardtop=`pwd | tr \\ /`
+   ;;
+*)
+   hardtop=`pwd`
+   ;;
+esac
 
 if ! test -d "$hardtop"; then

   AC_MSG_ERROR([cannot determine current directory])


Things are complicated because

  - on Cygwin, pwd gives you /cygdrive/c/...
  - on MSYS, pwd gives you /c/...

(remember we still support MSYS), and we want c:/...

So we used to use cygpath on cygwin, and some horrible sed command on MSYS, 
IIRC.  It was a mess, and frequently went wrong.


Sure there are other ways to do it, but I think at the time it seemed 
simpler to write a Haskell program.  In hindsight, probably a C program 
(compiled using mingw gcc) would be better for bootstrapping.  A shell 
script would be problematic for the reasons above, I'm guessing.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Using "GHC as a library" with own functions makes runStmt return RunBreak

2008-02-01 Thread Simon Marlow

Mads Lindstrøm wrote:


For those interested I figured out how to avoid the RunBreak -returns.
Use RunToCompletion in stead of SingleStep in the application of runStmt.
I guess Interactive-6.8.hs should also use SingleStep. 


SingleStep is what GHCi uses to implement :step - that is, it runs until 
the next breakpoint location and then stops, returning RunBreak to the 
caller of runStmt.  To run the whole statement, what you want is 
RunToCompletion, as you discovered.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users