Behaviour of div & mod with negative arguments?

2002-09-24 Thread Dr Mark H Phillips

Hi,

Does Haskell specify how div and mod should behave when
given one or both arguments negative?

Eg, in hugs we get:

div   13  = 0
div (-1)   3  = -1
div   1  (-3) = -1
div (-1) (-3) = 0

and so on.

I've had a bit of a look for where div and mod are
specified exactly, but I can only find a definition of
their type.  Are they defined anywhere?  And what is
the rational behind the negative arguments part of
the definition?

Thanks,

Mark.

P.S.  I notice in hugs if I type "-1 `div` 3" the `div`
binds to the 1 and 3 first, and only applies the "-"
at the end.  Is there a reason why the unary "-" has
weak binding?

-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

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



empty field label constructor infelicity

2002-09-24 Thread Hal Daume III

Hi again,

The report says "The expression F {}, where F is a data constructor, is
legal whether or not F was declared with record syntax, provided F has no
strict fields: it denotes F _|_1 ... _|_n where n is the arity of F."

It unclear to me why there needs to be this provision for records with
strict fields -- just let them be undefined -- but that notwithstanding,
GHC seems to do the wrong thing:

> module Foo where
> data F = F !Int deriving (Show, Eq)
> data G = G  Int deriving (Show, Eq)

If we then load it up in ghci, both "F {}" and "G {}" ellicit the same
error: "Missing field in record construction".

If we do:

Foo> case (F {}) of { F x -> "1" }

we get the exeption.  If we use G instead of F, we correctly get "1".

Hugs seems to obey the report.  For "F {}" it
give: "INTERNAL_ERROR: depConFlds" which is different from "G {}" which
yields "G" followed by "Program error: {undefined}".

For the case expressions, Hugs generates "INTERNAL ERROR: depConFlds" for
F and "1" for G.

Arguably, this is weirdness in the report, but I think it's clear that GHC
isn't doing the right thing (where right thing is defined to be what the
report says).

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

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



report definition of field names

2002-09-24 Thread Hal Daume III

Hi All,

I was just reading the report and was confused by something.  In section
3.15 "Datatype with Field Labels", it says:

"A datatype declaration may optionally include field labels for some or
all of the components of the type."

This seems to say that if you have some datatype declaration, you can
label some of the fields and not label others.  Which would imply you
could write something like:

data Foo = Foo { x :: String } Int

or something like that.  However, this disagrees strongly with the
definition in 4.2.1 for the CFG for datatypes:

topdecl   -> data [context =>] simpletype = constrs [deriving]
constrs   -> constr1 | ... | constrn
constr-> con [!] atype1 ... [!] atypek
   | (btype | !atype) conop (btype | !atype)
   | con { fielddecl1 , ... , fielddecln }
fielddecl -> vars :: (type | ! atype)

where clearly you are not allowed to mix them.

The only other interpretation that I can get out of the sentence in 3.15
is that you can use field labels for some constructors and not for other,
but that you must choose which one you want to use per constructor.  This
is certainly consistent with implementations and with the CFG.  however,
in the discussion of labelled field in section 4.2.1, it says:

"A data constructor of arity k create an object with k component"

which clearly implies that the definition of "component" has to do with
the fields within a particular constructor, not with different
constructors for the same datatype.

