[ ghc-Bugs-1162965 ] Exponential behaviour with type synonyms

2005-11-21 Thread SourceForge.net
Bugs item #1162965, was opened at 2005-03-14 12:54
Message generated for change (Comment added) made by simonpj
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1162965group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: Compiler (Type checker)
Group: None
Status: Open
Resolution: None
Priority: 3
Submitted By: Simon Peyton Jones (simonpj)
Assigned to: Simon Peyton Jones (simonpj)
Summary: Exponential behaviour with type synonyms

Initial Comment:
You're quite right.  GHC has a simple but non-
performant representation of type synonyms in types, so 
as to be able to generate good error messages,  In 
particular, the type

S t

where S is a type synonym defined by 'type S a = s', is 
represented as

SynNote (S t) (s [t/a])

That is, (S t) is represented by *both* its un-expanded 
and expanded form.  

The SynNote is ignored by unification, but the un-
expanded form is useful for error messages.  
Unfortunately, t is duplicated, as you can see, and that 
leads to the behaviour you describe.

I don't see myself fixing this soon, at least partly 
because I can't see an obvious way to fix it that doesn't 
lose error message behaviour.

I'm going to open a SourceForge bug for it.  If anyone 
has good ideas, let me know.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] 
[mailto:glasgow-haskell-bugs-
| [EMAIL PROTECTED] On Behalf Of Iavor Diatchki
| Sent: 17 February 2005 01:27
| To: glasgow-haskell-bugs@haskell.org
| Subject: 'type' declarations
| 
| hello,
| ghc seems to be having trouble with 'type' declarations.
| while compiling (i guess kind checking is the correct 
word here)
| the following program for a very long time, ghc (6.2) 
runs out of 300Mb of heap.
| 
| module Test where
| 
| type S  = Maybe
| type S2 n   = S  (S  n)
| type S4 n   = S2 (S2 n)
| type S8 n   = S4 (S4 n)
| type S16 n  = S8 (S8 n)
| type S32 n  = S16 (S16 n)
| 
| type N64 n  = S32 (S32 n)
| 
| type N64'   =
|   S ( S ( S ( S ( S ( S ( S ( S (
|   S ( S ( S ( S ( S ( S ( S ( S (
|   S ( S ( S ( S ( S ( S ( S ( S (
|   S ( S ( S ( S ( S ( S ( S ( S (
|   S ( S ( S ( S ( S ( S ( S ( S (
|   S ( S ( S ( S ( S ( S ( S ( S (
|   S ( S ( S ( S ( S ( S ( S ( S (
|   S ( S ( S ( S ( S ( S ( S ( S (
|   Int
|   
|   
|   
|   
|   
|   
|   
|   
| 
| if i remove the N64 definition things work.  i guess 
something
| exponential is happening
| (substitution?).
| 
| -iavor


--

Comment By: Simon Peyton Jones (simonpj)
Date: 2005-11-21 11:28

Message:
Logged In: YES 
user_id=50165

I've fixed the exponential behaviour arising from synonyms 
being held in both expanded and unexpanded form.  The test 
is tc199.hs.

However, this SourceForge bug has a type that genuinely is 
exponential in the program size, so it remains un-fixed.

Simon

--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1162965group_id=8032
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[ ghc-Bugs-1362711 ] Recompilation check fails for TH

2005-11-21 Thread SourceForge.net
Bugs item #1362711, was opened at 2005-11-21 11:33
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1362711group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: Template Haskell
Group: None
Status: Open
Resolution: None
Priority: 3
Submitted By: Simon Peyton Jones (simonpj)
Assigned to: Simon Peyton Jones (simonpj)
Summary: Recompilation check fails for TH

Initial Comment:
The recompilation check only recompiles a module when 
the *interface* of a module it imports changes.  But 
with Template Haskell, it may need to be recompiled 
when the *implementation* changes.

Concrete example below.  It's quite awkward to fix.

* Perhaps a module that contains any splices should be 
recompiled always.
* Perhaps a module that exports any TH stuff (how 
would we tell?) should be flagged as changed if 
anything about it changes.  

Simon

The following scenario reproduces this error
(thanks to Bulat Ziganshin [EMAIL PROTECTED]):

1) create Main.hs containing code

module Main where
import Sub
main = print $x

and Sub.hs containing code

module Sub where
x = [| 1 |]



2) compile them with --make:

C:\!\Haskell\!ghc --make -fth Main.hs
Chasing modules from: Main.hs
Compiling Sub  ( ./Sub.hs, ./Sub.o )
Compiling Main ( Main.hs, Main.o )
Loading package base-1.0 ... linking ... done.
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... 
done.
Linking ...

C:\!\Haskell\!main.exe
1


3) now change Sub.hs to the following code:

module Sub where
x = [| 2 |]



4) and recompile program:

C:\!\Haskell\!ghc --make -fth Main.hs
Chasing modules from: Main.hs
Compiling Sub  ( ./Sub.hs, ./Sub.o )
Skipping  Main ( Main.hs, Main.o )
Linking ...

C:\!\Haskell\!main.exe
1


As you see, Main.hs is not recompiled despite the fact 
that definition
of x is changed and now program must print 2



--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1362711group_id=8032
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: smart recompilation checker fails when only TH functions is imported

2005-11-21 Thread Simon Peyton-Jones
Quite correct, and thank you for pointing it out.  I have known about
this bug for some time.  I've turned it into a sourceforge bug  so we
don't forget it.  But it's a bit awkward to see how to fix it, so I'm
probably not going to do much about it unless more people yell!  (Submit
follow-ups to the sourceforge bug)

https://sourceforge.net/tracker/index.php?func=detailaid=1362711group_
id=8032atid=108032

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-bugs-
| [EMAIL PROTECTED] On Behalf Of Bulat Ziganshin
| Sent: 16 November 2005 17:20
| To: glasgow-haskell-bugs@haskell.org
| Subject: smart recompilation checker fails when only TH functions is
imported
| 
| Hello glasgow-haskell-bugs,
| 
| the following scenario reproduces this error:
| 
| 1) create Main.hs containing code
| 
| module Main where
| import Sub
| main = print $x
| 
| and Sub.hs containing code
| 
| module Sub where
| x = [| 1 |]
| 
| 
| 
| 2) compile them with --make:
| 
| C:\!\Haskell\!ghc --make -fth Main.hs
| Chasing modules from: Main.hs
| Compiling Sub  ( ./Sub.hs, ./Sub.o )
| Compiling Main ( Main.hs, Main.o )
| Loading package base-1.0 ... linking ... done.
| Loading package haskell98-1.0 ... linking ... done.
| Loading package template-haskell-1.0 ... linking ... done.
| Linking ...
| 
| C:\!\Haskell\!main.exe
| 1
| 
| 
| 3) now change Sub.hs to the following code:
| 
| module Sub where
| x = [| 2 |]
| 
| 
| 
| 4) and recompile program:
| 
| C:\!\Haskell\!ghc --make -fth Main.hs
| Chasing modules from: Main.hs
| Compiling Sub  ( ./Sub.hs, ./Sub.o )
| Skipping  Main ( Main.hs, Main.o )
| Linking ...
| 
| C:\!\Haskell\!main.exe
| 1
| 
| 
| As you see, Main.hs is not recompiled despite the fact that definition
| of x is changed and now program must print 2
| 
| --
| Best regards,
|  Bulat  mailto:[EMAIL PROTECTED]
| 
| 
| 
| ___
| Glasgow-haskell-bugs mailing list
| Glasgow-haskell-bugs@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: Broken build

2005-11-21 Thread Simon Peyton-Jones
I believe I have fixed this.  (It was my fault, late last week.)

I'm compiling now to test.  Meanwhile it'd be worth your having another
go.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Dinko Tenev
| Sent: 20 November 2005 14:07
| To: glasgow-haskell-users@haskell.org
| Subject: Broken build
| 
| I updated from HEAD recently, and got some strange error messages
| while building the stuff under libraries/X11:
| 
| ../../ghc/compiler/ghc-inplace -H32m -O0 -W -fno-warn-unused-matches
| -fwarn-unused-imports -cpp -fffi -Iinclude -I/usr/X11R6/include
| -ignore-package X11 -O -dcore-lint -W -fno-warn-unused-matches
| -fwarn-unused-imports -keep-hc-files  -package base -fgenerics-c
| Graphics/X11/Xlib/Font.hs -o Graphics/X11/Xlib/Font.o  -ohi
| Graphics/X11/Xlib/Font.hi
| 
| Font.hsc:70:0:
| Unacceptable argument type in foreign declaration: Display
| When checking declaration:
|   foreign import ccall unsafe static HsXlib.h XQueryFont
queryFont :: Display
|
- Font
|
- IO FontStruct
| 
| ...as well as several others for the same file, along the same lines.
| 
| I am none the wiser by the messages, but the comment for
| ghc/compiler/prelude/TysWiredIn.lhs#rev1.75 seems to be related.  Is
| this a regression?
| 
| BTW, could someone give me a clue what the point is with a type like
| the one mentioned?
| 
| Regards,
| Dinko
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


adding to GHC/win32 Handle operations support of Unicode filenames and files larger than 4 GB

2005-11-21 Thread Bulat Ziganshin
Hello glasgow-haskell-users,

Simon, what you will say about the following plan?

ghc/win32 currently don't support operations with files with Unicode
filenames, nor it can tell/seek in files for positions larger than 4
GB. it is because Unix-compatible functions open/fstat/tell/... that
is supported in Mingw32 works only with char[] for filenames and
off_t (which is 32 bit) for file sizes/positions

half year ago i discussed with Simon Marlow how support for unicode
names and large files can be added to GHC. now i implemented my own
library for such files, and got an idea how this can incorporated to
GHC with minimal efforts:

GHC currently uses CString type to represent C-land filenames and COff
type to represent C-land fileseizes/positions. We need to
systematically change these usages to CFilePath and CFileOffset,
respectively, defined as follows:

#ifdef mingw32_HOST_OS
type CFilePath = LPCTSTR
type CFileOffset = Int64
withCFilePath = withTString
peekCFilePath = peekTString
#else
type CFilePath = CString
type CFileOffset = COff
withCFilePath = withCString
peekCFilePath = peekCString
#endif

and of course change using of withCString/peekCString, where it is
applied to filenames, to withCFilePath/peekCFilePath (this will touch
modules System.Posix.Internals, System.Directory, GHC.Handle)

the last change needed is to conditionally define all c_* functions
in System.Posix.Internals, whose types contain references to filenames
or offsets:

#ifdef mingw32_HOST_OS
foreign import ccall unsafe HsBase.h _wrmdir
   c_rmdir :: CFilePath - IO CInt

#else
foreign import ccall unsafe HsBase.h rmdir
   c_rmdir :: CFilePath - IO CInt

#endif

(note that actual C function used is _wrmdir for Windows and rmdir for
Unix). of course, all such functions defined in HsBase.h, also need to
be defined conditionally, like:

#ifdef mingw32_HOST_OS
INLINE time_t __hscore_st_mtime ( struct _stati64* st ) { return st-st_mtime; }
#else
INLINE time_t __hscore_st_mtime ( struct stat* st ) { return st-st_mtime; }
#endif

That's all! of course, this will broke compatibility with current programs
which directly uses these c_* functions (c_open, c_lseek, c_stat and
so on). this may be issue for some libs. are someone really use these
functions??? of course, we can go in another, fully
backward-compatible way, by adding some f_* functions and changing
high-level modules to work with these functions


-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]



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


Patch for Word64

2005-11-21 Thread Matt

I was doing some work with Word64 and noticed that it was about 3 times
slower than Int64. The reason appears to be expensive conversions from
Int64# to Word64# and vice versa. I modified the libraries to remove the
conversion overhead, and the result is that Int64# and Word64# now have
equal performance, at least on the domain that I tested (==, +, -).

I can't check into the tree, so I was told to send my changes to this list.
Could someone else check them in? I have attached a patch file representing
my changes.

-Matt or [ricebowl, wearkilts, soysauce] on #haskell on Freenode 


word64.patch
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Patch for Word64

2005-11-21 Thread Bulat Ziganshin
Hello Matt,

Monday, November 21, 2005, 5:56:51 PM, you wrote:

M I was doing some work with Word64 and noticed that it was about 3 times
M slower than Int64. The reason appears to be expensive conversions from
M Int64# to Word64# and vice versa. I modified the libraries to remove the
M conversion overhead, and the result is that Int64# and Word64# now have
M equal performance, at least on the domain that I tested (==, +, -).

the original code seems to be automatically generated. imho, we are
not need to touch all these code, but concentrate on eliminating cost
of conversions between these two types:

int64ToWord64# = id
word64ToInt64# = id


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Patch: Add support for using --mk-dll with --make

2005-11-21 Thread Esa Ilari Vuokko
Hi!

Attached small simple patch that allows using --mk-dll with --make.
Behaviour before patch was to link .exe instead .dll, as batchmode
simply called staticLink - now doMkDLL is called instead.

* Add support for using --mk-dll with --make

I changed documentation a bit, and moved --mk-dll from 4.17.3
Alternative modes of operation into 4.17.21 Linking options.
This documentation change isn't tested, as I don't have necessary
tools installed on my machine.  But it *seems* harmless (and
I think, more intuitive.)  Due to lack of tools, and because there's
little to say, I didn't touch 11.5. Building and using Win32 DLLs.

Patch should apply cleanly on cvs HEAD with patch -p0 under
fptools.  Any comments are welcome.

Thanks in advance,
--Esa


mk-dll-20051121.patch
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Andrew Pimlott
On Sun, Nov 20, 2005 at 08:54:35AM -0500, David Roundy wrote:
 As an aside, what's responsible for the insanity of pattern matching record
 fields being backwards? I'd bar = b to bind b to bar, not the other way
 around... why should record pattern matching use '=' in a manner opposite
 from the rest of Haskell?

Perhaps it's better to think of '=' as asserting equality, than as
binding?

Andrew
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Type Class Question

2005-11-21 Thread Paul Govereau
Hello,

I was hoping that someone could answer a question I have about the
type class system. In Haskell, I cannot write a term with an exact
constraint:

 data X = X
 bar :: Show X = X - String
 bar x = show x

According to the Haskell 98 report, a qualifier can only be applied to
type variables, but I don't see where the trouble is. The term seems
to have reasonable type, and I don't see any reason why the
dictionary-passing translation shouldn't work out; I am wondering what
problems you run into if this restriction is lifted?

Note, with GHC and Glasgow extensions you can write this program:

 data Y a = Y
 foo :: Show (Y a) = Y a - String
 foo x = show x

However, the first program is still ruled out. Are there any
type-class experts out there that can offer an explanation?

Thanks,
Paul
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Type Class Question

2005-11-21 Thread Cale Gibbard
data X = X deriving Show

bar :: X - String
bar x = show x

There's no need for the class constraint at all. If it's an instance
of Show, then you're okay with just applying show to it. There's no
need to actually assert that it's actually an instance of Show again.

The only purpose of class constraints is to restrict polymorphism. If
a function isn't polymorphic to begin with, you should never need
them.

 - Cale

On 21/11/05, Paul Govereau [EMAIL PROTECTED] wrote:
 Hello,

 I was hoping that someone could answer a question I have about the
 type class system. In Haskell, I cannot write a term with an exact
 constraint:

  data X = X
  bar :: Show X = X - String
  bar x = show x

 According to the Haskell 98 report, a qualifier can only be applied to
 type variables, but I don't see where the trouble is. The term seems
 to have reasonable type, and I don't see any reason why the
 dictionary-passing translation shouldn't work out; I am wondering what
 problems you run into if this restriction is lifted?

 Note, with GHC and Glasgow extensions you can write this program:

  data Y a = Y
  foo :: Show (Y a) = Y a - String
  foo x = show x

 However, the first program is still ruled out. Are there any
 type-class experts out there that can offer an explanation?

 Thanks,
 Paul
 ___
 Haskell mailing list
 Haskell@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] ANNOUNCE: Frag: a First Person Shooting game

2005-11-21 Thread Mun Hon Cheong

Frag is a 3D First Person Shooting game.

Features:

*Yampa, a domain-specific embedded language
 for the programming of hybrid systems that
 using the concepts of Functional Reactive
 Programming (FRP) was used to program the
 game entities.

*The Quake 3 BSP level format, Q3Map2,
 and the MD3 format for models and
 animations are used in this game.

*Sven Panne's OpenGL binding, HOpenGL is
 used to render graphics.

Requirements:

 HOpenGL which is provided with GHC

 OpenGL drivers that support the vertex array
 and multitexture OpenGL extensions

Darcs: darcs get http://www.cse.unsw.edu.au/~pls/repos/frag

Thanks goes to Don Stewart, this project would not
have become public if not for him.

Enjoy,
Mun
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] ANNOUNCE: Frag: a First Person Shooting game

2005-11-21 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 05:05:17PM +1100, Mun Hon Cheong wrote:
 Frag is a 3D First Person Shooting game.

I would be nice if you could put some screenshots somewhere.

Best regards
Tomasz
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] ANNOUNCE: Frag: a First Person Shooting game

2005-11-21 Thread Donald Bruce Stewart
tomasz.zielonka:
 On Tue, Nov 22, 2005 at 05:05:17PM +1100, Mun Hon Cheong wrote:
  Frag is a 3D First Person Shooting game.
 I would be nice if you could put some screenshots somewhere.

A wiki page has been put up on haskell.org, with screenshots:

http://haskell.org/hawiki/Frag

-- Don
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Type Class Question

2005-11-21 Thread Paul Govereau

Ah yes, but this forces me to write my instance of Show right away. I
cannot write:

module A where data X = X
module B where
  import A
  bar x = show x  -- here is the problem
moduel C where
  import A
  instance Show X where show x = X
module Main where
 import A
 import B -- Show instance used
 import C -- Show instance defined

I am not saying that this is terribly useful, I am just wondering why
it is a problem to allow it?

Paul

BTW, The above program is a translation of an idiomatic use of
functors in ML (pardon my syntax):

  module A : sig type t = ... end
  module B : funsig(X:SHOW where t = A.t) sig bar : A.t - string end
  module C : SHOW where t = A.t
  open A
  open B(C)


On Nov 21, Cale Gibbard wrote:
 data X = X deriving Show
 
 bar :: X - String
 bar x = show x
 
 There's no need for the class constraint at all. If it's an instance
 of Show, then you're okay with just applying show to it. There's no
 need to actually assert that it's actually an instance of Show again.
 
 The only purpose of class constraints is to restrict polymorphism. If
 a function isn't polymorphic to begin with, you should never need
 them.
 
  - Cale
 
 On 21/11/05, Paul Govereau [EMAIL PROTECTED] wrote:
  Hello,
 
  I was hoping that someone could answer a question I have about the
  type class system. In Haskell, I cannot write a term with an exact
  constraint:
 
   data X = X
   bar :: Show X = X - String
   bar x = show x
 
  According to the Haskell 98 report, a qualifier can only be applied to
  type variables, but I don't see where the trouble is. The term seems
  to have reasonable type, and I don't see any reason why the
  dictionary-passing translation shouldn't work out; I am wondering what
  problems you run into if this restriction is lifted?
 
  Note, with GHC and Glasgow extensions you can write this program:
 
   data Y a = Y
   foo :: Show (Y a) = Y a - String
   foo x = show x
 
  However, the first program is still ruled out. Are there any
  type-class experts out there that can offer an explanation?
 
  Thanks,
  Paul
  ___
  Haskell mailing list
  Haskell@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell
 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] Records

2005-11-21 Thread Ketil Malde
Simon Marlow [EMAIL PROTECTED] writes:

 I'm assuming you don't consider the distinction between '::' and ': :'
 to be a problem - the justification for this is simple and logical: a
 double colon '::' is a reserved symbol, in the same way that 'then' is a
 reserved identifier.

Intuitively a contigous string of symbols should form one identifier,
just like a string of letters does.  So '=' is different from ' ='
or ' =' etc.  I suspect I have to make some kind of exception for
nesting/grouping symbols - parentheses and quotes etc.

   - single-line comments  (--??? is not a comment, but -- ??? is)

...so this doesn't bother me so much.

Perhaps we need to either start adopting symbols outside of 7-bit
ASCII?  The other solution is to learn to use actual *names* instead
of inventing ad-hoc strings of symbols.  Haskell code tends to go
overboard with symbolic operators, but in general, it detracts from
the readability and adds to the learning curve.  We don't have to just
because we can. :-)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Jesper Louis Andersen
On Sat, 2005-11-19 at 15:40 +0300, Bulat Ziganshin wrote:

 my 15 CRT holds entire 100, even 102 chars in line and i don't want
 to lose even one of them! :)  especially when comment to this function
 occupies another 7 lines :)

The best argument I can come up with when advocating lines of 80 chars
for most programming code is subtle, but important:

Code is easier to read for me when it is printed on good old paper.
a2ps(1) is magnificient, but it takes 80 chars only if you want two
pages on a single A4. Quite a number of projects violates the 80 column
principle with the result it is unreadable on print.

The human eye is not good at scanning long lines. You tend to miss the
beginning of the next column and has to scan longer for it when reading
code. It helps quite a bit that code is indented though, so it is not
entirely impossible.

I tend to use rather big fonts and not maximize my emacs. I can cram 80
columns in, but no more.



On the other hand, having long lines improves the chance that the
grep(1) catches what you want when searching for context.

You have some empty space in the end of lines to provide a helpful
comment more often than in an 80 column setup.



All in all, this is bikesheds on greener grass (google for bikeshed and
Poul Henning Kamp).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Project postmortem

2005-11-21 Thread Simon Peyton-Jones
If it's MacOS specific, we're not going to be much help at GHC HQ,
because we don't have any (Macs that is).  Wolfgang Thaller is the MacOS
expert, but maybe there are others now?

Simon

| -Original Message-
| From: Joel Reymont [mailto:[EMAIL PROTECTED]
| Sent: 19 November 2005 00:57
| To: Simon Marlow
| Cc: Simon Peyton-Jones; Haskell Cafe
| Subject: Re: [Haskell-cafe] Project postmortem
| 
| I'm happy to report that the problem can be reproduced by running the
| code from my darcs repo at http://test.wagerlabs.com/postmortem. See
| the README file. I'm on Mac OSX 10.4.3.
| 
| The server just sits there, goes through the SSL handshake and...
| does nothing else. The clients go through the handshake with the
| server and do nothing else. The handshake goes through X number of
| times and then the client crashes.
| 
| On Nov 18, 2005, at 1:55 PM, Simon Marlow wrote:
| 
|  How we normally proceed for a crash like this is as follows: examine
|  where the crash happened and determine whether it is a result of
|  heap or
|  stack corruption, and then attempt to trace backwards to find out
|  where
|  the corruption originated from.  Tracing backwards means running the
|  program from the beginning again, so it's essential to have a
|  reproducible example.  Without reproducibility, we have to use a
|  combination of debugging printfs and staring really hard at the
code,
|  which is much more time consuming (and still requires being able to
|  run
|  the program to make it crash with debugging output turned on).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project postmortem

2005-11-21 Thread Joel Reymont

Is Wolfgang still around?

Would you guys be willing to guide me through this? I could then  
possibly become the next Mac OSX expert :-).


I have the disassembler dumps, etc. I do not know how to approach  
this problem. I read up a bit on the GHC internals, STG, code  
generation, etc.


Thanks, Joel

P.S. Please feel free to take the email exchange offline, could be  
too boring for everyone else


On Nov 21, 2005, at 9:35 AM, Simon Peyton-Jones wrote:


If it's MacOS specific, we're not going to be much help at GHC HQ,
because we don't have any (Macs that is).  Wolfgang Thaller is the  
MacOS

expert, but maybe there are others now?


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 08:31 schrieb Bulat Ziganshin:
 Hello Wolfgang,

 Sunday, November 20, 2005, 6:21:05 PM, you wrote:
  data Coord = { x,y :: Double }
  data Point : Coord = { c :: Color }

  A point is not a special coordinate pair.  Instead it has a coordinate
  paar as one of its properties.  So the above-mentioned problem would be
  better handled this way:
 
  data Coord { x, y :: Double }
  data Point = Point {coord :: Coord, c :: Color }

 because this allows a large number of procedures written to work with
 Coord, to automatically work with Point. iy just a matter of
 usability. currently, my program is full of double-dereferncing, like
 this:

 [...]

You should never use bad design to increase usability, I'd say.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Wolfgang Jeltsch
Am Sonntag, 20. November 2005 12:28 schrieb Jesper Louis Andersen:
 [...]

 The best argument I can come up with when advocating lines of 80 chars
 for most programming code is subtle, but important:

 Code is easier to read for me when it is printed on good old paper.
 a2ps(1) is magnificient, but it takes 80 chars only if you want two
 pages on a single A4. Quite a number of projects violates the 80 column
 principle with the result it is unreadable on print.

Hmm, printing code on paper isn't good for the environment.

 The human eye is not good at scanning long lines.

This is a good argument.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project postmortem

2005-11-21 Thread Joel Reymont

Simon,

What about the non-OSX issue of using a Chan to collect traces from  
thousands of threads?


It's not working very well for me when I use readChan in a loop (see  
the code). getChanContents works much better but then the logger  
thread is stuck forever and everything else that waits on it is stuck  
as well.


The output from logger (Util.hs) stops after a few lines and thus  
memory taken starts to grow because all the output sent to the chan  
is not being processed.


Thanks, Joel

On Nov 21, 2005, at 9:35 AM, Simon Peyton-Jones wrote:


If it's MacOS specific, we're not going to be much help at GHC HQ,
because we don't have any (Macs that is).  Wolfgang Thaller is the  
MacOS

expert, but maybe there are others now?


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Sebastian Sylvan
On 11/21/05, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Sonntag, 20. November 2005 12:28 schrieb Jesper Louis Andersen:
  [...]

  The best argument I can come up with when advocating lines of 80 chars
  for most programming code is subtle, but important:
 
  Code is easier to read for me when it is printed on good old paper.
  a2ps(1) is magnificient, but it takes 80 chars only if you want two
  pages on a single A4. Quite a number of projects violates the 80 column
  principle with the result it is unreadable on print.

 Hmm, printing code on paper isn't good for the environment.

  The human eye is not good at scanning long lines.

 This is a good argument.


Also that terminals etc. usually have 80 chars width. It may be time
to stop worrying about code width, especially in languages like
Haskell where you tend to use horizontal rather than vertical space to
write your algorithms. But still, I always try to stick under 80 chars
if possible to make it readible in terminals (and some email-clients
etc.).


/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad strictness

2005-11-21 Thread Yitzchak Gale
In the following, why does testA work and testB diverge?
Where is the strictness coming from?

Thanks,
Yitz

module Test where

import Control.Monad.State
import Control.Monad.Identity

repeatM :: Monad m = m a - m [a]
repeatM = sequence . repeat

testA =
  take 5 $
  flip evalState [1..10] $ repeatM $ do
x - gets head
modify tail
return x

testB =
  take 5 $
  runIdentity $
  flip evalStateT [1..10] $ repeatM $ do
x - gets head
modify tail
return x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to use notFollowedBy function in Parsec

2005-11-21 Thread Christian Maeder

Sara Kenedy wrote:

import qualified ParsecToken as P


the proper hierarchical module name is:
Text.ParserCombinators.Parsec.Token


str1 :: Parser String
str1 = do {str - many anyToken; notFollowedBy semi; return str}


simply try:

str - many anyToken; notFollowedBy (char ';'); return str

semi only skips additional white spaces (that you are not interested in)

(I find it easier not to use the Parsec.Token und Parsec.Language 
wrappers and remain Haskell 98 conform)


Christian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] records proposals list

2005-11-21 Thread Bulat Ziganshin
Hello Wolfgang,

Monday, November 21, 2005, 1:30:10 PM, you wrote:

  data Coord { x, y :: Double }
  data Point = Point {coord :: Coord, c :: Color }

 because this allows a large number of procedures written to work with
 Coord, to automatically work with Point. iy just a matter of
 usability. currently, my program is full of double-dereferncing, like
 this:

 [...]

WJ You should never use bad design to increase usability, I'd say.

to be exact now i have the following definitions:

data FileInfo = FileInfo
  { fiFilteredName :: !PackedFilePath
  , fiDiskName :: !PackedFilePath
  , fiStoredName   :: !PackedFilePath
  , fiSize :: !FileSize  
  , fiTime :: !FileTime  
  , fiIsDir:: !Bool  
  }

-- |File to compress: either file on disk or compressed file in existing archive
data FileToCompress = DiskFile {
  cfFileInfo :: FileInfo
  }
| CompressedFile {
  cfFileInfo :: FileInfo
, cfArcBlock :: ArchiveBlock-- Archive datablock 
which contains file data
, cfPos  :: FileSize-- Starting byte of 
file data in datablock
, cfCRC  :: CRC -- File's CRC
  }

i prefer to replace second definition with the
  
-- |File to compress: either file on disk or compressed file in existing archive
data CompressedFile : FileInfo =
  CompressedFile {
  cfArcBlock :: ArchiveBlock-- Archive datablock 
which contains file data
, cfPos  :: FileSize-- Starting byte of 
file data in datablock
, cfCRC  :: CRC -- File's CRC
  }

and then use procedures, written to work with FileInfo, to directly
work with CompressedFile also. now my program is full of constructs
like:

  uiStartProcessing (map cfFileInfo (arcDirectory arcinfo))
  let fileinfo  = cfFileInfo compressed_file

and double-dereferencing about i wrote in previous letter. such change
will allow me to omit all these superfluous code. imho, new design will
be more natural and allow me to think about my algorithms instead of
implementation complications

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 14:27 schrieb David Roundy:
 On Sun, Nov 20, 2005 at 04:21:05PM +0100, Wolfgang Jeltsch wrote:
  Am Samstag, 19. November 2005 17:35 schrieb Bulat Ziganshin:
   7. OOP-like fields inheritance:
  
   data Coord = { x,y :: Double }
   data Point : Coord = { c :: Color }
  
   of course this is just another sort of syntax sugar once we start
   using classes to define getter/setter functions
 
  I thought that even many OO people say that inheritance of fields is not
  good practice.  So why should we want to support it?

 Think of it instead as being syntactic sugar for a class declaration:

 class Coord a where
   get_x :: a - Double
   get_y :: a - Double
   set_x :: Double - a - a
   set_y :: Double - a - a

As I pointed out in another e-mail just sent, this kind of special syntax only 
solves a very specific problem so that it's questionable whether this syntax 
should be included into Haskell.  However, if we manage to create a more 
generalized approach, inclusion of it into the language might be quite fine.

In addition, having a line which begins with data declaring a class is 
*very* misleading, in my opinion.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread David Roundy
On Mon, Nov 21, 2005 at 02:48:48PM +0100, Wolfgang Jeltsch wrote:
 Am Montag, 21. November 2005 14:27 schrieb David Roundy:
  On Sun, Nov 20, 2005 at 04:21:05PM +0100, Wolfgang Jeltsch wrote:
   Am Samstag, 19. November 2005 17:35 schrieb Bulat Ziganshin:
7. OOP-like fields inheritance:
   
data Coord = { x,y :: Double }
data Point : Coord = { c :: Color }
   
of course this is just another sort of syntax sugar once we start
using classes to define getter/setter functions
  
   I thought that even many OO people say that inheritance of fields is not
   good practice.  So why should we want to support it?
 
  Think of it instead as being syntactic sugar for a class declaration:
 
  class Coord a where
get_x :: a - Double
get_y :: a - Double
set_x :: Double - a - a
set_y :: Double - a - a
 
 As I pointed out in another e-mail just sent, this kind of special syntax
 only solves a very specific problem so that it's questionable whether
 this syntax should be included into Haskell.  However, if we manage to
 create a more generalized approach, inclusion of it into the language
 might be quite fine.
 
 In addition, having a line which begins with data declaring a class is
 *very* misleading, in my opinion.

Data lines declare instances all the time via deriving.  If something like
this were implemented--and really this applies to any scheme that creates
functions to access record fields--there would need to be a set of implicit
classes for field access.  To fix the namespace issue with field names, the
only two solutions (as far as I can tell) are

(a) Don't create getter or setter functions for field access.  This is what
the SM proposal does.

(b) Create some sort of class that allows getter and/or setter functions
for field access.

(a) involves the creation of a non-function syntax for something that is
essentially a function--and means you'll need boiler-plate code if you want
to create accessor functions.  (b) means a proliferation of classes, which
is perhaps more problematic, but you gain more from it--you avoid the
requirement of a special syntax for accessing fields of a record.  So if
some variant of (b) is practical, I'd vote for it.  I'm not attached to the
inheritance idea, but it's basically a limited form of (b).
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Philippa Cowderoy
On Mon, 21 Nov 2005, David Roundy wrote:

 (b) Create some sort of class that allows getter and/or setter functions
 for field access.
 
 (a) involves the creation of a non-function syntax for something that is
 essentially a function--and means you'll need boiler-plate code if you want
 to create accessor functions.  (b) means a proliferation of classes, which
 is perhaps more problematic, but you gain more from it

I'm not sure it's all that bad if we can avoid namespace pollution?

-- 
[EMAIL PROTECTED]

Performance anxiety leads to premature optimisation
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad strictness

2005-11-21 Thread Roberto Zunino

Yitzchak Gale wrote:


In the following, why does testA work and testB diverge?
Where is the strictness coming from?


My guess: from strict pattern matching in (=).

The following StateT variant uses lazy (irrefutable) pattern match instead.

Regards,
Roberto Zunino.


newtype StT s m a = StT { runStT :: s - m (a,s) }

instance (Monad m) = Monad (StT s m) where
return a = StT $ \s - return (a, s)
m = k  = StT $ \s - do
-- was: (a, s') - runStT m s
~(a, s') - runStT m s
runStT (k a) s'
fail str = StT $ \_ - fail str

stGet :: Monad m = StT s m s
stGet = StT $ \s - return (s,s)

stPut :: Monad m = s - StT s m ()
stPut s = StT $ \_ - return ((),s)

evalStT :: Monad m = StT s m a - s - m a
evalStT m s = do (x,_) - runStT m s ; return x

repeatM :: Monad m = m a - m [a]
repeatM = sequence . repeat

testC =
  take 5 $
  runIdentity $
  flip evalStT [1..10] $ repeatM $ do
s - stGet
let x = head s
stPut $ tail s
return x

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad strictness

2005-11-21 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 16:09 schrieb Roberto Zunino:
 Yitzchak Gale wrote:
  In the following, why does testA work and testB diverge?
  Where is the strictness coming from?

 My guess: from strict pattern matching in (=).

This is a problem I came across some months ago.  State uses lazy pattern 
matching (implicitely via a let expression) while StateT uses strict pattern 
matching (inside a do statement).  Both should definitely use lazy pattern 
matching, in my opinion.

 [...]

 The following StateT variant uses lazy (irrefutable) pattern match instead.

Good! :-)

 Regards,
 Roberto Zunino.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Keean Schupke

Hi,

   Haskell already has static records (in H98)

   Dynamic records are addressed by the HList library, which uses 
extensions already present in GHC and Hugs (namely Multi-parameter 
type-classes and function-dependancies).


   So you can do this now... with reasonable syntax, for example to 
create an extensible record


   (some thing .*. (27 :: Int) .*. True .*. HNil)

   is a statically typed anonymous record.
  

   In other words there is no need for any more extensions to GHC or 
Hugs to implement Records (although  having a type-level type-equality 
constaint would simplify the internal implementation of the library)...


   For details see the HList paper: http://homepages.cwi.nl/~ralf/HList/

   Regards,  
   Keean.


Bulat Ziganshin wrote:


Hello Haskell,

 can anyone write at least the list of record proposals for Haskell?
or, even better, comment about pros and contras for each proposal?

 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] records proposals list

2005-11-21 Thread Bulat Ziganshin
Hello Keean,

Monday, November 21, 2005, 6:56:06 PM, you wrote:

KS So you can do this now... with reasonable syntax, for example to
KS create an extensible record

KS (some thing .*. (27 :: Int) .*. True .*. HNil)

KS is a statically typed anonymous record.
   
it is not record, but heterogenous list, in my feel. record must be
indexed by field name, not by type name or position


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Keean Schupke
One thing, which I am sure you must have got right, but which burned me, 
is that you must explicitly free enitities created by FFI calls.


For example network sockets exist outside of the haskell runtime, and 
are not free'd automatically when a haskell thread is killed, you need 
an explicit exception handler to close the handle... They may eventually 
be garbage collected - but your application may run out of resources 
before this happens.


   Keean.

Joel Reymont wrote:

Maybe one of the Simons can comment on this. I distinctly remember  
trying the mdo approach to kill the other thread and getting burned  
by that. Don't know why I forgot to mention it.


On Nov 17, 2005, at 2:03 PM, Sebastian Sylvan wrote:


What I do remember is that the timeout and parIO functions in the
concurrent programming papers I found were NOT correct. killThread did
NOT behave as expected when I killed an already killed thread.
I tried multiple tricks here (including some which required recursive
do-notation) to try to get the parIO function to only kill the *other*
thread.
This could be done by having the two spawned threads take their
computations in an MVar along with the threadID of the other thread.



--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Joel Reymont
I'm being quite careful with resources these days. The outstanding  
issues are


1) Crashes on Mac OSX that are not reproduced on Linux, Windows, etc.

2) Some kind of a problem with Chan. getChanContents retrieves things  
smoothly, readChan only does it for the first few lines. Simon? Anyone?


3) Different performance of the logger thread on Mac OSX and Windows.

I'm having thousands of threads write their trace messages to a Chan.  
The logger On Windows I only see the first few lines of output when  
using isEmptyChan/readChan to retrieve values in a loop. On Mac OSX I  
do see smooth output.


On Windows I run out of memory because all the output sent to the  
chan builds up and is never processed. I can process it by replacing  
isEmptyChan/readChan with getChanContents but then my logger thread  
hangs forever (right semantics) and hangs everything else that waits  
for the logger thread to check an MVar and exit.


On Nov 21, 2005, at 4:34 PM, Keean Schupke wrote:

One thing, which I am sure you must have got right, but which  
burned me, is that you must explicitly free enitities created by  
FFI calls.


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] records proposals list

2005-11-21 Thread Ralf Lammel
I certainly agree with Keean. It's just that the given example is a bit
misleading. As Bulat observed, the example is about a heterogeneous
list, as opposed to a record. But there are of course tons of record
examples to be found, if you follow the HList link.

Ralf

P.S.: The HList paper also has a reasonable related work section, which
might hold more information of the kind that Bulat asked for.


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Keean Schupke
 Sent: Monday, November 21, 2005 7:56 AM
 To: Bulat Ziganshin
 Cc: Haskell Cafe
 Subject: Re: [Haskell-cafe] records proposals list
 
 Hi,
 
 Haskell already has static records (in H98)
 
 Dynamic records are addressed by the HList library, which uses
 extensions already present in GHC and Hugs (namely Multi-parameter
 type-classes and function-dependancies).
 
 So you can do this now... with reasonable syntax, for example to
 create an extensible record
 
 (some thing .*. (27 :: Int) .*. True .*. HNil)
 
 is a statically typed anonymous record.
 
 
 In other words there is no need for any more extensions to GHC or
 Hugs to implement Records (although  having a type-level type-equality
 constaint would simplify the internal implementation of the
library)...
 
 For details see the HList paper:
http://homepages.cwi.nl/~ralf/HList/
 
 Regards,
 Keean.
 
 Bulat Ziganshin wrote:
 
 Hello Haskell,
 
   can anyone write at least the list of record proposals for Haskell?
 or, even better, comment about pros and contras for each proposal?
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Keean Schupke
You can change the project and update operators in the HList library to 
behave
in exactly this way. At the moment they are constrained to not allow 
multiple
identical labels in records. If this kind of access is considered 
useful, I can

add it to the HList distribution.

   Keean.

David Menendez wrote:


Chris Kuklewicz writes:

 


Would the record system describe at
http://lambda-the-ultimate.org/node/view/1119
also be convertable into System Fw, GHC's existing, strongly-typeed
intermediate language. ?
   



Probably. Daan's current implementation uses MLF, which I believe is
system F implemented for ML.

(We're talking about the system in Daan Leijen's paper, Extensible
Records With Scoped Labels. Good stuff.)
 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Keean Schupke
Can this not be done with the HList code? I am pretty sure you should be 
able to
map projections over HLists of HLists... (although the HList generic map 
is a bit

ugly, requiring instances of the Apply class).

Actually you should look in the OOHaskell paper (if you haven't already) 
where it

discusses using narrow to allow homogeneous lists to be projected from
heterogeneous ones...

   Keean.

John Meacham wrote:


another thing is that for any record syntax, we would want higher order
versions of the selection, setting, and updating routines. A quick
perusal of my source code shows over half my uses of record selectors
are in a higher order fashion. (which need to be generated with DrIFT
with the current syntax)

I mean something like 


map (.foo) xs
to pull all the 'foo' fields out of xs.  (using made up syntax)

or 


map (foo_s 3) xs

to set all the foo fields to 3. (using DrIFT syntax)


   John

 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Malcolm Wallace
David Roundy [EMAIL PROTECTED] writes:

 I'd benefit from just a list of problems that the record proposals want to
 solve.
 
 1. The field namespace issue.
 2. Multi-constructor getters, ideally as a function.
 3. Safe getters for multi-constructor data types.
 4. Getters for multiple data types with a common field.
 5. Setters as functions.
 6. Anonymous records.
 7. Unordered records.

Personally, I would quite like to have first-class labels.  By this
I mean the ability to pass record labels as arguments, and to return
them as results.

With this one generalisation, it would be possible to cover most of
the wishlist above.  A generic getter and setter could be defined
simply as polymorphic functions e.g.

get :: Label n - Record (n::a | r) - a
set :: Label n - a - Record r - Record (n::a | r)
upd :: Label n - (a-a) - Record (n::a | r) - Record (n::a | r)

You could even define your own preferred syntactic sugar for these
operations e.g.

r . l = get l r

.. and the higher-order uses fall out for free

map (get foo) listOfRecords

There are several proposals incorporating this idea.

Oleg Kiselyov and Ralf Lämmel, Haskell's overlooked object system
http://homepages.cwi.nl/~ralf/OOHaskell/

Daan Leijen, First-class labels for extensible rows
http://www.cs.uu.nl/~daan/pubs.html

Benedict Gaster and Mark Jones, A Polymorphic Type System for
Extensible Records and Variants
http://www.cse.ogi.edu/~mpj/pubs/polyrec.html

Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Max Eronin
On 11/21/05, David Roundy [EMAIL PROTECTED] wrote:
 class Coord a where
   get_x :: a - Double
   get_y :: a - Double
   set_x :: Double - a - a
   set_y :: Double - a - a


I'd say this is a typical OO solution to the problem that doesn't exist

Why do you need setters and getters for coordinate in purely
functional language? Doesn't  data Coord = Coord Double Double,
functional composition and monads solve problems in way better than
inheritance?
The most impressive feature of haskell for me, as a former OO-design
patterns-UML is great programmer was that I don't have to and in fact
must not use OO and inheritance and can write code that doesn't leave
you guessing what exactly it is doing and what is not. And that the
language forces you make good design decisions and doesn't let you
make wrong ones. Inheritance  is no doubt one of the most sensless
solutions for code reuse i have ever seen.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Henning Thielemann


On Sat, 19 Nov 2005, David Roundy wrote:


1. Field namespace issue:

Field names should not need to be globally unique.  In Haskell 98, they
share the function namespace, and must be unique.  We either need to make
them *not* share the function namespace (which means no getters as
functions), or somehow stick the field labels into classes.


I found that problem more annoying when starting with Haskell. But since I 
do now try to define only one data type per module, equal field names 
don't collide so easy anymore. It remains the inconvenience that field 
names must be qualified with the module name rather than the record 
variable name.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Henning Thielemann


On Sat, 19 Nov 2005, Antti-Juhani Kaijanaho wrote:


Ketil Malde wrote:
[about A.b and A . b potentially meaning different things:]

Syntax that changes depending on spacing is my number
one gripe with the Haskell syntax


I also think that it is problematic that a character which can be part of 
an alpha-numeric identifier can also be part of an infix operator 
identifier. This is the cause of the relevance of the spacing. 'A+b' and 
'A + b' always mean the same, but 'A.b' and 'A . b' do not. Very 
confusing.



Hence, spacing being significant is not Haskell-specific


So Haskell is somehow BASICish -- how awful.


and is generally a good thing.


FORTRAN is even more space sensitive ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Henning Thielemann


On Mon, 21 Nov 2005, Wolfgang Jeltsch wrote:


Am Sonntag, 20. November 2005 12:28 schrieb Jesper Louis Andersen:

[...]



The best argument I can come up with when advocating lines of 80 chars
for most programming code is subtle, but important:

Code is easier to read for me when it is printed on good old paper.
a2ps(1) is magnificient, but it takes 80 chars only if you want two
pages on a single A4. Quite a number of projects violates the 80 column
principle with the result it is unreadable on print.


Hmm, printing code on paper isn't good for the environment.


But is quite the same argument for e-paper. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] getCPUTime ??

2005-11-21 Thread Michael Benfield

I'm new to Haskell. I'm apparently misunderstanding something here.

When I run this program:

-
module Main where

import System.Posix
import System.CPUTime

printTime = getCPUTime = putStrLn . show

main = printTime  sleep 5  printTime
-

It produces this output:
14300
14300

or similar. In any case, both the numbers are the same. Should the 
second number not reflect a time 5 seconds later than the first? I've 
tried this with both GHC and Hugs, and both give me the same thing.


Thanks.
Mike Benfield

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Tomasz Zielonka
On Mon, Nov 21, 2005 at 04:42:33PM +, Joel Reymont wrote:
 2) Some kind of a problem with Chan. getChanContents retrieves things  
 smoothly, readChan only does it for the first few lines. Simon? Anyone?

This is interesting. Could you show some source code?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Cale Gibbard
On 21/11/05, Henning Thielemann [EMAIL PROTECTED] wrote:

 On Sat, 19 Nov 2005, Antti-Juhani Kaijanaho wrote:

  Ketil Malde wrote:
  [about A.b and A . b potentially meaning different things:]
  Syntax that changes depending on spacing is my number
  one gripe with the Haskell syntax

 I also think that it is problematic that a character which can be part of
 an alpha-numeric identifier can also be part of an infix operator
 identifier. This is the cause of the relevance of the spacing. 'A+b' and
 'A + b' always mean the same, but 'A.b' and 'A . b' do not. Very
 confusing.

This really isn't so bad in practice though. I've certainly never been
confused by it. You'd have to go out of your way to construct a
situation in which it's potentially confusing, which is something that
might be relevant in the IOHCC, but not in ordinary programming.

There are much more important issues to deal with than this, really.

In a sane language, small amounts of whitespace sensitivity are going
to be around no matter what you do. We use whitespace to denote
function application. I can't write fx to mean f x. This is a good
thing. The same perhaps ought to apply to operators. It would be nice
sometimes to be able to use '-' as a hyphen in the middle of names.

 - Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Max Eronin
On 11/18/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:

 I'm not saying it's impossible to make good use of (.), I'm saying
 that it's not crucial enough to warrant giving it the dot, which in my
 opinion is one of the best symbols (and I'd hand it over to record
 selection any day of the week!).
 I'm also saying that people tend to abuse the (.) operator when they
 start out because they think that less verbose == better, whereas
 most people, in my experience, tend to stop using (.) for all but the
 simplest cases (such as filte (not . null)) after a while to promote
 readability. I prefer adding a few lines with named sub-expressions to
 make things clearer.


In case someone counts votes pro et contra of replacing (.) operator,
I must say that find it one of the most useful and readable way for
doing many different things (not only higher-order). And very compact
too.
And in my code it is very common operator.
While if somebody, who at this moment counts my vote, will remove
records from the language some day, I very likely wouldn't notice such
a loss.
And I can't say I'm very experienced haskell programmer. Actually I'm
a beginner comparing my experience with other, particularly imperative
OOP languages.
And records with (.) as field selector (coupled with dumb
constructors) will be the last thing i would miss in haskell.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getCPUTime ??

2005-11-21 Thread Jon Fairbairn
On 2005-11-21 at 15:14EST Michael Benfield wrote:
 I'm new to Haskell. I'm apparently misunderstanding something here.
 
 When I run this program:
 
 -
 module Main where
 
 import System.Posix
 import System.CPUTime
 
 printTime = getCPUTime = putStrLn . show
 
 main = printTime  sleep 5  printTime
 -
 
 It produces this output:
 14300
 14300
 
 or similar. In any case, both the numbers are the same. Should the 
 second number not reflect a time 5 seconds later than the first? I've 
 tried this with both GHC and Hugs, and both give me the same thing.

Should 'sleep 5' take any CPU time?
 
-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getCPUTime ??

2005-11-21 Thread Cale Gibbard
getCPUTime gets the amount of CPU time used by the program so far, in
picoseconds (though with limited resolution). Use getClockTime from
System.Time to get the current clock time.

 - Cale

On 21/11/05, Michael Benfield [EMAIL PROTECTED] wrote:
 I'm new to Haskell. I'm apparently misunderstanding something here.

 When I run this program:

 -
 module Main where

 import System.Posix
 import System.CPUTime

 printTime = getCPUTime = putStrLn . show

 main = printTime  sleep 5  printTime
 -

 It produces this output:
 14300
 14300

 or similar. In any case, both the numbers are the same. Should the
 second number not reflect a time 5 seconds later than the first? I've
 tried this with both GHC and Hugs, and both give me the same thing.

 Thanks.
 Mike Benfield

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getCPUTime ??

2005-11-21 Thread Duncan Coutts
On Mon, 2005-11-21 at 15:14 -0500, Michael Benfield wrote:
 I'm new to Haskell. I'm apparently misunderstanding something here.
 
 When I run this program:
 
 -
 module Main where
 
 import System.Posix
 import System.CPUTime
 
 printTime = getCPUTime = putStrLn . show
 
 main = printTime  sleep 5  printTime
 -
 
 It produces this output:
 14300
 14300
 
 or similar. In any case, both the numbers are the same. Should the 
 second number not reflect a time 5 seconds later than the first? I've 
 tried this with both GHC and Hugs, and both give me the same thing.

http://haskell.org/ghc/docs/latest/html/libraries/base/System-CPUTime.html

getCPUTime :: IO Integer
Computation getCPUTime returns the number of picoseconds CPU
time used by the current program. The precision of this result
is implementation-dependent. 

The key point there is that it is the CPU time *used* by the program. So
sleeping uses no cpu time. Also, the precision is probably not terribly
high which is why you get the exact same answer despite having used a
minute about of actual cpu time. You can find the precision by using
cpuTimePrecision.

You probably want actual time rather than cpu time, in which case you
should use the System.Time module.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Joel Reymont

Yes, of course.

darcs repo at http://test.wagerlabs.com/postmortem.

logger in Util.hs

On Nov 21, 2005, at 8:30 PM, Tomasz Zielonka wrote:


On Mon, Nov 21, 2005 at 04:42:33PM +, Joel Reymont wrote:

2) Some kind of a problem with Chan. getChanContents retrieves things
smoothly, readChan only does it for the first few lines. Simon?  
Anyone?


This is interesting. Could you show some source code?


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Tomasz Zielonka
On Mon, Nov 21, 2005 at 09:50:20PM +, Joel Reymont wrote:
 Yes, of course.
 
 darcs repo at http://test.wagerlabs.com/postmortem.
 
 logger in Util.hs

It's in Conc.hs

You seem to be busy waiting. I can see two ways of solving the problem:
1. use STM and non-deterministic choice
2. use a (Chan (Maybe String)), where (Just s) means the next log
   entry, and Nothing means break the logger loop

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to use notFollowedBy function in Parsec

2005-11-21 Thread Andrew Pimlott
On Sun, Nov 20, 2005 at 09:27:53PM -0500, Sara Kenedy wrote:
 Thanks for your solution. However, when I try this,
 
  str1 :: Parser String
 str1 = do str - many anyToken
notFollowedBy' semi
  return str
 
  notFollowedBy' :: Show a = GenParser tok st a - GenParser tok st ()
  notFollowedBy' p  = try $ join $  do  a - try p
  return (unexpected 
  (show a))
   |
   return (return ())
   run:: Show a = Parser a - String - IO()
 
   run p input
 
  = case (parse p  input) of
 
  Left err - do {putStr parse error at  ;print err}
 
  Right x - print
 
 When I compile, it still displays ; at the end of the string.
 
   Parser run str1 Hello ;
   Hello ;
 
 The reason, as I think, because anyToken accepts any kind of token, it
 considers ; as token of its string. Thus, it does not understand
 notFollowedBy' ???

That's right--your parser consumes and returns the whole input.  I can't
tell you what to use instead, because it depends on what kinds of
strings you want to parse.  Since you are using Token parsers, maybe you
want symbol?  The functions in the Char module might also be useful.

Andrew
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Joel Reymont
STM would complicate things too much for me. At least I think so. I  
would love to use STM but I would need to fit it into type  
ScriptState = ErrorT String (StateT World IO) just to use the  
logger. I'm not THAT comfortable with monads.


Let me see if I understand you correctly... Are you saying that I  
should be using getChanContents in the code below?


logger :: Handle - MVar () - IO ()
logger h die =
do empty - isEmptyChan parent
   unless empty $ do x - readChan parent
 putStrLn x
 hPutStrLn h x
   alive - isEmptyMVar die
   when (alive || not empty) $ logger h die

I think using Maybe is a great trick but I'm curious why so few  
messages actually get taken out of the channel in the code above? Are  
you saing that with all the checking it does not get to pull messages  
out?


I see clearly how using Maybe with getChanContents will work out  
perfectly. I don't understand why the above code is inefficient to  
the point of printing just a few messages (out of hundreds) out on  
Windows. I would like to understand it to avoid such mistakes in the  
future.


Thanks, Joel

On Nov 21, 2005, at 9:56 PM, Tomasz Zielonka wrote:

You seem to be busy waiting. I can see two ways of solving the  
problem:

1. use STM and non-deterministic choice
2. use a (Chan (Maybe String)), where (Just s) means the next log
   entry, and Nothing means break the logger loop


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-21 Thread Albert Lai
I offer a simpler, more direct, and pre-existing correspondence
between a functional programming construct and unix pipes:

  http://www.vex.net/~trebla/weblog/pointfree.html

Scherrer, Chad [EMAIL PROTECTED] writes:

 I'm still trying to settle on a feel for good programming style in
 Haskell. One thing I've been making some use of lately is
 
 (\|) = flip ($)
 infixl 0 \|
 
 Then expressions like
 
 f4 $ f3 $ f2 $ f1 $ x
 
 become
 
 x  \|
 f1 \|
 f2 \|
 f3 \|
 f4
 
 I've seen something like this on haWiki using (#), but I prefer this
 notation because it looks like a Unix pipe, which is exactly how it's
 used. 

[...]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] re-definition of '.'

2005-11-21 Thread Max Eronin
 2) sequential functions application in OOP style:

 [1..100] .map (2*) .sum

Great proposal! And the only feature haskell will lack is computable go to!
And if we add both haskell would become the most expressive and
powerful programming language since INTERCAL

--max
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] re-definition of '.'

2005-11-21 Thread jerzy . karczmarczuk
Max Eronin: 

2) sequential functions application in OOP style: 


[1..100] .map (2*) .sum


Great proposal! And the only feature haskell will lack is computable go to!
And if we add both haskell would become the most expressive and
powerful programming language since INTERCAL


But we have those computed gotos already. 

Actually, all irony apart, seriously, I have a theorem for you. 

It says: 


At least 2 times per month somebody
tries to reinvent continuations. 

Jerzy Karczmarczuk 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Antti-Juhani Kaijanaho
Henning Thielemann wrote:
 Hence, spacing being significant is not Haskell-specific
 
 So Haskell is somehow BASICish -- how awful.

No, you got it backwards. I was contrasting a BASIC dialect as an
example of a space-*in*sensitive language to just about every modern
language, including Haskell.  In other words, Haskell was specifically
*not* like BASIC in my comparison.

I believe early FORTRAN is another example of a spacing-*in*sensitive
language comparable to that BASIC dialect, and *not* similar to Haskell.
-- 
Antti-Juhani
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread David Menendez
Keean Schupke writes:

 Haskell already has static records (in H98)
 
 Dynamic records are addressed by the HList library, which uses 
 extensions already present in GHC and Hugs (namely Multi-parameter 
 type-classes and function-dependancies).

Is this the case? Every implementation of HList that I've seen also uses
overlapping and undecidable instances.
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Tomasz Zielonka
On Mon, Nov 21, 2005 at 10:41:38PM +, Joel Reymont wrote:
 STM would complicate things too much for me. At least I think so. I  
 would love to use STM but I would need to fit it into type  
 ScriptState = ErrorT String (StateT World IO) just to use the  
 logger. I'm not THAT comfortable with monads.

I am talking about Software Transactional Memory, which is in
Control.Concurrent.STM. I think you confused it with State
Transformer Monad.

In your case STM would allow you to wait simultaneously on (T)MVar and
(T)Chan. It would look like this:

logger :: TMVar () - IO ()
logger die =
join $ atomically $
(do x - readTChan parent
return $ do
putStrLn x
logger die)
`orElse`
(do takeTMVar die
return (return ()))

but you have to modify the rest of code to use STM. I modified your
Conc.hs to use STM, but using the greater guarantees of STM you
could surely simplify it further (see the attached patch).

 Let me see if I understand you correctly... Are you saying that I  
 should be using getChanContents in the code below?

I am not proposing to use getChanContents. You are busy-waiting
on MVar and Chan. I just proposed a solution to stuff messages
and die-request into the same concurrency primitive, so you
can wait for both events using a single operation.

But you are right (below) that this bug doesn't explain the behaviour of
your program. It is only a performance bug.
 
 logger :: Handle - MVar () - IO ()
 logger h die =
 do empty - isEmptyChan parent
unless empty $ do x - readChan parent
  putStrLn x
  hPutStrLn h x
alive - isEmptyMVar die
when (alive || not empty) $ logger h die

 I think using Maybe is a great trick but I'm curious why so few  
 messages actually get taken out of the channel in the code above?

Actually, I am not sure. I just noticed that your code uses a bad
coding practice and could be improved. If I find some time I'll try to 
examine it more closely.

 Are  you saing that with all the checking it does not get to pull
 messages  out?

As it is, you code can impose a big performance penalty, but indeed
it shouldn't change the semantics. Perhaps I miss something.

 I see clearly how using Maybe with getChanContents will work out  
 perfectly. I don't understand why the above code is inefficient to  
 the point of printing just a few messages (out of hundreds) out on  
 Windows. I would like to understand it to avoid such mistakes in the  
 future.

Yes, this is strange. Perhaps we're both missing something obvious.

Best regards
Tomasz

New patches:

[Use STM in Conc.hs
Tomasz Zielonka [EMAIL PROTECTED]**20051122065752] {
hunk ./Conc.hs 6
+import Control.Concurrent.STM
hunk ./Conc.hs 15
-children = unsafePerformIO $ newMVar []
+children = unsafePerformIO $ atomically $ newMVar []
hunk ./Conc.hs 20
-parent = unsafePerformIO newChan
+parent = unsafePerformIO $ atomically newChan
hunk ./Conc.hs 28
-   writeChan parent $ stamp ++ :  ++ (show tid) ++ :  ++ a
+   atomically $ writeChan parent $ stamp ++ :  ++ (show tid) ++ :  ++ a
hunk ./Conc.hs 46
-do empty - isEmptyChan parent
-   unless empty $ do x - readChan parent
- putStrLn x
-   alive - isEmptyMVar die
-   when (alive || not empty) $ logger die
+join $ atomically $
+(do x - readChan parent
+return $ do
+putStrLn x
+logger die)
+`orElse`
+(do takeMVar die
+return (return ()))
hunk ./Conc.hs 58
-   logDie - newEmptyMVar
-   logDead - newEmptyMVar
-   l - forkIO (logger logDie `finally` putMVar logDead ())
+   logDie - atomically newEmptyMVar
+   logDead - atomically newEmptyMVar
+   l - forkIO (logger logDie `finally` atomically (putMVar logDead ()))
hunk ./Conc.hs 63
-  do cs - takeMVar children
+  do cs - atomically (takeMVar children)
hunk ./Conc.hs 65
- []   - do putMVar die ()
-takeMVar dead
+ []   - do atomically $ do
+putMVar die ()
+takeMVar dead
hunk ./Conc.hs 69
- m:ms - do putMVar children ms
-takeMVar m
+ m:ms - do atomically $ do
+putMVar children ms
+takeMVar m
hunk ./Conc.hs 76
-do mvar - newEmptyMVar
-   childs - takeMVar children
-   putMVar children (mvar:childs)
-   forkIO (io `finally` putMVar mvar ())
+do mvar - atomically newEmptyMVar
+   atomically $ do
+   childs - takeMVar children
+   putMVar children (mvar:childs)
+   forkIO (io `finally` atomically (putMVar mvar ()))

Re: [Haskell-cafe] Records

2005-11-21 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 07:09:33AM +0200, Antti-Juhani Kaijanaho wrote:
 Henning Thielemann wrote:
  Hence, spacing being significant is not Haskell-specific
  
  So Haskell is somehow BASICish -- how awful.
 
 No, you got it backwards. I was contrasting a BASIC dialect as an
 example of a space-*in*sensitive language to just about every modern
 language, including Haskell.  In other words, Haskell was specifically
 *not* like BASIC in my comparison.
 
 I believe early FORTRAN is another example of a spacing-*in*sensitive
 language comparable to that BASIC dialect, and *not* similar to Haskell.

Aren't C and C++ space insensitive (except the preprocessor)?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe