Hdirect

2001-07-24 Thread Mike Thomas

Hi there.

I get the impression someone is working on this stuff from the changes in
CVS so you probably know about these problems, but just in case (and to
prove that it is all worthwhile, for you to do this stuff), here they are:

Using the latest Win32 GHC (thanks to Reuben for the ongoing work) and CVS
source for HDirect:

- Trying to build Hdirect straight from CVS has a number of dependency
problems.  I find I have to do several iterations of make and make boot  and
make lib.  (Happy likewise has a crossdependency when bootstrapping without
installing a binary copy first)

- The dependency analysis seems to fail for IDLUtils.lhs - I have to do a
make IDLUtils.hi

- You have to build ihc.exe by bootstrapping without com first.

- make clean does not delete src/ihc.exe

- the com interface files seem to think they are in package main eg:

__interface Main PointerPrim 1 501 where
__export  PointerPrim finalFreeMemory finalNoFree primAllocFrame
primAllocMemory primFinalise primFreeBSTR primFreeMemory primNoFree;
import Prelude :: 1;
import PrelBase ! :: 1;
import PrelWord :: 1;
import PrelIOBase :: 1;

and so at build time in the comcli example:


--
miketh@NASTURTIUM //e/cvs/ghc/hdirect/examples/comcli
$ make
/cygdrive/e/ghc/ghc-5.01/bin/ghc -fglasgow-exts -package
com -fno-warn-missing-m
ethods  -O-c Quartz.hs -o Quartz.o