I suggest (I know it's late) the following change to 3.15:

Replace:
 "A datatype declaration may optionally include field labels for some
  or all of the components of the type."
With:
 "A datatype declaration may optionally include field labels.  Each
  constructor must use either labelled fields or unlabelled fields,
  but different constructors of a datatype may use whichever,
  independent of the other constructors."

Or something like that.

 - Hal
  

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

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



EACL03: Last Call for Workshop Proposals

2002-09-24 Thread Steven Krauwer


EACL-03: LAST CALL FOR WORKSHOP PROPOSALS

 Proposal submission deadline: October 1, 2002

   The EACL-03 Organizing Committee invites proposals
 for workshops to be held at EACL-03.

EACL-03 will take place in Budapest, Hungary, April 12-17, 2003
 with workshops being held on Sunday and Monday, April 13 and 14, 2003.

*  Workshop topics

 EACL-03 workshops provide organizers and participants with an
 opportunity to focus intensively on a specific topic within
 computational linguistics. Often, workshops concentrate on specific
 topics of technical interest (e.g., parsing technologies), particular
 areas of application for language processing technologies (e.g., NLP
 applied to IR), or community-wide issues that deserve attention (e.g.,
 standardization of resources and tools).

 We welcome proposals on any topic that is of interest to the EACL
 community, but we particularly encourage proposals that broaden the
 scope of our community through the consideration of new or
 interdisciplinary techniques or applications.

 We also encourage topics that are specific to the EACL community such
 as resources and tools for European or Mediterranean languages.

*  Workshop format

 Traditionally, workshops are shaped as mini-conferences, but we
 encourage proposers to consider other formats that exploit the fact
 that smaller settings allow for more interaction between participants
 (discussions, panels, working sessions). The default duration of a
 workshop is one day, but longer or shorter durations can be proposed
 (but should be justified).

 Please note that capacity limitations may cause us to request the
 organizers to shorten a workshop or to merge it with another workshop
 in a related area.

*  Financial guidelines

 The workshop organisers will benefit from the standard logistic
 facilities provided for the conference e.g., room, equipment, coffee,
 proceedings. Any additional cost should be covered by the organisers
 (especially invited speakers, PC meetings etc.).

*  Registration fees

 Participants pay a registration fee which is dependent on the duration
 of the workshop. Participants not registered for the main conference,
 pay a higher fee.

*  Proposals

 Workshop proposals should provide sufficient information to evaluate
 the quality and importance of the topic, and the size of the
 interested community. Proposals should be 2-4 pages and contain the
 following information:
   * A title and brief description of the workshop topic.
   * The target audience and projected number of participants along
 with support for the projected count. Supporting evidence could
 include a list of potential submitters, a list of conferences that
 contained papers on the proposed topic, the number of new
 companies focused on this topic, or recent funding initiatives
 that address this topic.
   * Resource needs such as room size and number of days. Include any
 special requirements for technical support (computer
 infrastructure, etc.).
   * The name, postal address, phone number, e-mail address, and
 webpage of each chair. In addition, indicate the chairs'
 background in the workshop area.
   * A preliminary programme committee

 Proposals should be submitted by electronic mail, in plain ASCII text,
 as soon as possible but no later than OCTOBER 1, 2002.

 The subject line should be: "EACL-03 WORKSHOP PROPOSAL".
 Please e-mail proposals and any inquiries to the Workshop Chair,
 Steven Krauwer ([EMAIL PROTECTED])

*  Timetable of Important Dates:

 Workshop proposals due: Oct. 1, 2002
 Notification of acceptance: Oct. 7, 2002
 Deadline for receipt of workshop Call for Papers and other publicity
 material: Oct. 21, 2002
 Send out Call for Papers: Nov. 1, 2002
 Suggested deadline for workshop paper submissions: Jan. 1, 2003
 Suggested deadline for notification of workshop paper acceptance: Jan.
 21, 2003
 Suggested deadline for camera-ready workshop papers: Feb. 13, 2003
 Workshop Dates: Apr. 13-14, 2003

*  Workshop Committee:

 Steven Krauwer (ELSNET / Utrecht University), Chair
 Jean-Pierre Chanod (Xerox Research Centre Europe, Grenoble)
 Ernst Buchberger (ÖFAI, Vienna)

*  Additional Information:

 Conference website: http://www.conferences.hu/EACL03
 Workshop website: http://www.elsnet.org/workshops-eacl2003.html

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



Re: Problems with IO

2002-09-24 Thread Ch. A. Herrmann

Hi Pavel,

> "pavel" == pavel  <[EMAIL PROTECTED]> writes:

pavel> I'm having a problem with writing a function dealing with
pavel> I/O. Maybe it's just a lack of experience or simple Haskell
pavel> knowledge because I'm just a beginer. The problem: I want to
pavel> write a function that converts an IO String into String lala
pavel> :: IO String -> String

pavel> Is it possible? If yes, how?

you cannot use (except from a dirty trick) an IO operation that
returns a string (IO String) as a string. What you can do 
--and, I assume, that's what you want to do-- is
to apply a function inside a composition of IO operations that uses the
result of a previous IO operation, e.g., function "f" in the
following program text:

main = do
string1 <- readFile "input"  <>
let result = f string1
print result <>
return ()

Note that this kind of "let" does not have a corresponding "in". 

The reason that a function like unIO :: IO a -> a
does not legally exist is that it would break a nice
theoretical property of Haskell called referential transparency
which makes reasoning about programs extremely productive.

Hope that helps.
--
 Christoph Herrmann

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



RE: Haskell 98: Behaviour of hClose

2002-09-24 Thread Simon Peyton-Jones


Glynn writes:

| 2. Regarding the buffering issue, I suggest adding something along the
| lines of the following to section 11.4.2 of the library report:
| 
| > For a stream which is associated with a terminal device, setting the
| > mode to no-buffering will also disable any line-buffering which may
| > be performed by the operating system's terminal driver.
| >
| > Similarly, setting the mode to line-buffering or block-buffering
| > will enable any line-buffering which may be performed by the
| > operating system's terminal driver.
| 
| However, it was only when analysing the existing behaviour in order to
| write that above that I became aware of the second half. This is
| potentially more problematic than the first half.

...and there are several more paragraphs (below).

I conclude that this is all very tricky, and there is no chance of
getting something that is obviously sensible into 11.4.2 in the next few
days.  Again, the swamp beckons, and we've struggled by without any such
words for many years now.  So I propose to do nothing here, rather than
risk making the situation worse.

Thank you to Glynn for trying!   There's a gold medal waiting for
someone who designs a better (portable) I/O library.

Simon



| 
| While there isn't much point disabling buffering at the stream level
| if it's still being performed by the terminal driver, there *are*
| reasons why you might wish to enable buffering at the stream level
| without enabling canonical mode (which is what the terminal driver's
| "line buffering" actually corresponds to).
| 
| E.g. in canonical mode, the EOF character (typically Ctrl-D) will
| result in a read() from the OS-level descriptor indicating EOF. In
| "raw" mode, the EOF character will be read literally (i.e. '\004' for
| Ctrl-D).
| 
| IOW, while canonical mode results in line-buffering, it also has other
| side-effects.
| 
| Another consequence, which has just sprung to mind, is that whereas
| the buffering mode of a stream is strictly user-space, and therefore
| internal to the program, the terminal driver settings are a property
| of the device, and will affect other programs which use that device.
| 
| Example: a Haskell program is run on a terminal for which canonical
| mode is enabled (which is normally the case), and that program does
| "hSetBuffering stdin NoBuffering", thereby disabling canonical mode.
| After the program terminates, canonical mode will still be disabled
| for that device.
| 
| Similar issues arise in C, i.e. you need to explicitly restore the
| terminal settings when the program terminates or is suspended (via
| SIGTSTP). However, in C, you would have to have explicitly change the
| terminal settings (with e.g. tcsetattr()), whereas Haskell does this
| "under the hood".
| 
| --
| Glynn Clements <[EMAIL PROTECTED]>
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Haskell 98: Behaviour of hClose

2002-09-24 Thread Simon Peyton-Jones

On the matter of echoing, in Section 7.1 there seem to be two
possibilities:

1.  Delete the sentence "By default, these input functions echo to
standard output." altogether.

2.  Replace the sentence by 
If the standard input (stdin) is a terminal device, 
any input on stdin is normally echoed on that device,
unless the operating system or environment has disabled
such echoing.

My original inclination was for (2), so that Joe's first program will
always work.  However, Glynn and Ross and Ferenc all favour (1).
Virtually no one has said anything else.

I therefore propose to adopt (1).  It's clear that (2) is leading into a
swamp of caveats which we just do not have time to resolve.  Any
implementation will probably do something sensible (i.e. behave like
other languages).

Simon


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