Re: Array interface refactoring

2006-02-22 Thread Donald Bruce Stewart
tomasz.zielonka:
> On Wed, Feb 22, 2006 at 03:39:48PM +1100, Donald Bruce Stewart wrote:
> > And unsafeRead/unsafeWrite are too verbose. They are usually (almost
> > always?) safe (since the code does its own checks),
> 
> The same can be said about most uses of unsafePerformIO - you wouldn't
> be using it if you weren't certain that your program will behave
> properly.
> 
> > so perhaps this essential-for-performance interface should have nicer
> > names? 
> 
> Any primitive with can destroy the nice properties of Haskell when
> *misused* should be marked as unsafe. The point is that you can do
> anything with other nice, non-unsafe functions and you will still stay
> within the semantics of the language.
> 
> If you don't like those long names, nobody is stopping you from defining
> your own local bindings. Thanks to inlining, it should be as efficient
> as using unsafeWrite/unsafeRead directly.
> 
> > They're not in the same unsafe league that unsafePerformIO is.
> 
> Why not? With unsafeWrite you can write to any address in memory, so you
> can crash the program, change values which should be constant, etc.
> Perhaps unsafeRead is not that dangerous, but you can surely cause SEGV
> with it.
> 

It's not a terribly serious suggestion ;) 

I just found that using unsafeRead/Write is very important for shootout
entries (we used it a lot -- it's the only way to beat C), but a lot
uglier on the page than (the equally dangerous) peek/poke, which get
nice short names for some reason.

Cheers,
   Don
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Pragmas for FFI imports

2006-02-22 Thread Simon Marlow
On 21 February 2006 18:14, Einar Karttunen wrote:

> On 21.02 16:50, Simon Marlow wrote:
>> I lost the argument for include files, but this is why libraries
>> cannot currently be specified inside source files.  Back in the FFI
>> discussion, we didn't have Cabal, but now that we do, Cabal is the
>> natural place to specify these things.
> 
> Cabal is a good place, but does not handle very well optional
> dependencies that most programs linking against the library
> don't need.
> 
>> I don't understand this - surely if you just put those two modules in
>> separate packages, then everything works?  Or is it that you don't
>> want to do that?
> 
> Think about a database library supporting e.g. mysql, postgresql,
> sqlite and odbc. Now it needs six packages to do this:
> 1) foo-common for common code that does not import any of the
> implementations 2) foo-mysql (depends on 1)
> 3) foo-pgsql (depends on 1)
> 4) foo-sqlit (depends on 1)
> 5) foo-odbc  (depends on 1)
> 6) foo (this has a connect function which uses any of the above, thus
>depends on 1, 2, 3, 4, 5)
> 
> I don't consider this very good design and in practise this is quite
> tedious for the library writer.

This is exactly what you need to do.  The rationale is this:  for
simplicity, packages are the unit in several concepts: distribution,
dependency, versioning, licensing, dynamic linking, include file
dependencies, external library dependencies, and more.  If we start
confusing the issue by having smaller units for some of these concepts,
things get even more complicated.  

I don't think that requiring a package distinction in order to have a
distinction between external library dependencies is too onerous.
Packages are supposed to be lightweight things - if it is too difficult
to divide a package, then we should address that in the tools and
infrastructure.  (I think it is more difficult than it needs to be right
now, but we have been thinking about how groups of packages should look
to the Cabal user recently - see discussions on the libraries list).

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: the MPTC Dilemma (please solve)

2006-02-22 Thread Simon Peyton-Jones
I would not say that it's well-specified, no.   What we do know is this:
GHC may loop if you use -fallow-undecidable-instances -- but if it
terminates, the program is well typed and should not "go wrong" at
runtime.

S

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Ashley Yakeley
| Sent: 21 February 2006 20:13
| To: haskell-prime@haskell.org
| Subject: Re: the MPTC Dilemma (please solve)
| 
| Simon Peyton-Jones wrote:
| 
| > Of course -fallow-undecidable-instances still lifts all
restrictions,
| > and then all bets are off.
| 
| Is the behaviour of GHC with -fallow-undecidable-instances (and
| -fcontext-stack) well-understood and specifiable? It is a very useful
| option, as you can join (meet?) classes like this:
| 
|class P a
|class Q a
| 
|class (P a,Q a) => PQ a
|instance (P a,Q a) => PQ a
| 
| --
| Ashley Yakeley
| 
| ___
| Haskell-prime mailing list
| Haskell-prime@haskell.org
| http://haskell.org/mailman/listinfo/haskell-prime
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Array interface refactoring

2006-02-22 Thread Simon Peyton-Jones
|  Perhaps this e-mail could be read more generally as a
| request to consistencify/update the (Data) libraries
| in general 
...
| 
|  Is this possible for Haskell'?  Or is this too much
| of a break?  If it's possible, I'm happy to build a
| wiki page for discussion (I noticed that a short page
| has been started.)

Library design is certainly part of the Haskell' process, as I
understand it.  And the refactoring you describe sounds sensible and
desirable.  What it needs is someone willing to take up the cudgels and
do it.  Library design takes real work.

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Array interface refactoring

2006-02-22 Thread bulat . ziganshin
Hello Simon,

Wednesday, February 22, 2006, 1:05:11 PM, you wrote:

SPJ> Library design is certainly part of the Haskell' process, as I
SPJ> understand it.  And the refactoring you describe sounds sensible and
SPJ> desirable.  What it needs is someone willing to take up the cudgels and
SPJ> do it.  Library design takes real work.

i can take this work. although i personally thinks that this library
more needs internal than external changes and interfaces are close to
fine


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: Pragmas for FFI imports

2006-02-22 Thread Simon Marlow
On 22 February 2006 01:33, John Meacham wrote:

> On Tue, Feb 21, 2006 at 04:50:20PM -, Simon Marlow wrote:
>> First of all, my position on this has always been (since we argued
>> about this during the design of the FFI) that include files and
>> libraries should be kept out of the source file and specified
>> separately, since they are a part of the build infrastructure, and
>> vary across platforms. 
>> 
>> I lost the argument for include files, but this is why libraries
>> cannot currently be specified inside source files.  Back in the FFI
>> discussion, we didn't have Cabal, but now that we do, Cabal is the
>> natural place to specify these things.
> 
> the problem is that package granularity is way to big for specifying
> dependencies, jhc wants all dependencies attached to each FFI import.
> the reason being that it collects only the dependencies for things
> that are actually used so for instance the following works:
> 
> foreign import ccall "fcntl.h open" c_unix_open ...
> foreign import ccall "win32.h OpenFile" c_win_open ...
> foreign import lvm "lvmOpen" c_lvm_open ...
> 
> 
> openFile = case os of
> "unix" -> ... c_unix_open ...
> "lvm" ->  c_lvm_open ...
> "win32" ->..  c_win_open ...
> 
> and all the intermediate code remains platform independent.

You could still break this into packages - I guess I'm not convinced by
the argument that packages have too large granularity.  It seems nice,
even, to put the OS-specific code into separate packages in this
example.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Array interface refactoring

2006-02-22 Thread Simon Marlow
On 22 February 2006 09:48, Donald Bruce Stewart wrote:

> It's not a terribly serious suggestion ;)
> 
> I just found that using unsafeRead/Write is very important for
> shootout entries (we used it a lot -- it's the only way to beat C),
> but a lot uglier on the page than (the equally dangerous) peek/poke,
> which get nice short names for some reason.

The obvious conclusion if you follow this line of reasoning is that we
should rename Foreign.* to Unsafe.Foreign.*  :-)

More seriously, I think the rationale here is that if we added "unsafe"
to every part of the FFI that could possibly be used to shoot yourself
in the foot, that would be an awful lot of "unsafe"s.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: superclass implications

2006-02-22 Thread Claus Reinke

   >   class Monad m => MonadPlus mif  <..oops..>

if Monad m, then declare MonadPlus m as follows..


This gloss doesn't make sense. The act of declaration is a constant 
static property of the module, and cannot be conditional on the property 
of a variable. The module _always_ declares the class.


would be nice, wouldn't it? and since section 4.3.1 "Class Declarations"
skirts the issue, one might assume that it does (*). but if you look through
4.3.2 "Instance Declarations", you'll find:

   1. .. In other words, T must be an instance of each of C's superclasses 
   and the contexts of all superclass instances must be implied by cx'. 


and

   If the two instance declarations instead read like this: 
   ...
   then the program would be invalid. 


in other words, whether or not the superclass instances exist does not
just affect whether or not the subclass instances exist, it affects whether
or not the instance declaration, and hence the whole program, is valid.
if you don't have any ms for which Monad m holds, you won't be able
to declare any instances of MonadPlus m.

it doesn't matter whether you never use those instances. this program 
is simply not valid (but adding an A Int instance makes so):


   class A x
   class A x => B x 
   instance B Int 

(*) granted, the class declaration alone might still be considered valid, 
but you couldn't actually use it for anything, so I'm not sure that makes 
a difference. and whether or not the instance declaration is statically 
valid _is_ conditional on the existence of other instances.


it is this early/eager checking of superclass constraints that I find odd,
and different from all other constraint handling. it means that I can't use
superclass constraints to lift out common method constraints, because

   class  => B x where {m1 :: ;..; mn :: }

is not equivalent to 


   class B x where {m1 ::  => ;..; mn ::  => }

[even if the conditions for variables in contexts would not rule that out]
whereas such lifting is possible for common constraints in instances.

it also means that I have to provide superclass instances at the _point
of declaration_ of subclass instances - I can not defer that obligation
to the _point of use_.

cheers,
claus

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


RE: Module System

2006-02-22 Thread Simon Marlow
On 21 February 2006 18:22, Henrik Nilsson wrote:

> Georg wrote:
> 
>  > Well, the hierarchical module system as it is implemented today and
>  > how it is proposed for being included into Haskell' uses the file
>  > system to locate modules.
> 
> Yes, tools need to, somehow, locate modules.
> 
> Yes, for portability reasons, it is convenient if tools support common
> conventions.
> 
> But that does not mean that the *language standard* should nail down
> these details.

While I've always liked the principle that the language spec is
completely independent of implementation details such as the filesystem,
I'm not sure we can hang on to it forever.

This is not the first time that someone has made the same suggestion as
Georg, and for good reasons: there's a lack of modularity in the current
design, such that renaming the root of a module hierarchy requires
editing every single source file in the hierarchy.  The only good reason
for this is the separation between language and implementation.

There are more elaborate proposals, such as "grafting", where a module
sub-hierarchy can be placed at an arbitrary position in the namespace at
compile time, which boils down to renaming modules at compile time
again, and violating the language/implementation separation.

I don't have anything concrete to say (sorry!) except that I'm not
convinced that the language spec should require a module to declare its
full name in the source code any more.  I certainly don't believe that
the language spec should say anything at all about file systems, but it
should be open to the possibility that "unspecified
implementation-dependent behaviour" might affect how module definitions
are paired with import declarations.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Module System

2006-02-22 Thread Henrik Nilsson

Dear all,

Simon M. wrote:

> This is not the first time that someone has made the same suggestion
> as Georg, and for good reasons: there's a lack of modularity in the
> current design, such that renaming the root of a module hierarchy
> requires editing every single source file in the hierarchy.

Point taken. (I did say that Georg's proposal had its merits, and this
is basically what I meant.)

> I don't have anything concrete to say (sorry!) except that I'm not
> convinced that the language spec should require a module to declare
> its full name in the source code any more.

Personally, I like the fact that the module names are explicitly there,
but again, yes I can certainly see that it can be inconvenient.

But as always, how much "refactoring support" should there be in
the language, and what does properly belong in tools?

Anyway, I'm not fundamentally opposed to more flexible imports,
I'm only worried about too many environmental dependencies unnecessarily
infiltrating the language spec.

As long as a discussion would be in terms of a hierarchical
module name space (or some other language-centred notion like
that), I have no objects to the discussion as such.

> I certainly don't believe that
> the language spec should say anything at all about file systems, but
> it should be open to the possibility that "unspecified
> implementation-dependent behaviour" might affect how module
> definitions are paired with import declarations.

Yes, that might be necessary in the end.

Best,

/Henrik

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]


This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: Export lists in modules

2006-02-22 Thread Malcolm Wallace
John Meacham <[EMAIL PROTECTED]> wrote:

> Malcolm Wallace wrote:
> > There is also the issue that we might adopt the proposal to allow
> > (and perhaps eventually, to require) type signatures on export
> > lists.
> 
> All I have to say is "please, no" to the requiring part that is.

I don't seriously propose for haskell-prime that signatures should be
required on exports.  Just permitting them would be a large and useful
step up already.  But the argument about whether to specify a module
interface completely and explicitly in the source file might arise again
in the next standardisation process, where I can see the balance might
tip more in favour of compulsion.

> I totally think type signatures in export lists should be allowed
> optionally with the exact same meaning as if they were specified at
> the top level within the module.

At the moment, only one type signature is permitted per entity (except
for FFI foreign exports, where the exported signature may be more
specific than the definitional signature).  My proposal is that the
normal export list can have signatures /in addition to/ the definitional
signature, but that if there are thus two signatures for an entity, they
must be identical.  This is to prevent the case where one modifies the
definition of the function, making it more general, but forgets to
modify the corresponding export.

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


Re: Export lists in modules

2006-02-22 Thread Johannes Waldmann
Malcolm Wallace wrote:

> ... but that if there are thus two signatures for an entity, they
> must be identical.  This is to prevent the case where one modifies the
> definition of the function, making it more general, but forgets to
> modify the corresponding export.

Sounds like the perfect example to illustrate the point
that information shouldn't be doubled in the first place.

Can you say why you want the type in the export list?
Or really, why you want an export list at all?

Presumably because it constitutes the module's "interface",
but it is an ad-hoc thing (one interface per module).
We already have the concept of "type class"
which gives us re-usable interfaces. Isn't that much better?

I was discussing that in (the second paragraph of):
http://www.haskell.org//pipermail/haskell-prime/2006-January/000230.html

Respectfully submitted,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

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


Re: Export lists in modules

2006-02-22 Thread John Meacham
On Wed, Feb 22, 2006 at 12:07:44PM +, Malcolm Wallace wrote:
> At the moment, only one type signature is permitted per entity (except
> for FFI foreign exports, where the exported signature may be more
> specific than the definitional signature).  My proposal is that the
> normal export list can have signatures /in addition to/ the definitional
> signature, but that if there are thus two signatures for an entity, they
> must be identical.  This is to prevent the case where one modifies the
> definition of the function, making it more general, but forgets to
> modify the corresponding export.

Another reason we might want to allow both is for scoped type variables.
We should probably only allow type variables in the definitional
signature to scope over the body of the function since it just doesn't
feel right for something in the export list to scope over the body of a
function in the module.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Module System

2006-02-22 Thread David Roundy
On Tue, Feb 21, 2006 at 03:50:29PM +, Henrik Nilsson wrote:
> I'm already somewhat unhappy about the way most present Haskell tools map
> module names to path names (I'd generally prefer to have the possibility
> to flatten my file hierarchies by, say, using dots in my file names), but
> at least these assumptions are not in the Haskell 98 language definition.

I'd like to second this.  I've been annoyed by the fact that ghc requires
extra subdirectories in order to use hierarchical modules, and would be
doubly annoyed if the language definition declared that this couldn't be
fixed.  jhc's behavior sounds nicer, but I'd rather there were the
possibility of naming our haskell files whatever we liked.  Currently, as
far as I can see, we can only do this with Main, and even then there are
weirdnesses in ghc because Main.hi gets generated.
-- 
David Roundy
http://www.darcs.net
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Module System

2006-02-22 Thread Georg Martius
Dear all,

Okay, I see the point of not including the environment into the spec. However 
other languages like Java for example do this as far as I know. 
Anyway, I would like to hear your comments about point 2-4 of my original 
mail, because there are more important from my point of view. These don't 
depend on how files are named or located after all.

Good day!
Georg

On Wednesday 22 February 2006 12:29, Henrik Nilsson wrote:
> Dear all,
>
> Simon M. wrote:
>  > This is not the first time that someone has made the same suggestion
>  > as Georg, and for good reasons: there's a lack of modularity in the
>  > current design, such that renaming the root of a module hierarchy
>  > requires editing every single source file in the hierarchy.
>
> Point taken. (I did say that Georg's proposal had its merits, and this
> is basically what I meant.)
>
>  > I don't have anything concrete to say (sorry!) except that I'm not
>  > convinced that the language spec should require a module to declare
>  > its full name in the source code any more.
>
> Personally, I like the fact that the module names are explicitly there,
> but again, yes I can certainly see that it can be inconvenient.
>
> But as always, how much "refactoring support" should there be in
> the language, and what does properly belong in tools?
>
> Anyway, I'm not fundamentally opposed to more flexible imports,
> I'm only worried about too many environmental dependencies unnecessarily
> infiltrating the language spec.
>
> As long as a discussion would be in terms of a hierarchical
> module name space (or some other language-centred notion like
> that), I have no objects to the discussion as such.
>
>  > I certainly don't believe that
>  > the language spec should say anything at all about file systems, but
>  > it should be open to the possibility that "unspecified
>  > implementation-dependent behaviour" might affect how module
>  > definitions are paired with import declarations.
>
> Yes, that might be necessary in the end.
>
> Best,
>
> /Henrik

-- 
 Georg Martius,  Tel: +49 177 6413311  -
--- http://www.flexman.homeip.net --


pgpCG9MAm2yDc.pgp
Description: PGP signature
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Pragmas for FFI imports

2006-02-22 Thread bulat . ziganshin
Hello Simon,

Wednesday, February 22, 2006, 12:53:09 PM, you wrote:

SM> simplicity, packages are the unit in several concepts: distribution,
SM> dependency, versioning, licensing, dynamic linking, include file
SM> dependencies, external library dependencies, and more.  If we start
SM> confusing the issue by having smaller units for some of these concepts,
SM> things get even more complicated.  

i definitely don't want to create packages just to add to my
application several C-defined functions. and moreover i think that it
will make using FFI in Haskell harder for novices. now it's rather
simple with ghc and i will be happy to preserve this simplicity. this
means "please preserve ability to specify include files and make this
uniform for all haskell'-compilers".

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Export lists in modules

2006-02-22 Thread Malcolm Wallace
Johannes Waldmann <[EMAIL PROTECTED]> wrote:

> Sounds like the perfect example to illustrate the point
> that information shouldn't be doubled in the first place.

Yes, I suppose one could argue that.

> Can you say why you want the type in the export list?

As a compact description of the module interface.  Many people already
do it, except that the signature is in a comment, and therefore not
checked.

> Or really, why you want an export list at all?

An explicit interface would be useful for many purposes besides
machine-checked documentation.  For instance, it could be used to
eliminate the hs-boot or hi-boot files used by some compilers when
dealing with recursive modules.

> Presumably because it constitutes the module's "interface",
> but it is an ad-hoc thing (one interface per module).
> We already have the concept of "type class"
> which gives us re-usable interfaces. Isn't that much better?

The near correspondence between type classes, modules, and records, is
well-known, yet still they are separate concepts in Haskell.  Perhaps
one day they will be merged.  However, in the meantime, for both records
and classes one is forced to give a signature to the contained
elements/methods.  For consistency, modules should do the same...

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


Re[2]: Module System

2006-02-22 Thread bulat . ziganshin
Hello David,

Wednesday, February 22, 2006, 4:09:07 PM, you wrote:

DR> I'd like to second this.  I've been annoyed by the fact that ghc requires
DR> extra subdirectories in order to use hierarchical modules, and would be

i'll be third :)  i planned to fill a ticket but still not done it

DR> doubly annoyed if the language definition declared that this couldn't be
DR> fixed.  jhc's behavior sounds nicer, but I'd rather there were the
DR> possibility of naming our haskell files whatever we liked.  Currently, as
DR> far as I can see, we can only do this with Main, and even then there are
DR> weirdnesses in ghc because Main.hi gets generated.