Quartz.hs:9:
Module `Automation' is located in package `com'
but its interface file claims it is part of package `Main'

Quartz.hs:13:
Module `Com' is located in package `com'
but its interface file claims it is part of package `Main'
make: *** [Quartz.o] Error 1

--


- various minor source problems:

Index: lib/ComDll.lhs
===
RCS file: /cvs/fptools/hdirect/lib/ComDll.lhs,v
retrieving revision 1.16
diff -r1.16 ComDll.lhs
39c39
 import Foreign
---
 import Foreign  hiding ( Ptr )
Index: lib/ComServ.lhs
===
RCS file: /cvs/fptools/hdirect/lib/ComServ.lhs,v
retrieving revision 1.16
diff -r1.16 ComServ.lhs
88c88
 import Foreign
---
 import Foreign hiding ( Ptr )
Index: lib/autoPrim.h
===
RCS file: /cvs/fptools/hdirect/lib/autoPrim.h,v
retrieving revision 1.10
diff -r1.10 autoPrim.h
100c100
 #ifdef __GNUC__
---
 #if defined(__GNUC__)  ! defined(__MINGW32__)
Index: src/Makefile
===
RCS file: /cvs/fptools/hdirect/src/Makefile,v
retrieving revision 1.57
diff -r1.57 Makefile
52c52

---
 SUPPORT_TYPELIBS = YES
Index: src/TLBWriter.lhs
===
RCS file: /cvs/fptools/hdirect/src/TLBWriter.lhs,v
retrieving revision 1.23
diff -r1.23 TLBWriter.lhs
36c36
 writeTLB :: [String] - [Decl] - IO ()
---
 --writeTLB :: [String] - [Decl] - IO ()
38c38
 writeTLB _ _ = ioError (userError (writeTLB: type library writer code not
com
piled in))
---
 --writeTLB _ _ = ioError (userError (writeTLB: type library writer code
not c
ompiled in))


Cheers (and as usual thanks for the good work)

Mike Thomas



___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



GHC derives and accepts illegal Haskell98 contexts

2001-07-24 Thread kahl


I have experimented with the definition of class assertions in section 4.1.3
in the Haskell 98 report, and found that GHC 4.08 and GHC 5.00.1
(invoked via ``ghc -c Test.hs'') both derive and accept type arguments
(in class assertions) that do not have a variable as head.

I cannot really imagine where this might hurt, though.


By the way, I find that the .hi format of 5.00 is, from a human-readability
point of view, in my opinion not optimal in that there is no separator
after the __forall-bound variables:

r2 :: __forall b (E (PrelBase.String, b)) = b - PrelBase.Bool;
^

There is no comparison with NHC since NHC still has the
``simple context restriction''.


Best regards,

Wolfram

=

module Test where

class T a where
  t :: a b c - Bool

class E a where
  e :: a - a - Bool

instance T (,) where
  t (a,b) = True

q1 :: (T a,Eq (a String b)) = a String b - Bool
q1 x = if x == x then t x else True

--r1 :: Eq (String, b) = b - Bool -- derived and accepted by GHC
--r1 :: Eq a = a - Bool   -- derived by Hugs98,
-- accepted by both Hugs98 and GHC
r1 x = q1 (asd,x)


q2 :: (T a,E (a String b)) = a String b - Bool
q2 x = if e x x then t x else True

--r2 :: E (String, b) = b - Bool  -- derived and accepted by GHC
r2 x = q2 (asd,x) -- not accepted by hugs +98

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Booting from HC files is completely broken

2001-07-24 Thread David Madore

Hi all.

I tried to compile ghc-5.00.2 on a RedHat-7.1 system by booting from
HC files.  (Actually, I have a ghc-5.00 installed, but apparently some
programs compiled with it segfault, and this makes compilation of
ghc-5.00.2 impossible.  Note that I have a working happy-1.10,
however.)

Now it seems that the distrib/hc-build script is broken.

First of all, this is a minor point, but it calls ./configure twice,
and the second time it omits passing $configopts to it, so that
anything like --prefix will fail.

But this is not the problem I have.  To avoid the above gotcha, I
manually drove the various commands.  Up to the second invocation of
configure, everything works fine.  I end up with a working
ghc-inplace (well, it seems to work).

But no interface (.hi) files.

How on earth are these supposed to be generated?  The hc-build script
calls ./configure a second time; now that does not find a working ghc
(of course: it doesn't know about the just built ghc-inplace), so
GHC= in the Makefiles, and the attempt to make all in ghc/utils
fails miserably (in a ridiculous way, in fact: since GHC=, the next
argument on the command line, viz. -ldl, becomes the command, and
GNU make looks for a program called ldl, doesn't find it, and
ignores the error because of the prepended -; similarly, some -o
commands look for a program named o and ignore the error).  I tried
passing GHC to point to the ghc-inplace program built, but that
doesn't work either (missing interface files, so ghc/utils can't be
built; and ghc/libs can't be built because of the missing ghc/utils).

It seems that we still have a chicken-and-egg problem which the .hc
files have done nothing to solve.

Any suggestion (other than starting from a binary build, which is what
I suppose I'll try now)?

(Note: I'm not subscribed to the list.  Please Cc me all replies.)

-- 
 David A. Madore
([EMAIL PROTECTED],
 http://www.eleves.ens.fr:8080/home/madore/ )

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: Booting from HC files is completely broken

2001-07-24 Thread Simon Marlow

 I tried to compile ghc-5.00.2 on a RedHat-7.1 system by booting from
 HC files.  (Actually, I have a ghc-5.00 installed, but apparently some
 programs compiled with it segfault, and this makes compilation of
 ghc-5.00.2 impossible.  Note that I have a working happy-1.10,
 however.)
 
 Now it seems that the distrib/hc-build script is broken.

Yes it is, sorry about that.  There are several open bug reports on
SourceForge relating to the broken hc bootstrapping situation.  I'm
working on fixing it, so hopefully the next release will have reliable
hc bootstrapping again.

Your particular problem can be solved by (a) getting the .hs files that
are generated from the .hsc files in the libraries, and (b) making in
ghc/lib/std and hslibs before ghc/utils.  Having the .hs files means you
don't need hsc2hs in order to build the libraries and works around the
chicken/egg problem.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: hGetContents and laziness in file io

2001-07-24 Thread Thomas Hallgren

Hi,

My guess is that there is a space leak in your program. In both function 
convert and parseAll, there are references (the variable ulf) to the 
contents of the input file, and they will probably not be released until 
the functions return (unless you use a compiler that is clever enough to 
delete references after their last use...). There might be sources of 
space leaks also in the function parse that is called from parseAll.

If your program only processes one file each time you run it, you could 
structure it like this:

main = interact parseAll'
  where
parseAll :: String - String
parseAll' = unlines . map convert' . parse'

parse' :: String - [Tree]
convert' :: Tree - String

parse' s =
  case parseOneTree s of
Good (tree,rest) - tree:parse' rest
Error err - error err

convert' tree = ...

Note that parse' is lazy: it returns the first tree before it tries to 
parse the rest of the input.

Anyway, space leaks can be hard to find and eliminate, but there are 
tools that can help. The Haskell compiler Nhc98 
(http://www.cs.york.ac.uk/fp/nhc98/) tries to generate space efficient 
code to begin with, but also provides heap profiling to help you find 
out what kind of data is occupying all the space (constructor profile), 
which functions produced the data (producer profile) which functions 
have references to the data (retainer profile), ...

Hope this helps!

Thomas Hallgren
 


Hal Daume wrote:

... the file that I'm working with is ~20mb of trees.  When I
run my program on this, it is unable to reclaim space (unless i set the
heap really high). ...

convert inF outF = do inH - openFile inF ReadMode
  ulf - hGetContents inH
  outH - openFile outF WriteMode
  parseAll outH ulf
  hClose inH
  hClose outH

parseAll outH ulf =
case parse s of
Good (tree, rest) - case convert tree of
 Good s'   - do hPutStrLn outFile s'
 Error err - do putStrLn err
Error err - do return ()


PLEASE help!



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



beginner's questions - fix f

2001-07-24 Thread Bob Koutsky

Hello,

After watching members of this list discussing some for me really 
incomprehensible details of Haskell standard, I feel sort of  silly for 
asking something probably very basic, but I'd be very grateful for any answer:
Some time ago, I have decided to educate myself in functional programming, 
and I choose Haskell as a language of choice. I purchased Haskell school 
of expression and began to study it. Everything went well, I understood 
(at least intuitively) everything, but then, suddenly, I hit a wall:


Exercise 9.9:
remainder a b = if a  b then a
 else remainder (a-b) b

fix f = f (fix f)

Rewrite remainder using fix so that it is not recursive.



Function fix left me completely puzzled. With help of hugs I found out that 
its type is ( a - a ) - a, but I have absolutely no idea how it could 
be used to do anything useful. It seems to me that argument to f on the 
right side of fix's definition must always evaluate to the same value, no 
matter how deep the recursion is, so there is no point to use it. I guess I 
am missing something very obvious, but what is it? Can somebody provide me 
with an example how to use fix for something just a bit useful, if possible 
to rewrite remainder?

thank you,
Bob Koutsky 


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: beginner's questions - fix f

2001-07-24 Thread Andreas Rossberg

Bob Koutsky wrote:
 
 remainder a b = if a  b then a
  else remainder (a-b) b
 
 fix f = f (fix f)
 
 Rewrite remainder using fix so that it is not recursive.
 
 
 Function fix left me completely puzzled. With help of hugs I found out that
 its type is ( a - a ) - a, but I have absolutely no idea how it could
 be used to do anything useful.

Function fix is a so-called fixpoint operator. Theory says that you can
formulate any computable function using only non-recursive definitions
plus fix.

 Can somebody provide me
 with an example how to use fix for something just a bit useful, if possible
 to rewrite remainder?

Try:

remainderF self a b = if a  b then a else self (a-b) b

remainder = fix remainderF

From this example it is easy to infer how to transform arbitrary
recursive definitions. Even generalising it to mutual recursion is not
difficult (and left as an exercise to the reader ;-).

All the best,

- Andreas

-- 
Andreas Rossberg, [EMAIL PROTECTED]

Computer games don't affect kids.
 If Pac Man affected us as kids, we would all be running around in
 darkened rooms, munching pills, and listening to repetitive music.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: lexical description problem in language report?

2001-07-24 Thread Wolfgang Lux

Thomas Hallgren wrote

 There seems to be a similar problem with qualified identifiers. The 
 production for lexeme includes varid, conid, etc, rather than qvarid, 
 qconid, etc. (Perhaps someone forgot to update it when qualified names 
 were introduced, in Haskell 1.3...)

Sorry we must have a different version of the report, but in my copy 
and also in the version on Simon PJ's web-pages section 2.4 (in the 
last paragraph) and appendix B include productions for the qualified 
identifiers.

Wolfgang


--
Wolfgang Lux  Phone: +49-251-83-38263
Institut fuer Wirtschaftinformatik  FAX: +49-251-83-38259
Universitaet Muenster Email: [EMAIL PROTECTED]



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Picky details about Unicode (was RE: Haskell 98 Report possible errors, part one)

2001-07-24 Thread Marcin 'Qrczak' Kowalczyk

Mon, 23 Jul 2001 11:23:30 -0700, Mark P Jones [EMAIL PROTECTED] pisze:

 I guess the intention here is that:
 
   symbol  - ascSymbol | uniSymbol_special | _ | : |  | '

Right.

 In fact, since all the characters in ascSymbol are either
 punctuation or symbols in Unicode, the inclusion of ascSymbol
 is redundant, and a better specification might be:
 
   symbol  - uniSymbol_special | _ | : |  | '

It would still be nice to explicitly list ASCII symbols, so one
doesn't need to look at Unicode specs to use ASCII-only source.

There are two places when character predicates are used in Haskell:
program source and module Char. I'm sure that we all agree that they
should be consistent with each other.

Some predicates in module Char are wrong, i.e. I don't agree with
their meaning. For example that isSpace is restricted to ISO-8859-1,
and that caseless letters are considered uppercase.

It's not clear what good definitions are, or even what set of
predicates is useful, because there is no single official source
with unambiguous and complete set of predicates. There are Unicode
character categories, Unicode property lists, and implementations of
C character predicates - all with different data. I guess Java specs
have something to tell here too.

I have an implemented proposal of improved Char predicates in QForeign
http://sf.net/projects/qforeign/. Definitions are based on both
Unicode character categories and PropList.txt from Unicode.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: beginner's questions - fix f

2001-07-24 Thread Lars Henrik Mathiesen

 From: Bob Koutsky [EMAIL PROTECTED]
 Date: Tue, 24 Jul 2001 09:49:33 +0200
 
 [...] suddenly, I hit a wall:
 
 
 Exercise 9.9:
 remainder a b = if a  b then a
  else remainder (a-b) b
 
 fix f = f (fix f)
 
 Rewrite remainder using fix so that it is not recursive.
 
 
 Function fix left me completely puzzled. With help of hugs I found out that 
 its type is ( a - a ) - a, but I have absolutely no idea how it could 
 be used to do anything useful. It seems to me that argument to f on the 
 right side of fix's definition must always evaluate to the same value, no 
 matter how deep the recursion is, so there is no point to use it. I guess I 
 am missing something very obvious, but what is it? Can somebody provide me 
 with an example how to use fix for something just a bit useful, if possible 
 to rewrite remainder?

Well, it is a kind of sleight of hand. The idea is that if you already
had a working remainder function, you could use that to write another,
like this:

 remainder2 a b = if a  b then a
  else remainder (a-b) b

That's not very interesting. But if you made the 'working' function
into an argument of a 'step' function:

 rem_step f a b = if a  b then a else f (a-b) b

you could actually define remainder like this:

 remainder3 = rem_step remainder3

Now this is still a recursive definition, but it makes it easier to
see how the fix function works in a minute. An example evaluation:

 remainder3 3 2 ==
 rem_step remainder3 3 2 ==
 if 3  2 then 3 else remainder3 (3-2) 2 ==
 remainder3 1 2 ==
 rem_step remainder3 1 2 ==
 if 1  2 then 1 else remainder3 (1-2) 2 ==
 1

Now, anything that's defined as x = f x is called a fixpoint of f.
It's possible to prove that there's only one (when f is a Haskell
function, at least) so we can talk of 'the' fixpoint.

Since we can rewrite all recursive definitions in this form, we could
get rid of all explicit recursion if we had a 'fixpoint operator' that
would solve the equation for us. That operator is usually called
'fix', and since we want fix f to be a solution to the equation, we
get the defining equation in your exercise:

 fix f = f (fix f)

This looks like a recursive definition again, but if you want a system
without explicit recursion you have to disallow this as a function. In
such a system, fix is a builtin operator, and the equation can be seen
as a rewrite rule that lets you reason about the evaluation of
expressions that contain it.

However, it turns out that Haskell is quite happy to use the
definition as it stands. Let's redo the example:

 fix f = f (fix f)
 remainder4 = fix rem_step

 remainder4 3 2 ==
 fix rem_step 3 2 ==
 rem_step (fix rem_step) 3 2 ==
 if 3  2 then 3 else (fix rem_step) (3-2) 2 ==
 fix rem_step 1 2 ==
 rem_step (fix rem_step) 1 2 ==
 if 1  2 then 1 else (fix rem_step) (1-2) 2 ==
 1

As you noted, each occurence of fix rem_step above is in a sense the
same, and could evaluate in the same way. But since the expression is
a function (in this case), how it actually behaves depends on its
arguments --- I think that's really the point you were looking for:
because Haskell is lazy, and there's no structure sharing between the
occurences, each occurence is only expanded as often as necessary.

Note that operationally, this Haskell version of the fixpoint operator
is only sort-of equivalent to a Haskell recursive definition (which is
defined in terms of a 'real' fixpoint). That's even clearer with data
structures; compare

 zeroes = 0 :: zeroes

and

 zer_step l = 0 :: l
 zeroes2 = fix zer_step

zeroes is a circular list with one element, while zeroes2 is an
infinite list with all zero elements. It may not be easy to tell the
difference from inside a Haskell program, but the sound of the disk
thrashing will sometimes alert the programmer to it.

Lars Mathiesen (U of Copenhagen CS Dep) [EMAIL PROTECTED] (Humour NOT marked)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Haskell 98 Report possible errors, part one

2001-07-24 Thread Lars Henrik Mathiesen

 From: Dylan Thurston [EMAIL PROTECTED]
 Date: Mon, 23 Jul 2001 19:57:54 -0400
 
 On Mon, Jul 23, 2001 at 06:30:30AM -0700, Simon Peyton-Jones wrote:
  Someone else, quoted by Simon, attribution elided by Dylan, wrote:
  | 2.2. Identifiers can use small and large Unicode letters. 
  | What about caseless scripts where letters are neither small 
  | nor large? The description of module Char says: For the 
  | purposes of Haskell, any alphabetic character which is not 
  | lower case is treated as upper case (Unicode actually has 
  | three cases: upper, lower and title). This suggests that the 
  | only anomaly is that titlecase letters are considered 
  | uppercase. But what is actually specified is that caseless 
  | scripts can be used to write constructor names, but not to 
  | variable names. I don't know how to solve this.
  
  I am woefully ignorant of Unicode, and I have no idea what to do
  about this one.  I therefore propose to do nothing on the grounds
  that I might easily make matters worse.
 
 In this case, what about requiring identifiers to start with an upper
 or lower case alphabetic character?

I'm not sure that makes things better. It just makes it impossible to
have identifiers in caseless scripts (some of which are alphabetic).

And whether you choose your upper or lower case alphabetic character
from Latin, Greek, Coptic, Cyrillic, Armenian, Georgian, or Deseret,
it will probably look silly in front of a variable name spelled in
Hangul.

What would make sense to me is to define that caseless letters
(Unicode class Lo) behave as lowercase, and to choose some easily
visible, culturally neutral, symbol as the official 'conid marker'.
Since the problem only arises on Unicode-capable systems, there should
be plenty of those to choose from, even outside Latin-1.

To fix Haskell 98, the least intrusive way might be to allow only
classes Ll, Lt, and Lu in identifiers, with Lt (titlecase) and Lu
counting as uppercase --- it looks like that may actually have been
the intention. And then add a note explaining that caseless scripts
can't be used because they weren't considered initially.

Lars Mathiesen (U of Copenhagen CS Dep) [EMAIL PROTECTED] (Humour NOT marked)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: beginner's questions - fix f

2001-07-24 Thread Marcin 'Qrczak' Kowalczyk

24 Jul 2001 12:04:33 -, Lars Henrik Mathiesen [EMAIL PROTECTED] pisze:

 Now, anything that's defined as x = f x is called a fixpoint of f.
 It's possible to prove that there's only one (when f is a Haskell
 function, at least) so we can talk of 'the' fixpoint.

Not necessarily only one, e.g. any value is a fixpoint of identity
function.

But there is one *least* fixpoint wrt. definedness, and it can be
effectively found. If the function is strict, the least fixpoint
is not very interesting because it's bottom, a value representing
nontermination or error.

If the function is not strict, bottom is not its fixpoint, so the
fixpoint obtained by x = f x or fix f is more interesting.

BTW, a better definition than
fix f = f (fix f)
is
fix f = let x = f x in x
because it increases sharing, avoiding recomputation.

  fix f = f (fix f)
 
 This looks like a recursive definition again, but if you want a system
 without explicit recursion you have to disallow this as a function. In
 such a system, fix is a builtin operator,

You can define fix without recursion in a typeless lambda calculus:

fix f = (\x - f (x x)) (\x - f (x x))

and this can even be stretched to fit Haskell's type system by smart
use of algebraic types.

 Note that operationally, this Haskell version of the fixpoint operator
 is only sort-of equivalent to a Haskell recursive definition (which is
 defined in terms of a 'real' fixpoint). That's even clearer with data
 structures; compare
 
  zeroes = 0 :: zeroes
 
 and
 
  zer_step l = 0 :: l
  zeroes2 = fix zer_step
 
 zeroes is a circular list with one element, while zeroes2 is an
 infinite list with all zero elements.

This is the difference between two definitions of fix above.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: beginner's questions - fix f

2001-07-24 Thread Lars Henrik Mathiesen

 From: Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED]
 Date: 24 Jul 2001 13:05:25 GMT
 
 24 Jul 2001 12:04:33 -, Lars Henrik Mathiesen [EMAIL PROTECTED] pisze:
 
  Now, anything that's defined as x = f x is called a fixpoint of f.
  It's possible to prove that there's only one (when f is a Haskell
  function, at least) so we can talk of 'the' fixpoint.
 
 Not necessarily only one, e.g. any value is a fixpoint of identity
 function.
 
 But there is one *least* fixpoint wrt. definedness, and it can be
 effectively found.

My error. I meant to write only one relevant fixpoint. This was a
beginner's question, after all, so I wasn't going to go into too many
details.

 BTW, a better definition than
 fix f = f (fix f)
 is
 fix f = let x = f x in x
 because it increases sharing, avoiding recomputation.

And it very obviously constructs a solution to x = f x and delivers
it. But trying to explain its operational behaviour gets right back to
Haskell's builtin recursion, which wasn't what the original poster was
trying to understand.

 You can define fix without recursion in a typeless lambda calculus:
 
 fix f = (\x - f (x x)) (\x - f (x x))
 
 and this can even be stretched to fit Haskell's type system by smart
 use of algebraic types.

I know. I even posted about it to another thread about two weeks ago.
But that loses sharing again, of course.

Lars Mathiesen (U of Copenhagen CS Dep) [EMAIL PROTECTED] (Humour NOT marked)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Minor inconsistency in the report wrt to qualified names

2001-07-24 Thread Wolfgang Lux

In section 5.5.1 the report states that a top-level declaration brings 
into scope qualified and unqualified names. Thus, the following 
declaration is legal:

  module Foo where
ones = 1 : Foo.ones

However, in section 2.4 the report says External names may optionally be 
qualified in certain circumstances by prepending them with a module 
identifier. And also in section 3.2 the report says Qualified names may 
only be used to reference and imported variable or constructor, from 
which the above program would not be legal (because Foo.ones is not an 
imported constructor or variable).

In order to make the report consistent, I would suggest to change the 
section 3.2 to say:
Qualified names may be used to reference variables or constructors 
which are imported from other modules or defined at the top level.

In section 2.4, the word External should be dropped from the 
sentence.

Wolfgang



--
Wolfgang Lux  Phone: +49-251-83-38263
Institut fuer Wirtschaftinformatik  FAX: +49-251-83-38259
Universitaet Muenster Email: [EMAIL PROTECTED]



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: lexical description problem in language report?

2001-07-24 Thread Thomas Hallgren

  Wolfgang Lux wrote:

Thomas Hallgren wrote

There seems to be a similar problem with qualified identifiers. The 
production for lexeme includes varid, conid, etc, rather than qvarid, 
qconid, etc.

Sorry we must have a different version of the report, but in my copy 
and also in the version on Simon PJ's web-pages section 2.4 (in the 
last paragraph) and appendix B include productions for the qualified 
identifiers.

The version of the report I looked in is here:

http://research.microsoft.com/Users/simonpj/haskell98-revised/haskell98-report-html/lexemes.html#sect2.2
 


which is probably the same one you have, so it seems I need to clarify 
what I wrote.

Although qualified names are listed in section 2.4,and in appendix B, 
the two first productions of the grammar are:

  program -  {lexeme | whitespace }
  lexeme  -  varid | conid | varsym | consym | literal | special | 
reservedop | reservedid

There is no reference to qualified names here. I thought the purpose of 
these productions were to say that a Haskell program is correct on the 
lexical level iff there is a derivation of it in the lexical grammar, 
starting from the nonterminal program. Since qualified names are not 
part of this grammar, they are not part of the lexical syntax, which 
contradicts the text in section 5.5.1.

So, I repeat my improvment suggestions: include qvarid, qconid, etc, in 
the production for lexeme. Move the explanation of the lexical 
properties of qualified names from section 5.5.1 to section 2.4.

Regards,
Thomas Hallgren


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: beginner's questions - fix f

2001-07-24 Thread Lennart Augustsson

Marcin 'Qrczak' Kowalczyk wrote:

 BTW, a better definition than
 fix f = f (fix f)
 is
 fix f = let x = f x in x
 because it increases sharing, avoiding recomputation.

The latter definition is more likely to give you sharing, but Haskell
gives you no such guarantees.  There are also implementations that
give you sharing for the first definition.


 You can define fix without recursion in a typeless lambda calculus:

 fix f = (\x - f (x x)) (\x - f (x x))

 and this can even be stretched to fit Haskell's type system by smart
 use of algebraic types.

But those algebraic types are recursive!

-- Lennart



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: hGetContents and laziness in file io

2001-07-24 Thread Hal Daume

Okay, I understand the problem.  I would do something like the solution
you propose, except that in the input file, trees span multiple lines.  So
the input file looks something like:

(:cat S
 :subs ((() (:cat NP
 :subs ((() (:surf John)
(() (:cat VP
 :subs ((() (:surf bought))
(() (:cat NP
 :subs ((() (:surf two))
(() (:surf cars
(() (:surf .


and then there will be another one directly following it (i detect the
breaks because each one is completely surrounded in parens).

So a line-by-line parse solution won't really do the job...

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: lexical description problem in language report?

2001-07-24 Thread Christian Sievers

Thomas Hallgren wrote:

   program -  {lexeme | whitespace }
   lexeme  -  varid | conid | varsym | consym | literal | special | 
 reservedop | reservedid
 
 There is no reference to qualified names here. I thought the purpose of 
 these productions were to say that a Haskell program is correct on the 
 lexical level iff there is a derivation of it in the lexical grammar, 
 starting from the nonterminal program. Since qualified names are not 
 part of this grammar, they are not part of the lexical syntax, which 
 contradicts the text in section 5.5.1.
 
 So, I repeat my improvment suggestions: include qvarid, qconid, etc, in 
 the production for lexeme. Move the explanation of the lexical 
 properties of qualified names from section 5.5.1 to section 2.4.

You could still parse a qualified name as three lexemes.
Of course you don't want this, as this would allow white space
between them.
For the same reason, you want backquoted functions and constructors
to be only one lexeme. In order to achieve this, just use qop instead
of qvarsym and qconsym. And we need opencom, as the report says {- is
a lexeme.

So I suggest:

  lexeme  - qvarid  | qconid  | qop
   | literal | special | reservedop | reservedid | opencom


It's all not new. See:
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01596.html
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01730.html


All the best
Christian Sievers

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



newbie syntax question

2001-07-24 Thread Cagdas Ozgenc



Hi,

I am extremely new to Haskell. This will be my 
first question, so go easy. I have just read Chapter 1 on Simon Thompson's 
book.

for example a function declaration is given as 
follows

scale : : Picture - Int - 
Picture


If the first two types are input variables why does 
the syntax require me to use arrows twice? I mean isn't the following syntax 
more readable (hypothetically)?

scale : : Picture , Int - Picture


Is there a specific reason not to be able to 
distinguish the input parameters from the output parameter?

Thanks



RE: newbie syntax question

2001-07-24 Thread Memovich, Gary



Actually, all functions in Haskell take only one argument, although the 
people writing the program usually don't think of it this 
way.

scale 
could alternatively have been defined with type

 scale :: (Picture, Int) - Picture

which 
looks more like what we would expect in a function of two arguments. But 
even here there is actually only a single argument, which happens to be a pair 
of values.

The 
given declaration

 scale :: Picture - Int - 
Picture

is 
written in 'curried' form. This means that scale is a function of 
oneargument, 'Picture', and that its return value is a new function with 
type Int - Picture. That new function can immediately be applied to an 
int value so that it appears as if you called scale with two values instead of 
just one.

instead of writing

 scale pic 3

for 
example, you could have written

 (scale pic) 3

or 
even

 let x = scale pic in x 3

Which 
might make it a little easier to see what is actually 
happening.

Hope 
this helps,
-- 
Gary

  -Original Message-From: Cagdas Ozgenc 
  [mailto:[EMAIL PROTECTED]]Sent: Tuesday, July 24, 2001 1:07 
  PMTo: [EMAIL PROTECTED]Subject: newbie syntax 
  question
  Hi,
  
  I am extremely new to Haskell. This will be my 
  first question, so go easy. I have just read Chapter 1 on Simon Thompson's 
  book.
  
  for example a function declaration is given as 
  follows
  
  scale : : Picture - Int - 
  Picture
  
  
  If the first two types are input variables why 
  does the syntax require me to use arrows twice? I mean isn't the following 
  syntax more readable (hypothetically)?
  
  scale : : Picture , Int - 
Picture
  
  
  Is there a specific reason not to be able to 
  distinguish the input parameters from the output parameter?
  
  Thanks
  


Re: newbie syntax question

2001-07-24 Thread Hamilton Richards

At 3:07 PM -0500 7/24/01, Cagdas Ozgenc wrote:
Hi,   I am extremely new to Haskell. This will be my  first question,
 so go easy. I have just read Chapter 1 on Simon Thompson's  book.  
 for example a function declaration is given as  follows

   scale : : Picture - Int -  Picture

 If the first two types are input variables why does  the syntax
 require me to use arrows twice? I mean isn't the following syntax
  more readable (hypothetically)?  

 scale : : Picture , Int - Picture
   
 Is there a specific reason not to be able to  distinguish the
 input parameters from the output parameter?   Thanks  

Welcome to Haskell! May you find it as rewarding as I have.

As you read further, you'll find that Haskell allows functions to be
applied to less than their full complement of arguments. For example, if
pict :: Picture, then

scale pict

is a function which, applied to an Int, produces a Picture. That is,

scale pict :: Int - Picture

This feature, known as Currying, is very useful for making rather general
functions which can be specialized by supplying some of their arguments.

The type notation has been designed to accommodate Currying in two ways:

  0. each parameter type is followed by an arrow

  1. the arrow has been designed to be right-associative.

The arrow's right-associativity means that these two types are identical:

scale : : Picture - Int -  Picture

scale : : Picture - (Int -  Picture)

That is, you are free to think of scale as either of

a function of two arguments which returns a Picture

a function of one argument which returns (a function of
one argument which returns a Picture)

That equivalence would be a bit less clear using the comma syntax you suggest.

Cheers,

--Ham




--
Hamilton Richards, PhD   Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
Taylor Hall 5.138Austin, Texas 78712-1188
[EMAIL PROTECTED][EMAIL PROTECTED]
--



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: newbie syntax question

2001-07-24 Thread John Meacham

this should be on a list of the 10 first questions someone will ask when
learning haskell. I have introduced several friends to the language and
they all seem to ask the same things, if not always in the same order..

whats the deal with Int - Int - Int ... (currying)
what does $ mean? is it 'special' syntax? (no, just a $ b = a b)
why can't a - getChar be a = getChar in a do expression?
how do I convert an IO a to just an a? (unsafePerformIO, but that is the
wrong answer to the wrong question)
general confusion about namespaces, the difference between (a,b) the
type and (a,b) the value for instance.
how to write some basic idioms only used in an imperitive setting,
incrementing a counter, processing input, maintaining state
with variables which don't directly translate to haskell usually leading
to some confusion when you try to explain why they need to restructure
their program.

and on a more abstract level, the view of 'do' as a hack for IO rather
than monads as an independant and useful abstraction. (i find the Maybe
monad one of the better ways to introduce people to non-IO monads,
especially if they are used to Maybe in non-monadic usage.)

I have some email exchanges somewhere where I explained some of these
concepts, perhaps I will edit them and add them to the Wiki, or better
yet, find the best explanations from the list and add them... and of
course any other newbie questions other people find they encounter...

this is somewhat odd ground, because when helping someone learn the
language, I WANT people to come to these questions on their own and ask
them since it means they are thinking and noticing the places where they
need to readjust, so its maybe not a newbies FAQ, for someone evaluating
whether to learn the language, but more of a two weeks in and not quite
getting everything FAQ. 

John


-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: beginner's questions - fix f

2001-07-24 Thread Samuel E . Moelius III

 Function fix is a so-called fixpoint operator. Theory says that you can
 formulate any computable function using only non-recursive definitions
 plus fix.

Could someone point me toward a proof of this?

Furthermore, can any computable function be expressed in this form:

fix u

where u is some non-recursive term?

Sam Moelius

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Machine bit representations

2001-07-24 Thread pachinko

Hello,

Is it possible in Haskell to access the underlying machine bit representation of a 
Float or Double value?

I need to be able to be able to send this bit representation as a list of bytes in 
network byte order to a process running on a different platform (with a different host 
byte order to my platform).

For reference, I run Haskell under Linux on Intel. The processes I want to communicate 
with run under Sun Solaris, Hitachi HPUX and Java everywhere.

Any suggestions, for any Haskell translator much appreciated.

Thanks.


_
Global Virtual Desktop
http://www.magicaldesk.com


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Machine bit representations

2001-07-24 Thread Ashley Yakeley

At 2001-07-24 16:51, [EMAIL PROTECTED] wrote:

Is it possible in Haskell to access the underlying machine bit 
representation of a Float or Double value?

If you mean the _actual_ bit representation, then I hope not! But maybe 
there should be (or are) functions for converting such values to 
_standard_ platform-independent bit representations...


-- 
Ashley Yakeley, Seattle WA


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



http://www.video2flash.com. Convert your videos into flash format!

2001-07-24 Thread video2flash

---
If you are not interested in video compressing we do appologize sending you
this email. You can unsubscribe by clicking the following link:
http://www.video2flash.com/cgi-bin/un.cgi?[EMAIL PROTECTED]
---
Hello there,

We would like to inform you about the following:

Troublesome web video transfers using plug-in and virus software are now
history thanks to video2flash. Using the well proven technology of
Flashplayer, we have designed a tool that enables you to transfer your video
media with astounding simplicity.

Our conversion tool offers you the opportunity to add value to your Internet
services, TV advertisements, video banners, film previews, video clips,
training tools, news channels, etc.

Research reports from established institutions have shown that the time your
website is visited is likely to be under 6 minutes. Ample time that you may
use to show commercial messages formatted in video2flash. E.g. the average
loading time for a 30 second add is no more than 1,5 minutes via a 56K
modem.


Check out the following site http://www.video2flash.com
It's a webtool to convert videoclips into flash format. Check it out, use it
and send me feedback on the functionality: [EMAIL PROTECTED]



Some features:


No cure no pay 
Bandwidth selector 
Quality of picture selector. 
Movie dimensions selector. 
Automatic calculated preloader. 
Build in Variable to build progress bar 
100% sync of sound / picture 
Multiple screen formats. 
Can convert plain AVI and quicktime (*.mov) (we only want high quality
movies, NO asf or other windows media formats) 
No special hardware required. We handle all of the processing. 
Notification by email. 
No 'windows' lockups. 
No Headache. 
A 100% service 
Batch processing. Can handle gigs of movies at one time. 
Overview of your converted movies. 
Send movies by ftp or e-mail. 




Thanks in advance






I've send you this mail because i think you might be interested in our service.
This is NO spam. To remove yourself from our list click the following link:

http://www.video2flash.com/cgi-bin/un.cgi?[EMAIL PROTECTED]

If interested please visit our site: http://www.video2flash.com






== 
This email message is intended only for the addressee(s) and contains 
information which may be confidential and/or copyright. If you are not 
the intended recipient please do not read, save, forward, disclose, or 
copy the contents of this email. If this email has been sent to you in 
error, please delete this email and any copies or links to this email 
completely and immediately from your system. No representation is made 
that this email is free of viruses. Virus scanning is recommended and is 
the responsibility of the recipient. 
== 


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Machine bit representations

2001-07-24 Thread Matt Harden

[EMAIL PROTECTED] wrote:
 
 Hello,
 
 Is it possible in Haskell to access the underlying machine bit representation of a 
Float or Double value?
 
 I need to be able to be able to send this bit representation as a list of bytes in 
network byte order to a process running on a different platform (with a different 
host byte order to my platform).
 
 For reference, I run Haskell under Linux on Intel. The processes I want to 
communicate with run under Sun Solaris, Hitachi HPUX and Java everywhere.
 
 Any suggestions, for any Haskell translator much appreciated.
 
 Thanks.

Look at encodeFloat and decodeFloat, documented in section 6.4.6 of The
Haskell 98 Report.  They offer efficient, machine-independent access to
the components of a floating-point number.

See http://www.haskell.org/onlinereport/basic.html#sect6.4.6

Matt Harden

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Machine bit representations

2001-07-24 Thread Ken Shan

On 2001-07-24T16:51:54-0700, [EMAIL PROTECTED] wrote:
 Hello,
 
 Is it possible in Haskell to access the underlying machine bit
 representation of a Float or Double value?
 
 I need to be able to be able to send this bit representation as a
 list of bytes in network byte order to a process running on a
 different platform (with a different host byte order to my
 platform).
 
 For reference, I run Haskell under Linux on Intel. The processes I
 want to communicate with run under Sun Solaris, Hitachi HPUX and
 Java everywhere.
 
 Any suggestions, for any Haskell translator much appreciated.

If you're using GHC, you should be able to get at the raw bits of the
machine representation using some Storable + Ptr + MarshallAlloc
trickery.  (These are modules in -package lang.)

I tested the following on GHC5 on i386-linux:

module Cast (cast) where

import Storable (Storable, sizeOf, peek)
import MarshalUtils (withObject)
import IOExts (unsafePerformIO)
import Ptr (castPtr)

cast :: (Storable a, Storable b) = a - b
cast a = b where
  b | sizeOf a == sizeOf b =
unsafePerformIO $ withObject a $ peek . castPtr

I was able to get

(cast :: Int - Char) 98 == 'b'

This might work with other compilers as well, but I don't know...

Fun fun fun!  More efficient implementations?

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
« ne gâche pas ta vie pour leur idée de patrie » le bouton me dit

 PGP signature