and Main.o also. i think that it is not right

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Module System

2006-02-22 Thread Johannes Waldmann
David Roundy wrote:

> DR> fixed.  jhc's behavior sounds nicer, but I'd rather there were the
> DR> possibility of naming our haskell files whatever we liked.  Currently, as
> DR> far as I can see, we can only do this with Main, and even then there are
> DR> weirdnesses in ghc because Main.hi gets generated.

I don't think this is weird. Java does the same thing:
you can have "class Foo {}" in a file named Bar.java,
you can compile the file, and you get Foo.class.
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

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


Re: The worst piece of syntax in Haskell

2006-02-22 Thread kahl
Ashley Yakeley <[EMAIL PROTECTED]> wrote:
 > 
 > Josef Svenningsson wrote:
 > 
 > > This is one of the things that the Clean people got right. In Clean, my 
 > > examples from above would look like:
 > > 
 > >  > class MonadPlus m | Monad m where ...
 > >  >
 > >  > class Ix a | Ord a where ..
 > >  >
 > >  > instance Eq (Ratio a) | Integral a where ...
 > 
 > Not quite the same complaint, but I've always been bothered by the 
 > inconsistent use of "=>". I would prefer "A => B" to mean "if A, then 
 > B". Accordingly:
 > 
 >class Monad m <= MonadPlus m
 >class Ord a <= Ix a
 >instance Integral a => Eq (Ratio a)
 >foo :: (Monad m) => [m a] -> m [a]

It may be useful to keep in mind how this would translate into the module
language of OCaml
(remember that in *ML, type application is written argument-first):

module type MonadPlus =
   functor (M: Monad) ->
 sig
   type m 'a = 'a M.m
   val mzero : 'a m
   val mplus : 'a m -> 'a m -> 'a m
 end;;

module type Eq =
  sig
type t
val (==) : t -> t -> bool
val (/=) : t -> t -> bool
  end;;

module IntegralRatioEq :: Eq
   functor (I: Integral) ->
 struct
   type t = I.t ratio
   let (==) = ...   
 end;

I am not claiming that all aspects of the syntax are more elegant,
but I think it makes the semantics clearer.
(Of course, OCaml does not have implicit module arguments,
 so ``foo :: (Monad m) => [m a] -> m [a]'' has no direct translation.)

See also ``Named Instances for Haskell Type Classes'':
http://www.cas.mcmaster.ca/~kahl/Publications/Conf/Kahl-Scheffczyk-2001.html




 > >  > instance Eq (Ratio a) | Integral a

Those who think of type classes as a medium for logic programming
might indeed prefer

instance Eq (Ratio a) :- Integral a

;-)


Wolfram
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Export lists in modules

2006-02-22 Thread Simon Peyton-Jones
| I don't seriously propose for haskell-prime that signatures should be
| required on exports.  Just permitting them would be a large and useful
| step up already. 

If this is to be a serious proposal, someone had better think what to do
about classes, data types, instances and so on.

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Module System

2006-02-22 Thread Henrik Nilsson

David Roundby wrote:

> I'd like to second this.  I've been annoyed by the fact that ghc
> requires extra subdirectories in order to use hierarchical modules,
> and would be doubly annoyed if the language definition declared that
> this couldn't be fixed.  jhc's behavior sounds nicer, but I'd rather
> there were the possibility of naming our haskell files whatever we
> liked.

And I'd like to second that!

But not a Haskell' issue (I hope).

Best,

/Henrik

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]


This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: Module System

2006-02-22 Thread Ben Rudiak-Gould

Simon Marlow wrote:

there's a lack of modularity in the current
design, such that renaming the root of a module hierarchy requires
editing every single source file in the hierarchy.  The only good reason
for this is the separation between language and implementation.


I don't see how this is related to implementation. Surely all the language 
spec has to say is that the implementation has some unspecified way of 
finding the code for a module given only its canonical name, along with (if 
desired) a way of expanding a glob to a list of canonical names. Then the 
module namespace reform boils down to rules for converting partial names 
into canonical names. I can't see how any useful functionality in the module 
system could depend on a particular way of organizing code on disk.


-- Ben

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


Re: Export lists in modules

2006-02-22 Thread Malcolm Wallace
"Simon Peyton-Jones" <[EMAIL PROTECTED]> wrote:

> | I don't seriously propose for haskell-prime that signatures should
> | be required on exports.  Just permitting them would be a large and
> | useful step up already. 
> 
> If this is to be a serious proposal, someone had better think what to
> do about classes, data types, instances and so on.

As far as I can see, there is very little to change.  Here is a concrete
proposal.  A qvar in an export list may optionally have a type
signature.  A qtycon or qtycls in an export list may optionally have an
annotation saying whether it is a type, newtype, data, or class.
Instances cannot be mentioned in export lists, and this does not change.

export  -> qvar
|  qtycon [ (..) | ( cname_1, ... , cname_n ) ] (n>=0)
|  qtycls [ (..) | ( var_1, ... , var_n ) ] (n>=0)
|  module modid

becomes

export  -> qvar [ :: type ]
|  [type]qtycon
|  [newtype] qtycon [ (..) | ( cname_1, ... , cname_n ) (n>=0)
|  [data]qtycon [ (..) | ( cname_1, ... , cname_n ) (n>=0)
|  [class]   qtycls [ (..) | ( var_1, ... , var_n ) (n>=0)
|  module modid

As far as import entity lists are concerned, we permit an optional
annotation for type synonyms, newtypes, datatypes, and classes:

import  -> var
| tycon [ (..) | ( cname_1, ... , cname_n ) ]   (n>=0)
| tycls [ (..) | ( var_1, ... , var_n ) ]   (n>=0)

becomes
 
import  -> var
| [type]tycon
| [newtype] tycon [ (..) | ( cname_1, ... , cname_n ) ] (n>=0)
| [data]tycon [ (..) | ( cname_1, ... , cname_n ) ] (n>=0)
| [class]   tycls [ (..) | ( var_1, ... , var_n ) ] (n>=0)

Anyone see any difficulties?

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


Re: Export lists in modules

2006-02-22 Thread Wolfgang Jeltsch
Am Dienstag, 21. Februar 2006 21:59 schrieb Ketil Malde:
> Wolfgang Jeltsch <[EMAIL PROTECTED]> writes:
> > On the other hand, sometimes it makes sense to have a "mostly qualified"
> > import.  For example, if you import Data.Set or Data.Map you might want
> > only the type constructors to be imported unqualified and the rest to be
> > imported qualified.
>
> Personally, I would greatly prefer to have libraries that do not clash
> with common Prelude functions.

I would solve this problem by reducing the Prelude to just a core.  List 
function could go, for example, (mostly) into Data.List.

> I find it quite annoying to always have to import these modules twice, and
> still have to qualify many uses.
>
> If you always have to qualify it, what's the advantage of
> Data.Set.empty over emptySet again?  At least with 'emptySet' I know
> what to grep for.

I would import Data.Set as Set.  So I would use Set.empty instead of emptySet.  
The advantage is that Set.empty is more structured.  You can easily 
distinguish the kind of operation (empty) and the type you are working with 
(Set).

> -k

-w
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: New syntax

2006-02-22 Thread Wolfgang Jeltsch
Am Dienstag, 21. Februar 2006 22:10 schrieb Ketil Malde:
> [...]

> Template Haskell breaks expressions with $,

It's very bad that with TH enabled you cannot write sections of the form ($ x) 
anymore which are sometimes very handy.

> [...]

> (Perhaps it would be better to always require whitespace after symbolic
> infix operators?)

Of course, this wouldn't help with the above-mentioned TH-related problem.

> [...]

> -k

-w
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Export lists in modules

2006-02-22 Thread Johannes Waldmann
Malcolm Wallace wrote:

> An explicit interface would be useful for many purposes besides
> machine-checked documentation.  

I don't see why you need the signature in two places
(at the point at declaration and in the export list) for that.
Do you want the compiler to check conformance
(of the implementation with the exported type)?
Then you probably designed the interface (export list) separately
from the implementation, so they should not be both in one file.

> For instance, it could be used to
> eliminate the hs-boot or hi-boot files used by some compilers when
> dealing with recursive modules.

Isn't this problem just *created* by the current
export mechanism? See this comment
http://www.haskell.org//pipermail/haskell/2006-February/017590.html

Best regards,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

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


Re: Export lists in modules

2006-02-22 Thread Georg Martius
On Wednesday 22 February 2006 15:53, Malcolm Wallace wrote:
> "Simon Peyton-Jones" <[EMAIL PROTECTED]> wrote:
> > | I don't seriously propose for haskell-prime that signatures should
> > | be required on exports.  Just permitting them would be a large and
> > | useful step up already.
> >
> > If this is to be a serious proposal, someone had better think what to
> > do about classes, data types, instances and so on.
>
> As far as I can see, there is very little to change.  Here is a concrete
> proposal.  A qvar in an export list may optionally have a type
> signature.  A qtycon or qtycls in an export list may optionally have an
> annotation saying whether it is a type, newtype, data, or class.
> Instances cannot be mentioned in export lists, and this does not change.
>
> export  -> qvar
>
> |  qtycon [ (..) | ( cname_1, ... , cname_n ) ]   (n>=0)
> |  qtycls [ (..) | ( var_1, ... , var_n ) ]   (n>=0)
> |  module modid
>
> becomes
>
> export  -> qvar [ :: type ]
>
> |  [type]qtycon
> |  [newtype] qtycon [ (..) | ( cname_1, ... , cname_n )   (n>=0)
> |  [data]qtycon [ (..) | ( cname_1, ... , cname_n )   (n>=0)
> |  [class]   qtycls [ (..) | ( var_1, ... , var_n )   
> (n>=0)
> |  module modid
>
> As far as import entity lists are concerned, we permit an optional
> annotation for type synonyms, newtypes, datatypes, and classes:
>
> import  -> var
>
> | tycon [ (..) | ( cname_1, ... , cname_n ) ] (n>=0)
> | tycls [ (..) | ( var_1, ... , var_n ) ] (n>=0)
>
> becomes
>
> import  -> var
>
> | [type]tycon
> | [newtype] tycon [ (..) | ( cname_1, ... , cname_n ) ]   (n>=0)
> | [data]tycon [ (..) | ( cname_1, ... , cname_n ) ]   (n>=0)
> | [class]   tycls [ (..) | ( var_1, ... , var_n ) ]   
> (n>=0)
>
> Anyone see any difficulties?
No, but one question: If the type signature is given in the export lists, is 
it then necessary (or even allowed) later on?
I would vote for _not_ having it twice in the file.

Cheers,
Georg


pgpCsWo4zYkq0.pgp
Description: PGP signature
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The worst piece of syntax in Haskell

2006-02-22 Thread Wolfgang Jeltsch
Am Mittwoch, 22. Februar 2006 01:25 schrieb Claus Reinke:
> > class Monad m
> >=> MonadPlus m
> >where ...
> >
> > class Ord a
> >=> Ix a
> >where ...
> >
> > instance Integral a
> >=> Eq (Ratio a)
> >where ...
>
> still difficult?-) works just as well when the constraint lists get longer.
>
> claus

I do something similar now (use a monospace font):

class Monad m =>
  MonadPlus m where
  [...]

Using a line break has also the advantage that changes before the => cannot 
introduce the necessity for a linebreak in the part after the =>.  So the 
formatting of the part after the => is not affected.  This is especially 
useful if you want to use darcs replace.

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


Re: Export lists in modules

2006-02-22 Thread Jon Fairbairn
On 2006-02-22 at 17:31+0100 Georg Martius wrote:

> No, but one question: If the type signature is given in
> the export lists, is it then necessary (or even allowed)
> later on?  I would vote for _not_ having it twice in the
> file.

Why not? Surely redundancy is a good thing, provided that it
is checked by the compiler?  It's certainly not going to be
/required/ to put it in both places.

I can't think of why off-hand, but it seems conceivable that
one might want to use a function polymorphically within a
module but export a monomorphic version.

-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: Export lists in modules

2006-02-22 Thread Henrik Nilsson

Dear all,

Malcolm wrote:
> As far as I can see, there is very little to change.  Here is a
> concrete proposal.
> [...]
> Anyone see any difficulties?

Georg asked:
> No, but one question: If the type signature is given in the export
> lists, is it then necessary (or even allowed) later on?
> I would vote for _not_ having it twice in the file.

I'd in principle welcome the possibility to write type signatures
in export lists. (I often write them there anyway, but as comments).

But I admit I have not thought about what the caveats might be.

If type signatures in export lists are allowed, I would hope it
would be possible to put a type signature next to the actual definition
as well, though, unless that would be terribly complicated for some
reason (in which case I'd personally stick with the unannotated
export list).

/Henrik

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]


This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: The worst piece of syntax in Haskell

2006-02-22 Thread Ben Rudiak-Gould

Ashley Yakeley wrote:

  foo :: (Monad m) => [m a] -> m [a]
  instance Integral a => Eq (Ratio a)
  class Monad m <= MonadPlus m


I think the most consistent (not most convenient!) syntax would be

   foo :: forall m a. (Monad m) => [m a] -> m [a]
   instance forall a. (Integral a) => Eq (Ratio a) where {...}
   class MonadPlus m. (Monad m) && {...}

There's implicit forall quantification in instance declarations. It's 
currently never necessary to make it explicit because there are never type 
variables in scope at an instance declaration, but there's no theoretical 
reason that there couldn't be. There's no implicit quantification in class 
declarations---if you added a quantifier, it would always introduce exactly 
the type variables that follow the class name. I think it's better to treat 
the class itself as the quantifier. (And it's more like existential 
quantification than universal, hence the && instead of =>.)


As far as syntax goes, I like

   foo :: forall m a | Monad m. [m a] -> m [a]
   class MonadPlus m | Monad m where {...}

but I'm not sure what to do about the instance case, since I agree with the 
OP that the interesting part ought to come first instead of last.


-- Ben

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


RE: Export lists in modules

2006-02-22 Thread Simon Marlow
On 22 February 2006 14:54, Malcolm Wallace wrote:

> "Simon Peyton-Jones" <[EMAIL PROTECTED]> wrote:
> 
>>> I don't seriously propose for haskell-prime that signatures should
>>> be required on exports.  Just permitting them would be a large and
>>> useful step up already.
>> 
>> If this is to be a serious proposal, someone had better think what to
>> do about classes, data types, instances and so on.
> 
> As far as I can see, there is very little to change.  Here is a
> concrete proposal.  A qvar in an export list may optionally have a
> type 
> signature.  A qtycon or qtycls in an export list may optionally have
> an annotation saying whether it is a type, newtype, data, or class.
> Instances cannot be mentioned in export lists, and this does not
> change. 
> 
> export  -> qvar
> |  qtycon [ (..) | ( cname_1, ... , cname_n ) ]   (n>=0)
> |  qtycls [ (..) | ( var_1, ... , var_n ) ]
(n>=0)
> |  module modid
> 
> becomes
> 
> export  -> qvar [ :: type ]
> |  [type]qtycon
> |  [newtype] qtycon [ (..) | ( cname_1, ... , cname_n
> ) (n>=0) |  [data]qtycon [ (..) | ( cname_1, ... ,
> cname_n ) (n>=0) |  [class]   qtycls [ (..) | ( var_1,
> ... , var_n ) (n>=0) |  module modid
> 
> As far as import entity lists are concerned, we permit an optional
> annotation for type synonyms, newtypes, datatypes, and classes:
> 
> import  -> var
> | tycon [ (..) | ( cname_1, ... , cname_n ) ] (n>=0)
> | tycls [ (..) | ( var_1, ... , var_n ) ] (n>=0)
> 
> becomes
> 
> import  -> var
> | [type]tycon
> | [newtype] tycon [ (..) | ( cname_1, ... , cname_n )
> ] (n>=0) | [data]tycon [ (..) | ( cname_1, ... ,
> cname_n ) ]   (n>=0) | [class]   tycls [ (..) | (
var_1,
> ... , var_n ) ]   (n>=0) 
> 
> Anyone see any difficulties?

You're combining two extensions here - type signatures in export lists
and tagging exported entities.  Not a problem, but I don't think they're
inextricably linked.

Regarding tagging of exported entities, see this message from John
Meacham in a previous discussion:

 
http://www.haskell.org//pipermail/haskell-prime/2006-January/000226.html

basically tagging exports lets us completely separate the namespaces of
classes and tycons (currently they share the same namespace, for no
really good reason).  But you don't need to go so far as to indicate the
difference between type/data/newtype - just differentiating classes from
tycons is enough to separate the namespaces.

Indeed, the distinction between data & newtype should be a completely
private property, so we certainly shouldn't distinguish those in
exports/imports.  It's less clear to me whether type and data/newtype
should be distinguished or not, which is why I asked the question.  I'm
not sure I agree with John's answer, I'd rather just say 'type' or
'data', using 'data' for both data and newtype, like Haddock does.

BTW, I think Simon PJ was asking about how to *declare* types & classes
in export lists, given that you're adding signatures to export lists
which are a kind of declaration.  If you want to put more of the
interface into the export list, shouldn't you put it all in?

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


minimal Prelude (was Re: Export lists in modules)

2006-02-22 Thread Malcolm Wallace
Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:

> I would solve this problem by reducing the Prelude to just a core. 
> List  function could go, for example, (mostly) into Data.List.

There is a proposal to shrink the prelude to the minimum possible.  I
have just fleshed out some of the details, at the bottom of this page:
http://hackage.haskell.org/trac/haskell-prime/wiki/Prelude

Here are the details, reproduced for email discussion:

Let the Prelude itself contain only entities that relate purely to
functions - no other datatypes.

module Prelude
( (->)
, (.)
, ($)
, ($!)
, flip
, id
, const
, error
, undefined
, seq
, asTypeOf
)

Everything else that is currently in the Haskell'98 Prelude is
re-distributed across a variety of small modules.  Where a syntactic
desugaring rule currently uses an entity from the Prelude, the new
interpretation is that it uses whatever binding of that entity is in
scope - if there is no such entity in scope, it is an error.  For
compatibility, we define a wrapper module called Prelude.Standard which
re-exports the original Haskell'98 Prelude:

module Prelude.Standard
( module Prelude
, module Prelude.Num
, module Prelude.Comparison
, module Prelude.Monad
, module Prelude.List
, module Prelude.Maybe
, module Prelude.Either
, module Prelude.Tuple
, module Prelude.IO
, module Prelude.Text
)

And here are the individual fragments:

module Prelude.Num
( data Natural(..)
, data Int(..)
, data Int8(..)
, data Int16(..)
, data Int32(..)
, data Int64(..)
, data Word8(..)
, data Word16(..)
, data Word32(..)
, data Word64(..)
, data Integer(..)
, data Float(..)
, data Double(..)
, type Rational
, class Integral(..)
, class Num(..)
, class Fractional(..)
, class Real(..)
, class RealFrac(..)
, class Floating(..)
, class RealFloat(..)
, gcd, lcm
, fromIntegral, realToFrac
, numericEnumFrom, numericEnumFromTo, numericEnumFromThen
, numericEnumFromThenTo
, (^), (^^), (%)
, even, odd, subtract
)

module Prelude.Comparison
( data Bool(..)
, data Ordering(..)
, class Eq(..)
, class Ord(..)
, class Enum(..)
, class Bounded(..)
, otherwise
, (&&), (||), not, until
)

module Prelude.Monad
( class Functor(..)
, class Monad(..)
, mapM, mapM_, sequence, sequence_, (=<<)
)

module Prelude.List
( data [](..)
, all, and, any, (++), break, concat, concatMap, cycle, drop, dropWhile
, elem, filter, foldl, foldl1, foldr, foldr1, head, (!!), init, iterate
, last, length, lines, lookup, map, maximum, minimum, notElem, null
, or, product, repeat, replicate, reverse, scanl, scanl1, scanr, scanr1
, span, splitAt, sum, tail, take, takeWhile, unlines, unwords, words
)

module Prelude.Maybe
( data Maybe(..)
, maybe
)

module Prelude.Either
( data Either(..)
, either
)

module Prelude.Tuple
( data ()(..)
, data (,)(..)
, data (,,)(..)
, data (,,,)(..)
, data ()(..)
, data (,)(..)
, data (,,)(..)
, data (,,,)(..)
, data ()(..)
, data (,)(..)
, data (,,)(..)
, data (,,,)(..)
, data ()(..)
, data (,)(..)
, data (,,)(..)
, fst, snd
, unzip, unzip3, zip, zip3, zipWith, zipWith3
, curry, uncurry
)

module Prelude.IO
( data IO
, data IOError(..)
, data FilePath
, ioError, userError, catch
, print
, putChar, putStr, putStrLn
, getChar, getLine, getContents, interact
, readFile, writeFile, appendFile, readIO, readLn
)

module Prelude.Text
( data Char(..)
, type String
, class Read(..)
, class Show(..)
, type ReadS
, type ShowS
, read, reads, readParen, lex
, shows, showString, showParen, showChar
)

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


Re[3]: Array interface refactoring

2006-02-22 Thread Alson Kemp
Bulat,

> SPJ> Library design is certainly part of the
> Haskell' process, as I
> SPJ> understand it.  And the refactoring you
> describe sounds sensible and
> SPJ> desirable.  What it needs is someone willing to
> take up the cudgels and
> SPJ> do it.  Library design takes real work.
> 
> i can take this work. although i personally thinks
> that this library more needs internal than external 
> changes and interfaces are close to
> fine

  Since I'm not a Haskell expert, I'm of the opposite
mind: the internal stuff seems fine to me (the joy of
ignorance), but the external face is rather confusing.
 The number of Wiki pages and mailing list discussions
dedicated to the peculiarities of the libraries
suggest that others were confused, too.  [Newbies are
always confused, so this isn't a bullet-proof
argument.]  

  I think that simply reviewing and revising library
function names while deprecating the old ones woudl
provide much improvement in return for little
breakage.

  In any case, if you would (1) start the process or
(2) recommend how we start this process up, I'd be
more than happy to contribute ideas/suggestion/sweat,
whatever the result.  

  - Alson
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Export lists in modules

2006-02-22 Thread Malcolm Wallace
"Simon Marlow" <[EMAIL PROTECTED]> wrote:

> You're combining two extensions here - type signatures in export lists
> and tagging exported entities.  Not a problem, but I don't think
> they're inextricably linked.

Indeed.  I made them separate pages on the wiki.  They were combined in
my email only because Simon PJ asked how they related to each other.
Although I now see that was not really his question at all.

>   But you don't need to go so far as to indicate
> the difference between type/data/newtype - just differentiating
> classes from tycons is enough to separate the namespaces.

Yes.  However it could be slightly confusing that one writes "newtype"
in the module body, but "data" in the module header?

>   It's less clear to me whether type and data/newtype
> should be distinguished or not, which is why I asked the question. 

They are already distinguished in ghc.  It always complains to me when I
write
Foo(..)
in an export list, where the Foo is a type synonym rather than a
datatype.  (Not that I necessarily agree with ghc's behaviour here...
:-)  You will notice that for this reason, the export production for
"type Foo" does not permit a subordinate list.  However, I would be
equally happy to combine type/newtype/data into a single keyword for
exports.

> BTW, I think Simon PJ was asking about how to *declare* types &
> classes in export lists, given that you're adding signatures to export
> lists which are a kind of declaration.  If you want to put more of the
> interface into the export list, shouldn't you put it all in?

Yes, I see the point.  In the fullness of time, perhaps we will indeed
specify the module interface in full, including datatype definitions.
But for the moment, I am more interested in regularising existing
practice.

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


Re: Array interface refactoring

2006-02-22 Thread Alson Kemp
> Bruce Stewart wrote:
> > And unsafeRead/unsafeWrite are too verbose. They
> are usually (almost
> > always?) safe (since the code does its own
> checks),
> 
> The same can be said about most uses of
> unsafePerformIO - you wouldn't
> be using it if you weren't certain that your program
> will behave
> properly.
> 
> > so perhaps this essential-for-performance
> interface should have nicer
> > names? 
> 
> Any primitive with can destroy the nice properties
> of Haskell when
> *misused* should be marked as unsafe. The point is
> that you can do
> anything with other nice, non-unsafe functions and
> you will still stay
> within the semantics of the language.

 Based on a ShootoutEntry discussion that Don and I
had, I was under the mistaken impression that
"unsafeWrite" broke an ST assumption because
"unsafePerformIO" broke an IO assumption.

 However, I think that I agree with both of you
because we're using multiple definitions of "unsafe". 
 I see these as different degrees of "unsafe":
 unsafePerformIO - breaks an IO assumption;
 unsafeWrite - doesn't do a bounds check...

>With unsafeWrite you can write to any address in
memory, so 
>you can crash the program 
  hmm...  If I put an incorrect index into
IArray.write, Ix.index errors and the program
exits/dies/crashes (without SEGV).  This doesn't seem
much "safer".
  To be "safe":
readArray :: (MArray a e m, Ix i) => a i e -> i -> m e
writeArray :: (MArray a e m, Ix i) => a i e -> i -> e
-> m ()
  could be
readArray :: (MArray a e m, Ix i) => a i e -> i -> m
(Maybe e)
writeArray :: (MArray a e m, Ix i) => a i e -> i -> e
-> m (Maybe ())
  ...but this seems to be carrying it a bit far.


 I think that I'd prefer clear markings for different
specializations:
 unsafePerformIO - UNSAFE; use with caution;
 writeArray  - write to an array; returns m (Maybe
()); very safe;
 writeArray_q- write _quickly without bounds
check; moderately less safe;
 foldl   - blah blah;
 foldl_s - "foldl" made more _strict. 

 - Alson
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Array interface refactoring

2006-02-22 Thread Tomasz Zielonka
On Wed, Feb 22, 2006 at 09:59:07AM -0800, Alson Kemp wrote:
> >With unsafeWrite you can write to any address in
> >memory, so 
> >you can crash the program 
>   hmm...  If I put an incorrect index into
> IArray.write, Ix.index errors and the program
> exits/dies/crashes (without SEGV).  This doesn't seem
> much "safer".

There is a huge difference - you know it will fail and how it will fail.
Also, in GHC it will throw an exception which can be caught.

On the other hand, with incorrectly used unsafeWrite your program *may*
fail, but it can also do something bizarre, like sending an email to
Santa Claus or simply returning wrong results.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML) && (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Array interface refactoring

2006-02-22 Thread Ben Rudiak-Gould
While we're on the topic, I have a couple of problems with the current array 
system that cut deeper than the naming:


* The function for getting the bounds of an MArray is pure, so the
  interface can't accommodate resizable arrays.

* unsafeAt, unsafeRead and unsafeWrite take 0-based indices, and the
  bounds checking and conversion is handled externally, based on the
  bounds you return. This means the interfaces can't support array
  windowing, at least in the multidimensional case. I'd be happy with
  windowing for one-dimensional arrays only, but there's no way to
  restrict your array type to one-dimensional index types.

-- Ben

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


Re: minimal Prelude (was Re: Export lists in modules)

2006-02-22 Thread Wolfgang Jeltsch
Am Mittwoch, 22. Februar 2006 18:12 schrieb Malcolm Wallace:
> [...]

> module Prelude.Standard
> ( module Prelude
> , module Prelude.Num
> , module Prelude.Comparison
> , module Prelude.Monad
> , module Prelude.List
> , module Prelude.Maybe
> , module Prelude.Either
> , module Prelude.Tuple
> , module Prelude.IO
> , module Prelude.Text
> )

Why Prelude.List, not Data.List, etc.?

> [...]

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


Re: Export lists in modules

2006-02-22 Thread Wolfgang Jeltsch
Am Mittwoch, 22. Februar 2006 18:27 schrieb Malcolm Wallace:
> [...]

> > But you don't need to go so far as to indicate the difference between
> > type/data/newtype - just differentiating classes from tycons is enough to
> > separate the namespaces. 
>
> Yes.  However it could be slightly confusing that one writes "newtype"
> in the module body, but "data" in the module header?

But whether a type is declared by data or by newtype is an implementation 
detail, so this distinction shouldn't be made in a part of the code which is 
supposed to specify an interface.  On the other hand, if you export 
constructors too, the distinction between newtype and data might be 
important...

> [...]

> > BTW, I think Simon PJ was asking about how to *declare* types &
> > classes in export lists, given that you're adding signatures to export
> > lists which are a kind of declaration.  If you want to put more of the
> > interface into the export list, shouldn't you put it all in?
>
> Yes, I see the point.  In the fullness of time, perhaps we will indeed
> specify the module interface in full, including datatype definitions.

Only those parts of datatype definitions which are exported.  And we would 
have to include fixity declarations too.

> [...]

> Regards,
> Malcolm

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


Re[2]: Array interface refactoring

2006-02-22 Thread Bulat Ziganshin
Hello Ben,

Wednesday, February 22, 2006, 9:47:19 PM, you wrote:

BRG> While we're on the topic, I have a couple of problems with the current 
array
BRG> system that cut deeper than the naming:

BRG>  * The function for getting the bounds of an MArray is pure, so the
BRG>interface can't accommodate resizable arrays.

i think that it is because such arrays can be implemented more
efficiently. then you can implement dynamic arrays on top of MArray
interface (although i'm not sure that this will be efficient. GHC's
classes efficiency is black magic :)

BRG>  * unsafeAt, unsafeRead and unsafeWrite take 0-based indices, and the
BRG>bounds checking and conversion is handled externally, based on the
BRG>bounds you return. This means the interfaces can't support array
BRG>windowing, at least in the multidimensional case. I'd be happy with
BRG>windowing for one-dimensional arrays only, but there's no way to
BRG>restrict your array type to one-dimensional index types.

for one-dimensional arrays it's easy to implement. i agree with you,
though, that we can move more operations to the class interface

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: minimal Prelude (was Re: Export lists in modules)

2006-02-22 Thread Malcolm Wallace
Wolfgang Jeltsch <[EMAIL PROTECTED]> writes:

> > module Prelude.Standard
> > ( module Prelude
> > , module Prelude.Num
> > , module Prelude.Comparison
> > , module Prelude.Monad
> > , module Prelude.List
> > , module Prelude.Maybe
> > , module Prelude.Either
> > , module Prelude.Tuple
> > , module Prelude.IO
> > , module Prelude.Text
> > )
> 
> Why Prelude.List, not Data.List, etc.?

No particular reason.  Either choice would be good.  (But I didn't want
to imply that everything currently in Data.List would be re-exported,
since it defines more than just Prelude entities.)

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


Re: Array interface refactoring

2006-02-22 Thread John Meacham
On Wed, Feb 22, 2006 at 06:47:19PM +, Ben Rudiak-Gould wrote:
> While we're on the topic, I have a couple of problems with the current 
> array system that cut deeper than the naming:
> 
> * The function for getting the bounds of an MArray is pure, so the
>   interface can't accommodate resizable arrays.

Indeed. this has bothered me a whole lot too. I keep on trying to
implement an expanding circular buffer and then being sad when it can't
be done.

We could fix it fairly easily, we just need to get rid of HasBounds as a
superclass of MArray and add a new method 'getBounds' that returns the
bounds in the monad and then modify the default methods to use getBounds
rather than bounds.  since they are all already in the monad this will
work just fine.

it would be almost perfectly backwards compatable, the only change would
be some code might need to list HasBounds in their type signatures
seperatly. If we can get this in before the next release of ghc that
would be really great.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Export lists in modules

2006-02-22 Thread John Meacham
On Wed, Feb 22, 2006 at 04:38:57PM +, Jon Fairbairn wrote:
> I can't think of why off-hand, but it seems conceivable that
> one might want to use a function polymorphically within a
> module but export a monomorphic version.

This would be tricky, functions have different representations depending
on their type, they would effectivly be different entities with the same
name which would cause a whole host of complications. (for instance does
Self.foo refer to the polymorphic or monomorphic version). I would think
that if multiple type signatures were allowed, they would need to be
identical. (modulo beta blah)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Export lists in modules

2006-02-22 Thread John Meacham
On Wed, Feb 22, 2006 at 05:11:26PM -, Simon Marlow wrote:
> Indeed, the distinction between data & newtype should be a completely
> private property, so we certainly shouldn't distinguish those in
> exports/imports.  It's less clear to me whether type and data/newtype
> should be distinguished or not, which is why I asked the question.  I'm
> not sure I agree with John's answer, I'd rather just say 'type' or
> 'data', using 'data' for both data and newtype, like Haddock does.

my best argument against this is to try to compile the following under
ghc in strict haskell 98 mode

> class Foo a 
> instance Foo IOError

oops!

Even if the restriction on synonyms in instance heads is lifted, being
able to use type synonyms to give true aliases for types is important
part of writing interfaces that can evolve and encapsulating
implementation details.

But more importantly, The haskell module system has a nice philosophy of
just being about controlling the namespace of what is in scope in a
module. Conflating representation details with it would just confuse
things. I'd say use 'type' for everything in the type namespace, class
for everything in the class namespace, value (or nothing) for things in
the value namespace and so forth.  We want the module system to describe
precicely what names are in scope and what entities names in a module
map too, nothing more. It is also a much simpler set of rules to
remember and much more straightforward to specify.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime