Re: In opposition of Functor as super-class of Monad

2012-10-24 Thread Duncan Coutts
On 24 October 2012 11:16, S. Doaitse Swierstra  wrote:
> There are very good reasons for not following this road; indeed everything 
> which is a Monad can also be made an instance of Applicative. But more often 
> than not we want to have a more specific implementation. Because Applicative 
> is less general, there is in general more that you can do with it.

I don't think anyone is suggesting that we force all type that are
both Monad and Applicative to use (<*>)  = ap as the implementation.
As you say, that'd be crazy.

The details and differences between the various superclass proposals
are to do with how you provide the explicit instance vs getting the
default.

The wiki page explains it and links to the other similar proposals:

http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances

Duncan

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


Re: String != [Char]

2012-03-19 Thread Duncan Coutts
On 17 March 2012 01:44, Greg Weber  wrote:
> the text library and Text data type have shown the worth in real world
> Haskell usage with GHC.
> I try to avoid String whenever possible, but I still have to deal with
> conversions and other issues.
> There is a lot of real work to be done to convert away from [Char],
> but I think we need to take it out of the language definition as a
> first step.

I'm pretty sure the majoirty of people would agree that if we were
making the Haskell standard nowadays we'd make String type abstract.

Unfortunately I fear making the change now will be quite disruptive,
though I don't think we've collectively put much effort yet into
working out just how disruptive.

In principle I'd support changing to reduce the number of string types
used in interfaces. From painful professional experience, I think that
one of the biggest things where C++ went wrong was not having a single
string type that everyone would use (I once had to write a C++
component integrating code that used 5 different string types). Like
Python 3, we should have two common string types used in interfaces:
string and bytes (with implementations like our current Text and
ByteString).

BTW, I don't think taking it out of the langauge would be a helpful
step. We actually want to tell people "use *this* string type in
interfaces", not leave everyone to make their own choice. I think
taking it out of the language would tend to encourage everyone to make
their own choice.

Duncan

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


Re: Proposal: Define UTF-8 to be the encoding of Haskell source files

2011-04-17 Thread Duncan Coutts
On Thu, 2011-04-07 at 15:44 +0200, Roel van Dijk wrote:
> On 7 April 2011 14:11, Duncan Coutts  wrote:
> > I would be happy to work with you and others to develop the report text
> > for such a proposal. I posted my first draft already :-)
> 
> What would be a good way to proceed? Looking at the process I think we
> should create a wiki page and a ticket for this proposal. If necessary
> I'll volunteer to be the proposal owner.

Ok, I can give you permissions on the wiki. What is your username on the
haskell-prime wiki?

Duncan


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


Re: Proposal: Define UTF-8 to be the encoding of Haskell source files

2011-04-07 Thread Duncan Coutts
On Thu, 2011-04-07 at 09:07 +0200, Roel van Dijk wrote:
> On 6 April 2011 15:13, Duncan Coutts  wrote:
> > So since the goal is interoperability of source files then perhaps we
> > should also have a section somewhere with interoperability guidelines
> > for implementations that do store Haskell programs as OS files.
> 
> I think a set of interoperability guidelines is a great idea. It seems
> these guidelines are already followed by GHC, Cabal, Hackage, Jhc and
> possibly others.
> 
> Shall we consider this the proposal instead of just the encoding part?

I would be happy to work with you and others to develop the report text
for such a proposal. I posted my first draft already :-)

Duncan


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


Re: Proposal: Define UTF-8 to be the encoding of Haskell source files

2011-04-06 Thread Duncan Coutts
On Wed, 2011-04-06 at 16:09 +0100, Ben Millwood wrote:
> On Wed, Apr 6, 2011 at 2:13 PM, Duncan Coutts
>  wrote:
> >
> > Interoperability Guidelines
> > 
> >
> > [...]
> >
> > To find a source file corresponding to a module name used in an import
> > declaration, the following mapping from module name to OS file name is
> > used. The '.' character is mapped to the OS's directory separator
> > string while all other characters map to themselves. The ".hs" or
> > ".lhs" extension is added. Where both ".hs" and ".lhs" files exist for
> > the same module, the ".lhs" one should be used. The OS's standard
> > convention for representing Unicode file names should be used.
> >
> 
> This standard isn't quite universal. For example, jhc will look for
> Data.Foo in Data/Foo.hs but also Data.Foo.hs [1]. We could take this
> as an opportunity to discuss that practice, or we could try to make
> the changes to the report orthogonal to that issue.

Indeed. But it's true to say that if you do support the common
convention then you get portability. This does not preclude JHC from
supporting something extra, but sources that take advantage of JHC's
extension are not portable to implementations that just use the common
convention.

> In some sense I think it's cute that the Report doesn't specify
> anything about how Haskell modules are stored or represented, but I
> don't think that freedom is actually used, so I'm happy to see it go.
> I'd think, though, that in that case there would be more to discuss
> than just the encoding, so if we could separate out the issues here, I
> think that would be useful.

It's not going. I hope I was clear in the example text that the
interoperability guidelines were not forcing implementations to use
files etc, just that if they do, if they uses these conventions then
sources will be portable between implementations.

It doesn't stop an implementation using URLs, sticking multiple modules
in a file or keeping modules in a database.

Duncan


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


Re: Proposal: Define UTF-8 to be the encoding of Haskell source files

2011-04-06 Thread Duncan Coutts
On 4 April 2011 23:48, Roel van Dijk  wrote:
> * Proposal
>
> The Haskell 2010 language specification states that: "Haskell uses the
> Unicode character set" [2]. It does not state what encoding should be
> used. This means, strictly speaking, it is not possible to reliably
> exchange Haskell source files on the byte level.
>
> I propose to make UTF-8 the only allowed encoding for Haskell source
> files. Implementations must discard an initial Byte Order Mark (BOM)
> if present [3].

> * Next step
>
> Discussion! There was already some discussion on the haskell-cafe
> mailing list [7].

This is a simple and obviously sensible proposal. I'm certainly in favour.

I think the only area where there might be some issue to discuss is
the language of the report. As far as I can see, the report does not
require that modules exist as files, does not require the ".hs"
extension and does not give the "standard" mapping from module name to
file name.

So since the goal is interoperability of source files then perhaps we
should also have a section somewhere with interoperability guidelines
for implementations that do store Haskell programs as OS files. The
section would describe the one module per file convention, the .hs
extension (this is already obliquely mentioned in the section on
literate Haskell syntax) and the mapping of module names to file names
in common OS file systems. Then this UTF8 stipulation could go there
(and it would be clear that it applies only to conventional
implementations that store Haskell programs as files).

e.g.

Interoperability Guidelines


This Report does not specify how Haskell programs are represented or
stored. There is however a conventional representation using OS files.
Implementations that conform to these guidelines will benefit from the
portability of Haskell program representations.

Haskell modules are stored as files, one module per file. These
Haskell source files are given the file extension ".hs" for usual
Haskell files and ".lhs" for literate Haskell files (see section
10.4).

Source files must be encoded as UTF-8 \cite{utf8}. Implementations
must discard an initial Byte Order Mark (BOM) if present.

To find a source file corresponding to a module name used in an import
declaration, the following mapping from module name to OS file name is
used. The '.' character is mapped to the OS's directory separator
string while all other characters map to themselves. The ".hs" or
".lhs" extension is added. Where both ".hs" and ".lhs" files exist for
the same module, the ".lhs" one should be used. The OS's standard
convention for representing Unicode file names should be used.

For example, on a UNIX based OS, the module A.B would map to the file
name "A/B.hs" for a normal Haskell file or to "A/B.lhs" for a literate
Haskell file. Note that because it is rare for a Main module to be
imported, there is no restriction on the name of the file containing
the Main module. It is conventional, but not strictly necessary, that
the Main module use the ".hs" or ".lhs" extension.


Duncan

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


Re: Haskell 2010 libraries

2010-05-04 Thread Duncan Coutts
On Fri, 2010-04-30 at 10:42 +0100, Simon Marlow wrote:
> Hi Folks,
> 
> I'm editing the Haskell 2010 report right now, and trying to decide what 
> to do about the libraries.  During the Haskell 2010 process the 
> committee agreed that the libraries in the report should be updated, 
> using the current hierarchical names, adding new functionality from the 
> current base package, and dropping some of the H'98 library modules that 
> now have better alternatives.
> 
> In Haskell 2010 we're also adding the FFI modules.  The FFI addendum 
> used non-hierarchical names (CForeign, MarshalAlloc etc.) but these are 
> usually known by their hierarchical names nowadays: e.g. Foreign.C, 
> Foreign.Marshal.Alloc.  It would seem strange to add the 
> non-hierarchical names to the Haskell language report.
> 
> So this is all fine from the point of view of the Haskell report - I can 
> certainly update the report to use the hierarchical module names, but 
> that presents us with one or two problems in the implementation.
> 
> However, what happens when someone wants to write some code that uses
> Haskell 2010 libraries, but also uses something else from base, say 
> Control.Concurrent?  The modules from haskell2010 overlap with those 
> from base, so all the imports of Haskell 2010 modules will be ambiguous.

>   The Prelude is a bit of a thorny issue too: currently it is in base, 
> but we would have to move it to haskell2010.

This problem with the Prelude also already exists. It is currently not
possible to write a H98-only program that depends only on the haskell98
package and not on the base package, because the Prelude is exported
from base and not from haskell98.

> Bear in mind these goals: we want to
> 
>a. support writing code that is Haskell 2010 only: it only uses
>   Haskell 2010 language features and modules.
> 
>b. not break existing code as far as possible
> 
>c. whatever we do should extend smoothly when H'2011 makes
>   further changes, and so on.
> 
> Here are some non-options:
> 
>1. Not have a haskell2010 package.  We lose (a) above, and we
>   lose the ability to add or change the API for these modules,
>   in base, since they have to conform to the H'2010 spec.  If
>   H'2011 makes any changes to these modules, we're really stuck.
> 
>2. As described above: you can either use haskell2010, or base,
>   but not both.  It would be painful to use haskell2010 in
>   GHCi, none of the base modules would be available.
> 
> Here are some options:
> 
>3. allow packages to shadow each other, so haskell2010 shadows
>   base.  This is a tantalising possibility, but I don't have
>   any idea what it would look like, e.g. should the client or
>   the package provider specify shadowing?

So one option is simply to have the client specify shadowing by the
order in which packages are listed on the command line / in the .cabal
file (or some other compiler-dependent mechanism).

If people think the order in the .cabal file is not sufficiently
explicit then I'm sure we can concoct some more explicit syntax. We
already need to add some syntax to allow a package to depend on multiple
versions of a single dependency.

The advantage of the client doing it is it's quite general. The downside
is it's quite general: people can do it anywhere and can easily get
incompatible collections of types. For example base:Prelude.Int would
only be the same as haskell2010:Prelude.Int because it is explicitly set
up to be that way. Arbitrary shadowing would not be so co-operative.


The provider doing it seems fairly attractive. Cases of co-operative
overlapping have to be explicitly constructed by the providing packages
anyway (see e.g. base3 and base4).

I'm not quite sure how it would be implemented but from the user's point
of view they just list the package dependencies as usual and get the
sensible overlapping order. Presumably packages not designed to be used
in an overlapping way should still give an error message.

The provider doing it rather than the client should avoid the user
having to think too much or there being too many opportunities to do
foolish and confusing things. Only the sensible combinations should
work.

> Thoughts?  Better ideas?

So I think I quite like option 3. I doesn't sound to me as complicated
or as subtle as Malcolm seems to fear.

If I write:

build-depends: base, haskell2010

then since haskell2010 has been explicitly set up for this overlapping
to be allowed, then we get haskell2010 shadowing base (irrespective of
the order in which the client lists the packages).

Duncan

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


Re: Haskell 2010 libraries

2010-05-04 Thread Duncan Coutts
On Fri, 2010-04-30 at 10:42 +0100, Simon Marlow wrote:

> Here are some options:
> 
>3. allow packages to shadow each other, so haskell2010 shadows
>   base.  This is a tantalising possibility, but I don't have
>   any idea what it would look like, e.g. should the client or
>   the package provider specify shadowing?

Note that we already have some notion of shadowing. Modules found in
local .hs files shadow modules from packages.

Duncan

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


Re: Unsafe hGetContents

2009-10-20 Thread Duncan Coutts
On Tue, 2009-10-20 at 15:45 +0100, Simon Marlow wrote:

> > I've not yet seen anyone put forward any practical programs that have
> > confusing behaviour but were not written deliberately to be as wacky as
> > possible and avoid all the safety mechanism.
> >
> > The standard use case for hGetContents is reading a read-only file, or
> > stdin where it really does not matter when the read actions occur with
> > respect to other IO actions. You could do it in parallel rather than
> > on-demand and it'd still be ok.
> >
> > There's the beginner mistake where people don't notice that they're not
> > actually demanding anything before closing the file, that's nothing new
> > of course.
> 
> If the parallel runtime reads files eagerly, that might hide a resource 
> problem that would occur when the program is run on a sequential system, 
> for example.

That's true, but we have the same problem without doing any IO. There
are many ways of generating large amounts of data.

Duncan

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


Re: Unsafe hGetContents

2009-10-20 Thread Duncan Coutts
On Tue, 2009-10-20 at 13:58 +0100, Simon Marlow wrote:

> Duncan has found a definition of hGetContents that explains why it has 
> surprising behaviour, and that's very nice because it lets us write the 
> compilers that we want to write, and we get to tell the users to stop 
> moaning because the strange behaviour they're experiencing is allowed 
> according to the spec.  :-)

:-)

> Of course, the problem is that users don't want the hGetContents that 
> has non-deterministic semantics, they want a deterministic one.  And for 
> that, they want to fix the evaluation order (or something).  The obvious 
> drawback with fixing the evaluation order is that it ties the hands of 
> the compiler developers, and makes a fundamental change to the language 
> definition.

I've not yet seen anyone put forward any practical programs that have
confusing behaviour but were not written deliberately to be as wacky as
possible and avoid all the safety mechanism.

The standard use case for hGetContents is reading a read-only file, or
stdin where it really does not matter when the read actions occur with
respect to other IO actions. You could do it in parallel rather than
on-demand and it'd still be ok.

There's the beginner mistake where people don't notice that they're not
actually demanding anything before closing the file, that's nothing new
of course.

Duncan

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


Re: Unsafe hGetContents

2009-10-11 Thread Duncan Coutts
On Sat, 2009-10-10 at 10:59 -0700, Iavor Diatchki wrote:
> Hello,
> 
> well, I think that the fact that we seem to have a program context
> that can distinguish "f1" from "f2" is worth discussing because I
> would have thought that in a pure language they are interchangable.

Crucially they are contexts in an IO program.

> The question is, does the context in Oleg's example really distinguish
> between "f1" and "f2"?  You seem to be saying that this is not the
> case:  in both cases you end up with the same non-deterministic
> program that reads two numbers from the standard input and subtracts
> them but you can't assume anything about the order in which the
> numbers are extracted from the input---it is merely an artifact of the
> GHC implementation that with "f1" the subtraction always happens the
> one way, and with "f2" it happens the other way.

Right.

> I can (sort of) buy this argument, after all, it is quite similar to
> what happens with asynchronous exceptions (f1 (error "1") (error "2")
> vs f2 (error "1") (error "2")).  Still, the whole thing does not
> "smell right":  there is some impurity going on here,

No, there's no impurity.

> and trying to offload the problem onto the IO monad only makes
> reasoning about IO computations even harder (and it is petty hard to
> start with).

Sure, reasoning about non-deterministic IO programs is tricky. But then
nobody here is advocating writing non-deterministic IO programs. Lazy IO
is sensible and useful when the non-determinism doesn't make any
difference to the results.

Lets look at a simplified case, instead of general IO and the whole OS
API at our disposal, lets look at the case of a single thread of control
and mutable variables, specifically the ST monad.

We can construct a semantics for this based on a sequence of read /
write events for the mutable variables. The ST monad bind gives
guarantees about the ordering of the events. So the ST programs are
deterministic.

do x <- readSTRef v
   writeSTRef v (x+1)
   writeSTRef v (x+2)

The semantics of this ST program is the trace

read(v,x)
write(v,x+1)
write(v,x+2)

We could introduce non-determinism to this system by allowing read /
write events to be arbitrarily interleaved with other subsequent events:

do x <- readSTRef v
   unsafeInterleaveST $ writeSTRef v (x+1)
   writeSTRef v (x+2)

now we can have two traces:

read(v,x)
write(v,x+1)
write(v,x+2)

or

read(v,x)
write(v,x+2)
write(v,x+1)

The semantics is the set of traces, in this case just the two.

Of course with this modified ST system we cannot allow a pure runST
because we've got non-deterministic ST programs (or we could make it
pure by returning the full set of traces). But it'd be ok for IO.

Now working with and reasoning about these non-deterministic ST programs
is tricky. Depending on the implementation choice for the interleaving
we'll get different results and under some implementation choices we'll
be able to influence the result by coding pure bits of the program
differently. None of this changes the semantics since the semantics just
says any possible interleaving is OK.

Another interesting thing to note is that we can limit the interleaving
somewhat by forcing deferred events to come before other subsequent
events:

do writeSTRef v 1
   x <- unsafeInterleaveST $ readSTRef v
   writeSTRef v 2
   evaluate x
   writeSTRef v 3

So in the traces for this program, x can have the value 1 or 2 but not 3
because of the partial order on events that we impose using evaluate.

We can also do something like Oleg's example (simplified to only a
single getChar rather than reading the whole input stream)

do
  let fileContent = "hello"
  seekPoint <- newSTRef 0
  let getChar = do
s <- readIORef seekPoint
writeIORef seekPoint (s+1)
return (fileContent !! s)

  s1 <- unsafeInterleaveST getChar
  s2 <- unsafeInterleaveST getChar
  
  --evaluate (f1 s1 s2)
  evaluate (f2 s1 s2)

Under some implementations of the interleaving we can expect to get
different event interleavings for the f1 program vs the f2 program. So
we apparently have a pure function influencing the event ordering. Of
course the semantics says we have both event orderings anyway.

It is also possible to write ST programs that produce the same result
irrespective of the event interleaving. These programs might actually be
useful. For example:

do writeSTRef v 1
   x <- unsafeInterleaveST $ readSTRef v
   ...
   -- no more writes to v

So here we allow the read from v do be performed any time. We still have
loads of different possible traces, but the value of x is the same in
each, because the v variable is never written to again.

In IO with the full OS API and other programs running concurrently it is
harder to reason about. But we can see similar possibilities for
non-deterministic primitives where we can still get a deterministic
result. One of those is if we read from a mutable variable (a file) and
can be sure that there are no other writes to 

Re: Unsafe hGetContents

2009-10-10 Thread Duncan Coutts
On Sat, 2009-10-10 at 02:51 -0700, o...@okmij.org wrote:

> > The reason it's hard is that to demonstrate a difference you have to get
> > the lazy I/O to commute with some other I/O, and GHC will never do that.
> 
> The keyword here is GHC. I may well believe that GHC is able to divine
> programmer's true intent and so it always does the right thing. But
> writing in the language standard ``do what the version x.y.z of GHC
> does'' does not seem very appropriate, or helpful to other
> implementors.

With access to unsafeInterleaveIO it's fairly straightforward to show
that it is non-deterministic. These programs that bypass the safety
mechanisms on hGetContents just get us back to having access to the
non-deterministic semantics of unsafeInterleaveIO.

> > Haskell's IO library is carefully designed to not run into this
> > problem on its own.  It's normally not possible to get two Handles
> > with the same FD...

> Is this behavior is specified somewhere, or is this just an artifact
> of a particular GHC implementation?

It is in the Haskell 98 report, in the design of the IO library. It does
not not mention FDs of course. The IO/Handle functions it provides give
no (portable) way to obtain two read handles on the same OS file
descriptor. The hGetContents behaviour of semi-closing is to stop you
from getting two lazy lists of the same read Handle.

There's nothing semantically wrong with you bypassing those restrictions
(eg openFile "/dev/fd/0") it just means you end up with a
non-deterministic IO program, which is something we typically try to
avoid.

I am a bit perplexed by this whole discussion. It seems to come down to
saying that unsafeInterleaveIO is non-deterministic and that things
implemented on top are also non-deterministic. The standard IO library
puts up some barriers to restrict the non-determinism, but if you walk
around the barrier then you can still find it. It's not clear to me what
is supposed to be surprising or alarming here.

Duncan

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


Re: Unsafe hGetContents

2009-10-06 Thread Duncan Coutts
On Tue, 2009-10-06 at 15:18 +0200, Nicolas Pouillard wrote:

> > The reason it's hard is that to demonstrate a difference you have to get 
> > the lazy I/O to commute with some other I/O, and GHC will never do that. 
> >   If you find a way to do it, then we'll probably consider it a bug in GHC.
> > 
> > You can get lazy I/O to commute with other lazy I/O, and perhaps with 
> > some cunning arrangement of pipes (or something) that might be a way to 
> > solve the puzzle.  Good luck!
> 
> Oleg's example is quite close, don't you think?
> 
> URL: http://www.haskell.org/pipermail/haskell/2009-March/021064.html


I didn't think that showed very much. He showed two different runs of
two different IO programs where he got different results after having
bypassed the safety switch on hGetContents.

It shows that lazy IO is non-deterministic, but then we knew that. It
didn't show anything was impure.

As a software engineering thing, it's recommended to use lazy IO in the
cases where the non-determinism has a low impact, ie where the order of
the actions with respect to other actions doesn't really matter. When it
does matter then your programs will probably be more comprehensible if
you do the actions more explicitly.

For example we have the shoot-yourself-in-the-foot restriction that you
can only use hGetContents on a handle a single time (this is the safety
mechanism that Oleg turned off) and after that you cannot write to the
same handle. That's not because it'd be semantically unsound if those
restrictions were not there, but it would let you write some jolly
confusing non-deterministic programs.

Duncan

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


Re: Strongly Specify Alignment for FFI Allocation

2009-09-28 Thread Duncan Coutts
On Sat, 2009-09-26 at 04:20 +0100, Brandon S. Allbery KF8NH wrote:
> On Sep 25, 2009, at 07:54 , Duncan Coutts wrote:
> > pessimistic. We could do better on machines that are tolerant of
> > misaligned memory accesses such as x86. We'd need to use cpp to switch
> 
> 
> Hm.  I thought x86 could be tolerant (depending on a cpu configuration  
> bit) but the result was so slow that it wasn't worth it?

It's slow and you would not want to do it much, however I think it's
still comparable in speed to doing a series of byte reads/writes and
using bit twiddling to convert to/from the larger word type. It's
probably also faster to do an unaliged operation sometimes than to do an
alignment test each time and call a special unaliged version.

Duncan

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


Re: Strongly Specify Alignment for FFI Allocation

2009-09-25 Thread Duncan Coutts
On Thu, 2009-09-24 at 23:13 +0100, Don Stewart wrote:

> > It would be beneficial if this wording was applied to all allocation
> > routines - such as mallocForeignPtrBytes, mallocForeignPtrArray, etc.
> > For the curious, this proposal was born from the real-world issue of
> > pulling Word32's from a ByteString in an efficient but portable manner
> > (binary is portable but inefficient, a straight forward
> > unsafePerformIO/peek is efficient but need alignment).
> 
> As a side issue, the get/put primitives on Data.Binary should be
> efficient (though they're about twice as fast when specialized to a
> strict bytestring... stay tuned for a package in this area).

They are efficient within the constraint of doing byte reads and
reconstructing a multi-byte word using bit twiddling.

eg:

getWord16be :: Get Word16
getWord16be = do
s <- readN 2 id
return $! (fromIntegral (s `B.index` 0) `shiftl_w16` 8) .|.
  (fromIntegral (s `B.index` 1))

Where as reading an aligned word directly is rather faster. The problem
is that the binary API cannot guarantee alignment so we have to be
pessimistic. We could do better on machines that are tolerant of
misaligned memory accesses such as x86. We'd need to use cpp to switch
between two implementations depending on if the arch supports misaligned
memory access and if it's big or little endian.

#ifdef ARCH_ALLOWS_MISALIGNED_MEMORY_ACCESS

#ifdef ARCH_LITTLE_ENDIAN
getWord32le = getWord32host
#else
getWord32le = ...
#endif

etc

Note also that currently the host order binary ops are not documented as
requiring alignment, but they do. They will fail eg on sparc or ppc for
misaligned access.

Duncan

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


Re: [Haskell'-private] StricterLabelledFieldSyntax

2009-08-10 Thread Duncan Coutts
On Sun, 2009-07-26 at 02:34 +0100, Ian Lynagh wrote:
> Hi all,
> 
> I've made a ticket and proposal page for making the labelled field
> syntax stricter, e.g. making this illegal:
> 
> data A = A {x :: Int}
> 
> y :: Maybe A
> y = Just A {x = 5}
> 
> and requiring this instead:
> 
> data A = A {x :: Int}
> 
> y :: Maybe A
> y = Just (A {x = 5})

I think I don't like it. It makes the "labelled function argument" trick
much less nice syntactically.

... <- createProcess proc { cwd = Just "blah" }

This is especially so if the labelled function argument is not the final
parameter since then one cannot use $, you'd have to put the whole thing
in ()'s.

The labelled argument technique is one I think we should be making
greater use of (eg look at the proliferation of openFile variants) so I
don't think we should be changing the syntax to make it harder / uglier.

Duncan

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


Re: Haskell 2010: libraries

2009-07-14 Thread Duncan Coutts
On Tue, 2009-07-14 at 00:20 +0100, Ian Lynagh wrote:
> On Mon, Jul 13, 2009 at 09:56:50PM +0100, Duncan Coutts wrote:
> > 
> > I'd advocate 4. That is, drop the ones that are obviously superseded.
> > Keep the commonly used and uncontroversial (mostly pure) modules and
> > rename them to use the new hierarchical module names.
> > 
> > Specifically, I suggest:
> > 
> >  1. Ratio   keep as Data.Ratio
> >  2. Complex keep as Data.Complex
> >  3. Numeric keep as Numeric (?)
> >  4. Ix  keep as Data.Ix
> >  5. Array   keep as Data.Array
> >  6. Listkeep as Data.List
> >  7. Maybe   keep as Data.Maybe
> >  8. Charkeep as Data.Char
> >  9. Monad   keep as Control.Monad
> > 10. IO  keep as System.IO
> > 11. Directory   drop
> > 12. System  drop (superseded by System.Process)
> > 13. Timedrop
> > 14. Locale  drop
> > 15. CPUTime drop
> > 16. Random  drop
> 
> We've been fortunate recently that, because the hierarchical modules
> haven't been in the standard, we've been able to extend and improve them
> without breaking compatibility with the language definition. In some
> cases, such as the changes to how exceptions work, we haven't had this
> freedom as the relevant functions are exposed by the Prelude, and that
> has been causing us grief for years.
> 
> To take one example, since List was immortalised in the H98 report with
> 104 exports, Data.List has gained an additional 7 exports:
> foldl'
> foldl1'
> intercalate
> isInfixOf
> permutations
> stripPrefix
> subsequences
> The last change (making the behaviour of the generic* functions
> consistent with their non-generic counterparts) was less than a year
> ago, and the last additions were less than 2.

Though also note that we have not changed any of the existing ones. Is
there a problem with specifying in the libraries section of the report
that the exports are a minimum and not a maximum?

> But to me, the most compelling argument for dropping them from the
> report is that I can see no benefit to standardising them as part of the
> language, rather than in a separate "base libraries" standard.

Some functions, especially the pure ones are really part of the
character of the language (and some are specified as part of the
syntax). We have not had major problems with the pure parts of the
standard libraries, our problems have almost all been with the system
facing parts (handles, files, programs, exceptions).

I don't see any particular problem with having some essential (in the
sense of being part of the essence of the language) libraries in the
main report and some separate libraries report in a year or two's time
standardising some of the trickier aspects of libraries for portable
programs to interact with the OS (addressing Malcolm's point about the
need for this so as to be able to write portable programs).

Duncan

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


Re: Haskell 2010: libraries

2009-07-13 Thread Duncan Coutts
On Mon, 2009-07-13 at 21:57 +0100, Duncan Coutts wrote:
> On Wed, 2009-07-08 at 15:09 +0100, Simon Marlow wrote:
> 
> > I'm mainly concerned with projecting a consistent picture in the Report, 
> > so as not to mislead or confuse people.  Here are the options I can see:
> 
> >   2. Just drop the obvious candidates (Time, Random, CPUTime,
> >  Locale, Complex?), leaving the others.
> > 
> >   3. Update the libraries to match what we have at the moment.
> >  e.g. rename List to Data.List, and add the handful of
> >  functions that have since been added to Data.List.  One
> >  problem with this is that these modules are then tied to
> >  the language definition, and can't be changed through
> >  the usual library proposal process.  Also it would seem
> >  slightly strange to have a seemingly random set
> >  of library modules in the report.

Another thing we can do here is specify that the contents of these
modules is a minimum and not a maximum, allowing additions through the
usual library proposal process.

> >   4. Combine 2 and 3: drop some, rename the rest.
> 
> I'd advocate 4. That is, drop the ones that are obviously superseded.
> Keep the commonly used and uncontroversial (mostly pure) modules and
> rename them to use the new hierarchical module names.

Oh and additionally include the FFI modules under their new names.

Duncan

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


Re: Haskell 2010: libraries

2009-07-13 Thread Duncan Coutts
On Wed, 2009-07-08 at 15:09 +0100, Simon Marlow wrote:

> I'm mainly concerned with projecting a consistent picture in the Report, 
> so as not to mislead or confuse people.  Here are the options I can see:

>   2. Just drop the obvious candidates (Time, Random, CPUTime,
>  Locale, Complex?), leaving the others.
> 
>   3. Update the libraries to match what we have at the moment.
>  e.g. rename List to Data.List, and add the handful of
>  functions that have since been added to Data.List.  One
>  problem with this is that these modules are then tied to
>  the language definition, and can't be changed through
>  the usual library proposal process.  Also it would seem
>  slightly strange to have a seemingly random set
>  of library modules in the report.
> 
>   4. Combine 2 and 3: drop some, rename the rest.

I'd advocate 4. That is, drop the ones that are obviously superseded.
Keep the commonly used and uncontroversial (mostly pure) modules and
rename them to use the new hierarchical module names.

Specifically, I suggest:

 1. Ratio   keep as Data.Ratio
 2. Complex keep as Data.Complex
 3. Numeric keep as Numeric (?)
 4. Ix  keep as Data.Ix
 5. Array   keep as Data.Array
 6. Listkeep as Data.List
 7. Maybe   keep as Data.Maybe
 8. Charkeep as Data.Char
 9. Monad   keep as Control.Monad
10. IO  keep as System.IO
11. Directory   drop
12. System  drop (superseded by System.Process)
13. Timedrop
14. Locale  drop
15. CPUTime drop
16. Random  drop

The slightly odd thing here is keeping System.IO but dropping the other
IO libs Directory and System. We obviously have to drop System, because
it's more or less a deprecated API and it's superseded by System.Process
(which we almost certainly do not want to standardise at this stage).

It'd be nice to have a clear dividing line of keeping the pure stuff and
dropping the bits for interacting with the system however we have to
keep System.IO since bits of it are re-exported through the Prelude
(unless we also trim the Prelude). The bits for interacting with the
system are of course exactly the bits that are most prone to change and
are most in need of improvement.

Another quirk is that we never changed the name of the Numeric module.

Duncan

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


Re: what about moving the record system to an addendum?

2009-07-07 Thread Duncan Coutts
On Mon, 2009-07-06 at 18:28 -0700, John Meacham wrote:
> Well, without a replacement, it seems odd to remove it. Also, Haskell
> currently doesn't _have_ a record syntax (I think it was always a
> misnomer to call it that) it has 'labeled fields'. None of the proposed
> record syntaxes fit the same niche as labeled fields so I don't see them
> going away even if a record syntax is added to haskell in the future.

The people proposing this can correct me if I'm wrong but my
understanding of their motivation is not to remove record syntax or
immediately to replace it, but to make it easier to experiment with
replacements by making the existing labelled fields syntax a modular
part of the language that can be turned on or off (like the FFI).

I'm not sure that I agree that it's the best approach but it is one idea
to try and break the current impasse. It seems currently we cannot
experiment with new record systems because they inevitably clash with
the current labelled fields and thus nothing changes.

Duncan

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


Re: what about moving the record system to an addendum?

2009-07-06 Thread Duncan Coutts
On Mon, 2009-07-06 at 17:30 -0400, Samuel Bronson wrote:
> According to ,
> ticket #99 was rejected, but the tickets own page,
> , says
> "probably yes". Which is it?
> 
> I was about to propose this myself, but decided to check the trac just
> in case it had already been proposed, Haskell being so popular with
> smart people and all, and was at first rather disappointed and ready
> to write an angry rant to the list, then rather confused when I
> noticed the ticket's page said almost the exact opposite of the Status
> page.
> 
> In particular, I want records to be considered an extension to
> Haskell', to be implemented only by compilers that care, and even then
> only allowed with a LANGUAGE pragma like this:
> 
>{-# LANGUAGE TraditionalRecordSyntax #-}
> 
> For pre-Haskell' compilers, we would want something like:
> 
>{-# LANGUAGE NoTraditionalRecordSyntax #-}
> 
> which would mean extending the LANGUAGE pragma to support turning
> extensions off by adding/removing a No from the front of it.

The motivation I suppose is so that people can experiment with other
record systems as extensions without having to worry so much about the
syntax clashing with the existing syntax.

It would have to be clear that it may not be possible to use certain
combinations of extensions together. In particular
TraditionalRecordSyntax with some future alternative record extension.

> Hmm, is it really the case that nobody has proposed LANGUAGE pragmas for
> Haskell'? I don't see them listed on the Status page.

This we certainly need to do. It's the primary mechanism by which we
allow flexibility in the language without breaking all existing code (by
letting modules declare which language features they want to turn on or
off).

For one thing the spec currently says that pragmas cannot change the
semantics of the program. That would have to read "apart from the
LANGUAGE pragma".

Duncan

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


Re: A HERE Document syntax

2009-04-24 Thread Duncan Coutts
On Wed, 2009-04-22 at 20:52 -0700, Jason Dusek wrote:
> The conventional HERE document operator -- `<<` -- is not a
>   good fit for Haskell. It's a perfectly legal user-level
>   operator. I'd like to propose the use of backticks for HERE
>   documents.

Just to say that I think this proposal is definitely worth considering.

I've not looked at all the details yet, but we should. See also some
comments on reddit:
http://www.reddit.com/r/haskell/comments/8ereh/a_here_document_syntax/


Duncan

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


Re: Specific denotations for pure types

2009-03-24 Thread Duncan Coutts
On Sat, 2009-03-21 at 11:15 -0700, Conal Elliott wrote:
> I'm suggesting that we have well-defined denotations for the pure
> types in Haskell, and that the various Haskell implementations be
> expected to implement those denotations.
> 
> I'm fine with IO continuing to be the (non-denotational) "sin bin"
> until we find more appealing denotationally-founded replacements.
> 
> I didn't answer your question as stated because I don't know what you
> include in "behaviour" for a functional program.  I have operational
> associations with that word.


You're right of course, once we have one machine-dependent type then all
of them are "infected" even simple things like Bool.

The question is what should we do about it, if anything? A certain
amount of machine dependent behaviour would seem to be useful. Even
machine-dependent Int it's not in the H98 standard, implementations
would want to add it as an efficiency extension and then we're back to
the same place because one machine-dependent type infects all types.

It doesn't even need machine dependent compilers. We've got plenty of
libraries that have different "pure" semantics on different platforms.
For example System.FilePath has a bunch of pure functions for
manipulating file paths. We could construct a similar dodgy :: Bool
example using functions from System.FilePath.

As, Ganesh said, I'm not sure what we can actually do, unless you want
to explain the denotation of everything with an extra (MachineInfo ->)
context.

Duncan

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


Re: Newtype unwrapping in the FFI

2009-02-12 Thread Duncan Coutts
On Thu, 2009-02-12 at 09:22 +, Simon Peyton-Jones wrote:
> [This email concerns an infelicity in the FFI spec. I'm directing it
> primarily to the Haskell Prime mailing list, but ccing the libraries
> list so that people there know about the thread. I suggest that
> replies go to Haskell Prime only.]
> 
> Consider this program (see
> http://hackage.haskell.org/trac/ghc/ticket/3008)
> 
>   module NT( N ) where
>  newtype N = MkN Int
> 
>   module FFI where
>  foreign import "f" :: N -> IO ()
> 
> Is module FFI OK?  It would definitely be OK if N was defined in the
> module FFI: the FFI spec says that the compiler must automatically
> unwrap any newtype arguments.
> http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise3.html#x6-120003.2
> 
> But it's less clear when N is defined in another module *and* its
> representation isn't exported.  The author of NT might believe that
> because N's representation is hidden, she can change it to, say
> data N = MkN Int
> without affecting the rest of the world.  But she can't.  This is a
> nasty failure of abstraction.  It is, I believe the only way in which
> a client of a NT could be affected by N's representation, even though
> that representation is allegedly hidden.  (ToDo: check on generalised
> newtype deriving.) This seems Bad to me.
> 
> Indeed, the cause of the above bug report is that GHC's implementation
> assumes that the representation is fully hidden if the constructor is
> not exported, and does not expose the representation of N even to
> separately-compiled modules (at least when you are not using -O).
> 
> But the point here is not what GHC stumbles on but what is supposed to
> happen.
> 
> Maybe we should fix it.  Proposal:
> 
>   * Clarify the spec to say that a newtype can only be automatically
> unwrapped if the newtype constructor (MkN in this case) is in
> scope

I agree up to here. For user-defined types, not exporting the
constructor should be a guarantee of abstraction.

> It happens that a large set of types from Foreign.C.Types, such as
> CInt and friends, are exported without their constructors, so adopting
> this new rule would require us to change Foreign.C.Types to expose the
> representation of CInt and friends.  (As it happens, nhc requires this
> already, so there's some #ifdeffery there already.)

The thing about CInt though is that it is supposed to be abstract *and*
an FFI type. I want to think of it as a primitive FFI type (though it is
not a "basic" type as defined by the FFI). We don't want to know that on
some system it is Int32 and on others it is Int64. We do not want access
to the constructor here.

Duncan

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


Re: Outlaw tabs

2009-01-24 Thread Duncan Coutts
On Sat, 2009-01-24 at 00:35 +0100, Achim Schneider wrote:
> I guess everyone knows why.

Can I recommend Ian's Good Haskell Style

http://urchin.earth.li/~ian/style/haskell.html

We should have it linked/published more widely. The Vim mode that it
links to is also excellent. We should try and get it ported to the
Haskell emacs mode.

As others have also pointed out adding ghc-options: -fwarn-tabs to a
project .cabal file is a good way to stop them creeping back in.

A lot of projects use -Wall. If there is consensus on the tabs issue
then we could ask for -fwarn-tabs to be included in -Wall. That should
be a good first step. If we cannot achieve consensus within the
community for having -Wall include -fwarn-tabs then we have no hope of
banning them in the language definition.

So lets first test test the waters on that proposal.

Duncan

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


RE: Repair to floating point enumerations?

2008-10-15 Thread Duncan Coutts
On Wed, 2008-10-15 at 11:25 +0100, Mitchell, Neil wrote:
> Hi Malcolm,
> 
> The current behaviour does sound like a bug, and the revised behaviour
> does sound like a fix - and one that has a sensible explanation if
> people trip over it. In general having floating point be a member of
> classes such as Eq has some obvious problems, but I realise is a
> necessity for practical programming. Given that we have Eq Double, then
> Enum Double seems no worse.
> 
> If we don't alter H98 then a valid program under H98 vs H' will give
> different results without any warning - that seems really bad. In
> addition, having two instances around for one typeclass/type pair in a
> big library (base) which are switched with some flag seems like a
> nightmare for compiler writers. So I think a good solution would be to
> fix H98 as a typo, and include it in H'.

I would take the contrary position and say H98 should be left alone and
the change should be proposed for H'.

The argument is that H98 is done and the revised report was published 7
years ago. Changing H98 now just doesn't seem to make much sense.

If we're talking about changing the meaning of 'valid' programs then
doing that at a boundary like H98 -> H' seems much more sensible than
having to explain the difference in H98-pre2008 programs vs
H98-post2008.

People will not expect all programs to be exactly the same between H98
and H' (otherwise there would be little need for a new standard). Yes H'
is mostly compatible extensions but not all of it.

Duncan

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


Re: Mutually-recursive/cyclic module imports

2008-08-17 Thread Duncan Coutts
On Sat, 2008-08-16 at 13:51 -0400, Isaac Dupree wrote:
> Duncan Coutts wrote:
> > [...]
> > 
> > I'm not saying it's a problem with your proposal, I'd just like it to be
> > taken into account. For example do dependency chasers need to grok just
> > import lines and {-# SOURCE -#} pragmas or do they need to calculate
> > fixpoints.
> 
> Good point.  What does the dependency chaser need to figure out?
> - exactly what dependency order files must be compiled 
> (e.g., ghc -c) ?
> - what files (e.g., .hi) are needed to be findable by the 
> e.g. (ghc -c) ?
> - recompilation avoidance?

It needs to work out which files the compiler will read when it compiles
that module.

So currently, I think we just have to read a single .hs file and
discover what modules it imports. We then can map those to .hi
or .hs-boot files in one of various search dirs or packages.

We also need to look at {#- SOURCE #-} import pragmas since that means
we look for a different file to ordinary imports.

Calculating dependency order and recompilation avoidance are things the
dep program has to do itself anyway. The basics is just working out what
things compiling a .hs file depends on. Obviously it's somewhat
dependent on the Haskell implementation.

Duncan

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


Re: Mutually-recursive/cyclic module imports

2008-08-16 Thread Duncan Coutts
On Fri, 2008-08-15 at 09:27 -0400, Isaac Dupree wrote:
> Haskell-98 specifies that module import cycles work 
> automatically with cross-module type inference.

[...]

I'd very much like you to consider in any proposal like this how easy it
is to implement module dependency chasing. If the dependency chaser has
to know too much about Haskell it makes it very difficult for tools like
Cabal or hmake and we could be stuck with only ghc --make or ghc -M. Our
plan with Cabal is to do dependency chasing which would enable
incremental and parallel rebuilds.

I'm not saying it's a problem with your proposal, I'd just like it to be
taken into account. For example do dependency chasers need to grok just
import lines and {-# SOURCE -#} pragmas or do they need to calculate
fixpoints.

Duncan

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


Re: patch applied (haskell-prime-status): add ""Make $ left associative, like application"

2008-04-23 Thread Duncan Coutts

On Tue, 2008-04-22 at 16:21 -0700, Simon Marlow wrote:
> Chris Smith wrote:
> > On Tue, 22 Apr 2008 15:53:39 -0700, Simon Marlow wrote:
> >> Tue Apr 22 15:53:31 PDT 2008  Simon Marlow
> >> <[EMAIL PROTECTED]>
> >>   * add ""Make $ left associative, like application"
> > 
> > Is there a justification for this somewhere?
> 
> I'm hoping someone will supply some.  There seemed to be strong opinion 
> on #haskell that this change should be made, but it might just have been 
> a very vocal minority.

It true that (f $ g $ h $ x) might be nicer written (f . g . h $ x)

but I've always thought the point of $ is for things like

withSomeResource foo $
  withSomeOtherThing bar $
yetAnotherBlockStructured thing $ ...

Does that work?

Or

withSomeResource foo $ \x ->
  withSomeOtherThing bar $ \y ->
yetAnotherBlockStructured thing $ \z ->

Or does that case still work?

There must have been some justification for the original design or was
it just f $ g $ h $ x  ?

Duncan

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


Re: patch applied (haskell-prime-status): add ""Make $ left associative, like application"

2008-04-23 Thread Duncan Coutts

On Tue, 2008-04-22 at 21:02 -0400, Dan Doel wrote:

> 3) Left associative ($) is consistent with left associative ($!). The right 
> associative version of the latter is inconvenient, because it only allows 
> things to be (easily) strictly applied to the last argument of a function.

What about having ! as a left associative strict apply operator?

f !x !y !z

Isn't there already a proposal along these lines? There is certainly a
proposal to stop using ! for array indexing.

Duncan

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


Re: patch applied (haskell-prime-status): add ""Make $ left associative, like application"

2008-04-22 Thread Duncan Coutts

On Tue, 2008-04-22 at 23:13 +, Chris Smith wrote:
> On Tue, 22 Apr 2008 15:53:39 -0700, Simon Marlow wrote:
> > Tue Apr 22 15:53:31 PDT 2008  Simon Marlow
> > <[EMAIL PROTECTED]>
> >   * add ""Make $ left associative, like application"
> 
> Is there a justification for this somewhere?  I know it would break 
> nearly every single piece of Haskell code I've ever written.  As such, 
> I'm biased toward thinking it's an extremely bad idea.

Indeed. I think it would at least be worth testing a bunch of packages
from hackage and seeing how many break and when they do, how nice the
fixes are.

Surely there was a justification to having $ be the opposite
associativity from application and not just a different precedence. Does
anyone know what it was?

Duncan

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


Re: Polymorphic strict fields

2007-05-01 Thread Duncan Coutts
On Tue, 2007-05-01 at 09:50 -0700, Iavor Diatchki wrote:
> Hello,
> 
> On 5/1/07, Duncan Coutts <[EMAIL PROTECTED]> wrote:
> > On Mon, 2007-04-30 at 19:47 -0700, Iavor Diatchki wrote:
> >
> > > All of this leads me to think that perhaps we should not allow
> > > strictness annotations on polymorphic fields.  Would people find this
> > > too restrictive?
> >
> > Yes.
> >
> > Our current implementation of stream fusion relies on this:
> >
> > data Stream a = forall s. Unlifted s =>
> >   Stream !(s -> Step a s)  -- ^ a stepper function
> >  !s-- ^ an initial state
> >
> > We use strictness on polymorphic (class constrained) fields to simulate
> > unlifted types. We pretend that the stream state types are all unlifted
> > and have various strict/unlifted type constructors:
> 
> This declaration uses existential and not universal quantification.
> More concretely, there exists some type that classifies the state of
> the stream but the users of the stream do not know what it is (by the
> way I saw Don talk about this stream stuff and I think that it is
> quite cool!).  A polymorphic field is one where the ``forall`` is
> associated with the field (it comes after the constructor), it allows
> you to store polymorphic values in a datatype.

Ah ok. When you said "strictness annotations on polymorphic fields" I
assumed you meant just ordinary things like:

data A a = A !a

rather than local universal quantification.

Duncan

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


Re: Polymorphic strict fields

2007-05-01 Thread Duncan Coutts
On Mon, 2007-04-30 at 19:47 -0700, Iavor Diatchki wrote:

> All of this leads me to think that perhaps we should not allow
> strictness annotations on polymorphic fields.  Would people find this
> too restrictive?

Yes.

Our current implementation of stream fusion relies on this:

data Stream a = forall s. Unlifted s =>
  Stream !(s -> Step a s)  -- ^ a stepper function
 !s-- ^ an initial state

We use strictness on polymorphic (class constrained) fields to simulate
unlifted types. We pretend that the stream state types are all unlifted
and have various strict/unlifted type constructors:

data (Unlifted a, Unlifted b) => a :!: b = !a :!: !b
instance (Unlifted a, Unlifted b) => Unlifted (a :!: b) where ...


Duncan

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


Re: defaults

2006-11-29 Thread Duncan Coutts
On Thu, 2006-11-30 at 12:21 +1100, Bernie Pope wrote:

> A compromise is to turn defaulting off "by default". This would mean
> that if you want defaulting you have to ask for it. The question then  
> would be:
> does defaulting get exported across module boundaries? I would be  
> inclined to say "no", but there may be compelling arguments for it.

If it's on a per-class basis then it would be reasonable to allow the
default to be exported, no? Then you just have to argue about if the
default Prelude should export defaults for the Num and other standard
classes.

For my GUI OOP inheritance hierarchy use-case I'd certainly want to
export the default. It'd be pretty useless otherwise (I don't mean in
general, just for this use-case).

Duncan

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


Re: defaults

2006-11-27 Thread Duncan Coutts
On Mon, 2006-11-20 at 12:05 +, Malcolm Wallace wrote:
> Prompted by recent discussion on the Hat mailing list about the problems
> of type-defaulting, I have added two new proposals for this issue to the
> Haskell-prime wiki at:
> 
> http://hackage.haskell.org/trac/haskell-prime/wiki/Defaulting
> 
> The main new proposal is a different way of specifying defaults, which
> includes the name of the class being defaulted (thus allowing
> user-defined classes to play this game), but unlike the original
> proposal, permits only one type to be specified per class.  The rules
> are therefore also simpler, whilst still (I believe) capturing the
> useful cases.

BTW, just to add another use case for allowing defaulting on any class:

One way to model OO class hierarchies (eg used in GUI libs like Gtk2Hs)
is by having a data type and a class per-object:

data Widget = ...

class WidgetClass widget where
  toWidget :: widget -> Widget --safe upcast

instance WidgetClass Widget

Then each sub-type is also an instance of the class, eg a button:

data Button = ...
class ButtonClass button where
  toButton :: button -> Button

instance WidgetClass Button
instance ButtonClass Button

etc.

So Widget is the canonical instance of WidgetClass.

Actually having this defaulting would be very useful. Suppose we want to
load a widget from a decryption at runtime (and we do, visual builders
like glade give us this). We'd have a functions like this:

xmlLoad :: WidgetClass widget => FilePath -> IO (String -> widget)

So the action loads up an xml file and gives us back a function which we
can use to lookup named widgets from the file. Of course to make this
type safe we need to do a runtime checked downcast from Widget to the
specific widget type we wish to use. For example:

getWidget <- xmlLoad "Foo.glade"
let button1 :: Button
button1 = getWidget "button1"

It would be nice not to have to annotate that button1 :: Button. However
often it would be necessary to do so because almost all operations on
the Button type are actually generic on the ButtonClass (since there are
some sub-types of Button). So actually we'd only constrain button1 to be
an instance of ButtonClass. So we'd end up with ambiguous overloading -
just like we get with (show . read). However if we could default it to
be actually of type Button then it should all work just fine.

Duncan

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


Re: Small note regarding the mailing list

2006-09-02 Thread Duncan Coutts
On Sat, 2006-09-02 at 12:45 -0700, isaac jones wrote:
> On Tue, 2006-08-29 at 14:04 +0200, Christophe Poucet wrote:
> > Hello,
> > 
> > Just a small request.  Would it be feasible to tag the Haskell-prime
> > list in a similar manner as Haskell-cafe?
> 
> I'd rather not.  If you want to be able to filter, you can use the
> "Sender" field which will always be:
> Sender: [EMAIL PROTECTED]

It's also got all the normal "list-id:" header which is the most
reliable way to identify it (and indeed all other mailing lists I've
ever seen).

Many email progs have special support for filter rules based on the
mailing list headers, eg evolution.

Duncan

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


Re: map and fmap

2006-08-14 Thread Duncan Coutts
On Mon, 2006-08-14 at 20:55 +0100, Jon Fairbairn wrote:
> On 2006-08-14 at 12:00PDT "Iavor Diatchki" wrote:
> > Hello,
> > I never liked the decision to rename 'map' to 'fmap', because it
> > introduces two different names for the same thing (and I find the name
> > `fmap' awkward).
> 
> I strongly concur. There are far too many maps even without
> that, and having two names for the same thing adds to the
> confusion.

If it goes in that direction it'd be nice to consider the issue of
structures which cannot support a polymorphic map. Of course such
specialised containers (eg unboxed arrays or strings) are not functors
but they are still useful containers with a sensible notion of map.

The proposals to allow this involve MPTCs where the element type is a
parameter. That allows instances which are polymorphic in the element
type or instances which constrain it.

Duncan

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


Re: WordPtr,IntPtr,IntMax,WordMax

2006-05-11 Thread Duncan Coutts
On Thu, 2006-05-11 at 14:57 +0100, Simon Marlow wrote:

> On the other hand, keeping intermediate Doubles to 80-bit precision is 
> both (a) non-portable and (b) unpredictable (the programmer doesn't know 
> which intermediates are going to be stored in 80 bits, and turning on 
> optimisation will probably make a difference).
> 
> I suppose you might argue that "extra precision is always good".  But I 
> like it when Haskell programs give the same results, regardless of the 
> platform, compilation strategy, and level of optimisation.
> 
> > (And while I'm on the subject, Haskell should have a LongDouble type.)
> 
> LongDouble would be fine, but storing intermediate Doubles in 80 bits is 
> bad.

I agree.

Note that if we did provide LongDouble that we would get the same
problems because the IEEE long double types are not precisely specified.
They specify minimum precision levels rather that fully specifying the
bit layout as in the IEEE 32 & 64 bit formats. Apparently both the x87
80-bit format and various implementations of 128bit formats conform to
the IEEE long double spec.

Duncan

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


RE: FFI proposal: allow some control over the scope of C headerfiles

2006-04-25 Thread Duncan Coutts
On Tue, 2006-04-25 at 10:16 +0100, Simon Marlow wrote:
> On 25 April 2006 09:51, John Meacham wrote:
> 
> > On Tue, Apr 25, 2006 at 09:40:58AM +0100, Simon Marlow wrote:
> >> Admittedly I haven't tried this route (not including *any* external
> >> headers at all when compiling .hc files).  It might be possible, but
> >> you lose the safety net of compiler-checked calls.
> > 
> > yeah, perhaps a hybrid approach of some sort, when building the
> > package, use the system headers, but then include generated
> > prototypes inside the package-file and don't propagate #includes once
> > the package is built. 
> > 
> > or just an intitial conformance check against the system headers
> > somehow (?), but then only use your own generated ones when actually
> > compiling haskell code. It would be nice to never need to include
> > external headers in .hc files.
> 
> Hmm, the more I think about it, the more I like this idea.  It means we
> could essentially forget about the public/private header file stuff, we
> don't need the extra pragmas, and there would be no restrictions on
> inlining of foreign calls.

That would be nice. If the module that imports the C functions were
compiled via-C with the headers (or some other check like c2hs does)
then we'd get the safety check. Then other client modules could be
compiled without a prototype at all (or one generated by the Haskell
compiler).

As you say, it is a bit of a pain that users of Haskell bindings libs
need to install the development versions of C libraries. For example
Gtk2Hs users on windows need the full dev version of Gtk+ which is
considerably larger than the runtime version.

One downside would be that we would only be able to call C functions
which conform to the standard platform ABI. As it is at the moment
(perhaps somewhat by accident) we can call C functions that have
non-standard ABI annotations in their prototype, eg:

int foo (int) __attribute__((regparam(3)))

ok that's a silly example, bu there are more sensible examples of ABI
weirdness - especially on arches like mips which seem to support half a
dozen different ABIs. Perhaps we don't care, I'm not sure I do.

Duncan

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


RE: FFI proposal: allow some control over the scope of C header files

2006-04-24 Thread Duncan Coutts
On Mon, 2006-04-24 at 14:44 +0100, Simon Marlow wrote:
> How about just adding a couple of new pragmas:
> 
>  {-# INCLUDE_PRIVATE "foo/bar.h" #-}
>  {-# INCLUDE_PACKAGE "foo/bar.h" #-}

Sounds reasonable. This is much like my original random syntax but as a
pragma.

> both pragmas apply to all the foreign imports in the current module,
> just like the existing INCLUDE pragma.  Additionally, INCLUDE_PRIVATE
> prevents any foreign import from being inlined outside the current
> module, and INCLUDE_PACKAGE does the same but for the package (this
> requires a little more support from GHC).

So the existing INCLUDE pagama is really INCLUDE_GLOBAL.

> We can then describe more accurately what is means to give an include
> file on a particular foreign import: it means the same as
> INCLUDE_PRIVATE, but for this foreign import only.

Yes. That's what GHC currently does and the FFI spec leaves it
unspecified.

> The problem you mentioned, namely that people use a private header file
> but don't export it with the package, only happens when they explicitly
> use {-# INCLUDE #-} or -#include flags, right?

Yes I think so. This normally happens because users specify the header
in the .cabal file and Cabal uses -#include.

> In that case, we can have Cabal check that all {-# INCLUDE #-} files
> are properly exported with the package, and discourage the use of
> explicit -#include options. Is that enough?

Yes, I think that would be a great improvement and would catch most of
the bugs.

I was hoping we could go one step further and have ghc check that all
the headers needed to compile a module are present (usually as a result
of importing a module that uses INCLUDE_GLOBAL). I think it'd just be
one extra bit of info for each .hi file.

So yes, I'd be satisfied with a GHC-only solution but I brought it up
here just in case anyone else thinks that this issue of header scope
might be worth specifying more clearly in the Haskell' FFI. Specifically
if it'd make sense to standardise GHC & JHC's INCLUDE_* pragma(s) into
proper FFI syntax (especially since most people seem to use that rather
than the official syntax).

Duncan

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


Re: FFI proposal: allow some control over the scope of C header files

2006-04-23 Thread Duncan Coutts
On Sun, 2006-04-23 at 17:26 -0400, Manuel M T Chakravarty wrote:
> Duncan Coutts:
> > On Fri, 2006-04-21 at 09:32 -0400, Manuel M T Chakravarty wrote:
> > 
> > > > I think we'd want to be able to specify that a C header file not
> > > > "escape" a module boundary and probably we'd also want to be able to ask
> > > > that it not escape a package boundary (though this may be beyond the H'
> > > > spec since Haskell does not talk about packages).
> > > 
> > > The H98 standard already specifies a NOINLINE pragma for any function:
> > > 
> > >   http://haskell.org/onlinereport/pragmas.html
> > > 
> > > The simplest solution is to ensure that all Haskell compilers implement
> > > this pragma properly for foreign imported functions.  If you want finer
> > > control over where inlining takes place, then maybe the pragma should be
> > > extended to provide that finer control.
> > 
> > I don't think we need to generalise the problem to all function
> > inlinings. There are specific practical problems caused by inlining
> > foreign calls that are not a problem for ordinary Haskell functions.
> 
> Inlining of foreign functions causes extra problems, but generally
> inlining is a concern; so, if we can use the same mechanisms, we get a
> simpler language.

True, though with a special case mechanism we can make automatic checks
possible/easier.

> > > Besides, the standard so far doesn't cover command line options at all.
> > > So, there is the more general question of whether it should.
> > 
> > I don't think we need to specify the command line interface. The
> > required headers can be put in the module.
> 
> That's ok with me.  I was just pointing out that many of the problems
> and/or lack of understanding of users that we are seeing has to do with
> the use of command line options.  We simply cannot address this unless
> the standard covers command line options.

Under my hypothetical scheme the ghc command line method would be
equivalent to putting it in the module and could be checked the same
way.

> > What I really want is for the issue of header scope to be something that
> > can be checked by the compiler. As a distro packager I see far too many
> > people getting it wrong because they don't understand the issue. If we
> > could declare the intended scope of the header files then 1. people
> > would think about and 2. if they got it wrong it'd be checkable because
> > the compiler would complain.
> 
> Whether or not the compiler can check for wrong use, seems to me
> independent of whether we use inline pragmas or any other syntax.  GHC
> could very well check some of these things today.  It just doesn't.  Do
> you propose to make such checks mandatory in the standard?

That'd be nice, though I can see that it is more work.

> We are having two issues here:
> 
> (1) Specification of which functions need what headers and whether 
> these functions can be inlined.
> (2) Let the compiler spot wrong uses of header files.
> 
> These two issues are largely independent.

Yes, ok.

>   Re (1), I dislike new syntax
> (or generally any additions to the language) and prefer using existing
> mechanisms as far as possible.  The reason is simply that Haskell is
> already very complicated.  Haskell' will be even more complicated.
> Hence, we must avoid any unnecessary additions.

Sure.

> Re (2), I am happy to discuss what kind of checks are possible, but I am
> worried that it'll be hard to check for everything without assistance
> from cabal, which I don't think will be part of Haskell'.

I think it can be checked without cabal. Outline: suppose we use a
module level granularity (I know jhc proposes to use a finer
granularity) so we track which C header files are needed to compile
which modules.

A FFI decl specifying a header file makes that module need that header.
Then transitively each module that imports that module needs that header
too. We can only stop the header leaking out of the module/package by
specifying NOINLINE on the imported function (or using some additional
syntax s I originally suggested).

So now it's easy to check what headers are needed to to compile any
module. Then we probably need to rely on an external mechanism (eg cabal
or the user) to make sure that all these headers are available - but at
least we can check that the user has done it right.

So it's at this point that issue (1) & (2) become related. If we say
that a header file transitively infects every client module then it
effectively bans private header files and so we need some mechanism to
limit the scope of 

Re: FFI proposal: allow some control over the scope of C header files

2006-04-21 Thread Duncan Coutts
On Fri, 2006-04-21 at 09:32 -0400, Manuel M T Chakravarty wrote:

> > I think we'd want to be able to specify that a C header file not
> > "escape" a module boundary and probably we'd also want to be able to ask
> > that it not escape a package boundary (though this may be beyond the H'
> > spec since Haskell does not talk about packages).
> 
> The H98 standard already specifies a NOINLINE pragma for any function:
> 
>   http://haskell.org/onlinereport/pragmas.html
> 
> The simplest solution is to ensure that all Haskell compilers implement
> this pragma properly for foreign imported functions.  If you want finer
> control over where inlining takes place, then maybe the pragma should be
> extended to provide that finer control.

I don't think we need to generalise the problem to all function
inlinings. There are specific practical problems caused by inlining
foreign calls that are not a problem for ordinary Haskell functions.

> Besides, the standard so far doesn't cover command line options at all.
> So, there is the more general question of whether it should.

I don't think we need to specify the command line interface. The
required headers can be put in the module.

> > So some syntax off the top of my head:
> > 
> > foreign import cheader module-local "foo/bar.h"
> > 
> > I think there are 3 possibilities for the C header escape/scope setting
> > (which should probably be manditory rather than optional):
> > module-local
> > package-local (extension for compilers that have a notion of a package)
> > global
> 
> Is this additional complexity really necessary or would the use of
> NOINLINE pragmas not suffice?  It's really in a library context where
> you want to restrict the inlining of foreign functions, but there the
> foreign functions are probably not much used inside the library itself,
> but mainly exported, so I doubt that you would get much of a performance
> loss by just tagging all foreign imported functions that you don't want
> to escape as NOINLINE.

What I really want is for the issue of header scope to be something that
can be checked by the compiler. As a distro packager I see far too many
people getting it wrong because they don't understand the issue. If we
could declare the intended scope of the header files then 1. people
would think about and 2. if they got it wrong it'd be checkable because
the compiler would complain.

As it is at the moment people don't know they're doing anything dodgy
until some user of their package gets a mysterious gcc warning and
possibly a segfault.

If we just tell everyone that they should use NOINLINE then they won't
and they'll still get it wrong.

The reason for some specific syntax rather than using NOINLINE is that
the compiler will be able to track the header files needed by each
module. So we can avoid the situation where a call gets made outside the
scope of its defining header file - either by automatically #including
the header file in the right place, or by complaining if the user does
not supply the header (eg by putting it in the .cabal file).

So it's not the general issue of inlining but the specific problem of
what C header files are required to compile what modules.

The ideal situation I imagine is that the scope of the headers can be
checked automatically so that the compiler or cabal will complain to a
library author that their private header file needs to be marked as
local to the package/module or included in the library package file and
installed with the package.

Duncan

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


FFI proposal: allow some control over the scope of C header files

2006-04-21 Thread Duncan Coutts
One problem that people writing FFI bindings often run into is that they
do not understand exactly where C header files are required to be
available.

The easy case is importing some C function defined in a well known and
widely available C header file (eg gtk/gtk.h). In this case we just make
sure that header is available for compiling every module in the package
and add that header file to the package info file (or .cabal file) so
that every module that uses the package will have the C header
available. In this case there is no problem with C calls being inlined
outside of the module which imported them since the C header file will
be available everywhere.

The tricky case is that people often use "private" header files that are
#included when compiling a module/package but are not installed along
with that package and so are not #included when compiling client
modules. Most of the time this works, however the Haskell compiler is
allowed to inline across modules and if it chooses to inline the C call
into a client module then things will break. Sadly it still compiles and
sometimes even works since C allows calling a C function without a
prototype. However occasionally it's going to break horribly.

Allowing us to limit where the C headers will be required would be very
useful. Sometimes it is very convenient to have private header files
that will not be installed with the package. It is also sometimes the
case that it's much more convenient to not require that the user has a
set of C header files installed to be able to use a library package.
Examples of this include some windows packages, eg DriectX where it's
rather inconvenient to require that users have the MS DirectX SDK
installed.

Currently GHC has a de-facto way of limiting the required scope of C
header files to a module - by using the standard FFI syntax (!). I know
people are already using this trick to allow the use of private header
files.

This issue also touches on the related issue that the way of specifying
C header files in the FFI spec is not really optimal. GHC implements a
couple other methods and these are probably used more that the method in
the FFI spec.

So I suggest that we briefly consider some possibilities for extending
control over where C header files will be needed and perhaps also for
specifying what C header files are needed in the first place.

I think we'd want to be able to specify that a C header file not
"escape" a module boundary and probably we'd also want to be able to ask
that it not escape a package boundary (though this may be beyond the H'
spec since Haskell does not talk about packages).

It would also be convenient to be able to specify that a module needs a
particular C header file rather than having to specify it in each
foreign import decl. Currently this can be done by cabal in a
compiler-specific way (it uses ghc's -#include command line mechanism)

It's a reasonable question to ask if specifying a C header file should
go in the module source code or elsewhere (eg a .cabal file) since
afterall we don't specify search paths etc in the module. I'd say that
it is right that the name of the header file be in the module source
code and that the search paths etc be external.

So some syntax off the top of my head:

foreign import cheader module-local "foo/bar.h"

I think there are 3 possibilities for the C header escape/scope setting
(which should probably be manditory rather than optional):
module-local
package-local (extension for compilers that have a notion of a package)
global

this should allow us to automatically check what C headers are needed by
client modules.

Duncan

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


Re: FFI, safe vs unsafe

2006-03-29 Thread Duncan Coutts
On Wed, 2006-03-29 at 07:32 -0600, Taral wrote:
> On 3/29/06, Simon Marlow <[EMAIL PROTECTED]> wrote:
> > If we were to go down this route, we have to make reentrant the default:
> > 'unsafe' is so-called for a good reason, you should be required to write
> > 'unsafe' if you're doing something unsafe.  So I'd suggest
> >
> >   unsafe
> >   concurrent unsafe
> >   concurrent  -- the hard one
> >   {- nothing -}
> 
> Can I suggest "sef" in this? Most cases of "unsafe" are actually
> claims that the call is side-effect free.

c2hs uses the keyword "pure" for this purpose, which I rather like.

c2hs transforms:
{# call pure foo_bar #}

into a call plus a foreign import with the "unsafe" tag.

Duncan

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


Re: Pragmas for FFI imports

2006-02-21 Thread Duncan Coutts
On Tue, 2006-02-21 at 20:13 +0200, 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 think there are some improvements planned to Cabal in the area of
optional dependencies.

> > 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.

However this is exactly the package structure that we want for distro
packages. We really do want all those foo-mysql packages.

Think about what the debian package would be like if there were only
one. You'd have one package that depended on all of those different
database systems. Now in practise they would not do this because it's
not an acceptable solution. They would be forced to split the package up
into several bits, on for each db system. So it's much better if it's
done this way from the start.

Oh except will really complain about item 6) above. People really really
will not like installing postgres and mysql just to use a binding for
sqlite. hsql and hdbc have all these backends but there is no package
that depends on all the backends so you can install just the ones you
need.

Duncan

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


Re: Pragmas for FFI imports

2006-02-21 Thread Duncan Coutts
On Mon, 2006-02-20 at 19:59 -0800, John Meacham wrote:
> On Fri, Feb 17, 2006 at 01:45:27AM +0200, Einar Karttunen wrote:
> > I would like to propose two pragmas to be included in Haskell'
> > for use with FFI. One for specifying the include file defining
> > the foreign import (INCLUDE in ghc) and an another for defining
> > a library that the foreign import depends on, called FFI_LIB
> > (not implemented at the moment). These changes would not break
> > any existing code.
> 
> Just to expand on this, Einar is working on adding this support to jhc
> right now in his work on the library system in jhc. the semantic we
> decided on was that an
> 
> {-# INCLUDE "foo.h" #-}

I'd just like to note that this shouldn't be the only way to specify
this info. For many real FFI bindings we don't know the right search
paths, defines, libs, lib link-time search paths, lib runtime search
paths etc until we start configuring on the target system. (Though we do
almost always know statically the names of the header files). This
information is often obtained from pkg-config and other similar
foo-config programs.

For example:
$ pkg-config --cflags --libs gtk+-2.0

-I/usr/include/gtk-2.0 -I/usr/lib64/gtk-2.0/include
-I/usr/include/atk-1.0 -I/usr/include/cairo -I/usr/include/pango-1.0
-I/usr/include/glib-2.0 -I/usr/lib64/glib-2.0/include  -lgtk-x11-2.0
-lgdk-x11-2.0 -latk-1.0 -lgdk_pixbuf-2.0 -lm -lpangocairo-1.0
-lpango-1.0 -lcairo -lgobject-2.0 -lgmodule-2.0 -ldl -lglib-2.0

This information is not universally static. It depends on the machine
were looking at. So it can't be embedded in .hs files. Current practise
is to grok the output of pkg-config and generate the .cabal file at
configure time. Cabal then passes all this info to ghc on the command
line.


So what I'm saying is that it'd be nice to standardise these simple
include pragmas, but I think it'd be more useful to think about
something to help with the bigger cases. Not that I am necessarily
suggesting we standardise the compiler command line syntax but this is
an important (for practical & portability purposes) and yet
under-specified part of the FFI spec.

Perhaps it's not a problem because we can say that Cabal "just knows"
the compiler-specific methods of supplying this information to each
Haskell implementation that Cabal supports. But it's certainly arguable
that this is unsatisfactory.

Duncan

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


Re: Parallel list comprehensions

2006-02-04 Thread Duncan Coutts
On Sat, 2006-02-04 at 15:11 +0100, John Hughes wrote:
> I noticed ticket #55--add parallel list comprehensions--which according to
> the ticket, will probably be adopted. I would argue against.

Can I second this?

The only time I ever used a parallel list comprehension was by accident.
I accidentally used '|' rather than ',' in a list comprehension and
ended up with a bug that was quite hard to track down.

Now one could argue that I could make a similar mistake with pretty much
any language feature, but it's precisely because it's a rarely used
language feature that it makes this problem worse because you're not
looking for that kind of problem.

Duncan

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


Re: Priorities

2006-02-02 Thread Duncan Coutts
On Thu, 2006-02-02 at 11:38 +0100, John Hughes wrote:

> One such tool is wxHaskell--named by 19% of Haskell users in my survey,
> it's the de facto standard GUI toolkit. wxHaskell makes essential use of
> existential types in its interface, a strong reason for including them in
> Haskell'. It also uses multi-parameter classes and functional dependencies,
> although much less heavily.

My priorities for Gtk2Hs (the second most popular GUI toolkit in John
Hughes's survey) are very similar. We have adopted wxHaskell's style of
attributes which is what uses existential types. I should not that in
both cases the use of existential types is not essential. It was done
that way only because the symbol that people wnated to use ':=' happens
to be a constructor operator. If '=:' were used instead then existential
construcotr types would not be necessary. We might make use of MPC
+FunDeps if they were standard but it is not at all crucial.

Our main concern is namespace issues. As I've said before, Gtk2Hs is a
very large library but with the current module system it must export a
flat name space. wxHaskell solves this with somewhat of a hack. It
defines many multi-parameter type classes to allow the same name to be
used by different widgets (with hopefully the same general meaning). I
think this would be better solved by using qualified names.

We have been trying hard to avoid non-H98isms so that we can hope to
work with compilers other than ghc. So having these features
standardised would allow us to present a better api and allow us to
remain portable.

> What other tools "must" be supported by Haskell'? What other extensions
> must be present to support them? What issues remain before those
> extensions are standardized, and thus frozen in stone for many years to 
> come?

Another gripe is in the FFI, in the handling of include files. The
method preferred by GHC and the method preferred by the FFI spec are
rather at odds. GHC prefers the file to be specified on the command line
while the FFI spec prefers it to be specified in each and every FFI
import declaration. If one does the latter then GHC refuses to inline
foreign calls across modules.

Other mundane but useful things include the ability to specify different
FFI import decls for different platforms without using #ifdef's. This
would allow a program using a Gtk2Hs GUI to be compiled to bytecode with
YHC and run on different platforms, rather than having to be built
differently on each platform. (The issue is that even for portable C
libs, the calling convention and symbol names can differ across
platforms. This is true to a minor degree with the Gtk+ library.)

Duncan

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Tue, 2006-01-31 at 13:28 +, Duncan Coutts wrote:
> On Tue, 2006-01-31 at 13:59 +0100, Wolfgang Jeltsch wrote:
> > Am Montag, 30. Januar 2006 19:02 schrieb Duncan Coutts:
> > > [...]
> > 
> > > I have often thought that it would be useful to have an existential
> > > corresponding to a class.
> > 
> > How would this work with multi-parameter classes, constructor classes, 
> > etc.? 
> > If you propose something that only works in conjunction with a special kind 
> > of classes I would hesitate to include such thing in a Haskell standard.
> 
> As John Mecham said it'd be for single parameter type class with a
> parameter of kind *.
> 
> But you're probably right that people should get more experience with
> using this technique before giving special support in the language to
> make it convenient.
> 
> As Bulat noted we can already use this construction:
> 
> class (Monad m) => Stream m h | h->m where
> vClose :: h -> m ()
> vIsEOF :: h -> m Bool
> .
> 
> data Handle = forall h . (Stream IO h) => Handle h
> 
> instance Stream IO Handle where
> vClose(Handle h) = vCloseh
> vIsEOF(Handle h) = vIsEOFh
> .
> 
> But we have to give the name of the most general instance a different
> name to the class which is rather inconvenient.
> 
> So perhaps we should start with allowing a class a data type to have the
> same name and in a future standard think about making it easy to define
> Bulat's Handle instance above with a short hand like:
> 
> class (Monad m) => Stream m h | h->m where
> vClose :: h -> m ()
> vIsEOF :: h -> m Bool
> .
>   deriving data Stream

Actually this is unnecessary. All we need is:

class (Monad m) => Stream m h | h->m where
vClose :: h -> m ()
vIsEOF :: h -> m Bool

newtype Handle = exists s. Stream s => Handle s
  deriving Stream


So all we need is existentials and newtype-deriving.

Duncan

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Tue, 2006-01-31 at 13:59 +0100, Wolfgang Jeltsch wrote:
> Am Montag, 30. Januar 2006 19:02 schrieb Duncan Coutts:
> > [...]
> 
> > I have often thought that it would be useful to have an existential
> > corresponding to a class.
> 
> How would this work with multi-parameter classes, constructor classes, etc.? 
> If you propose something that only works in conjunction with a special kind 
> of classes I would hesitate to include such thing in a Haskell standard.

As John Mecham said it'd be for single parameter type class with a
parameter of kind *.

But you're probably right that people should get more experience with
using this technique before giving special support in the language to
make it convenient.

As Bulat noted we can already use this construction:

class (Monad m) => Stream m h | h->m where
vClose :: h -> m ()
vIsEOF :: h -> m Bool
.

data Handle = forall h . (Stream IO h) => Handle h

instance Stream IO Handle where
vClose(Handle h) = vCloseh
vIsEOF(Handle h) = vIsEOFh
.

But we have to give the name of the most general instance a different
name to the class which is rather inconvenient.

So perhaps we should start with allowing a class a data type to have the
same name and in a future standard think about making it easy to define
Bulat's Handle instance above with a short hand like:

class (Monad m) => Stream m h | h->m where
vClose :: h -> m ()
vIsEOF :: h -> m Bool
.
  deriving data Stream


I have to say though that I am surprised that us Haskell folk are not
more interested in making it easy or even possible to have abstract
values accessed via interfaces. Classes make it easy and elegant to have
type based dispatch but for the few times when value based dispatch
really is necessary it's a pain. The fact that we've suffered with a
non-extensible abstract Handle type for so long is an example of this.

Duncan

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Mon, 2006-01-30 at 18:20 -0800, John Meacham wrote:
> so if I understand this proposal properly, it would mean the following
> 
> every single parameter type class whole parameter is of kind * 
> class Foo a where
> 
> automatically declares a data type defined as

perhaps semi-automatically?

class Foo a where
  ...
  ...
  deriving data Foo

> data Foo = exists a . Foo a => Foo_ a   
> (where Foo_ is some internal, non user accessable name)
> 
> and an instance
> 
> instance Foo Foo where
> method (Foo_ x) = method x 
> ...
> 
> this all seems quite nice, I really like it, we can always determine
> whether a name is a class or type from context (I think the only reason
> the namespaces are combined is due to import/export lists)


Duncan

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Mon, 2006-01-30 at 18:20 -0800, John Meacham wrote:
> so if I understand this proposal properly, it would mean the following
> 
> every single parameter type class whole parameter is of kind * 
> class Foo a where
> 
> automatically declares a data type defined as
> 
> data Foo = exists a . Foo a => Foo_ a   
> (where Foo_ is some internal, non user accessable name)
> 
> and an instance
> 
> instance Foo Foo where
> method (Foo_ x) = method x 
> ...
> 
> this all seems quite nice, I really like it, we can always determine
> whether a name is a class or type from context (I think the only reason
> the namespaces are combined is due to import/export lists)
> 
> the only issue is the autoboxing. we can't introduce an actual
> constructor because constructors are in a different namespace. so we
> would need to automatically turn anything of type Foo a => a into a Foo
> when it is used as such.

Is that really necessary (or desirable)?

As it was suggested in the thread on existential types it probably wants
to be made explicit when you throw away type information by putting
something behind an interface.

How about just making the conversion "Foo a => a -> Foo" explicit? And
of course the conversion is just the constructor Foo.

Duncan

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-30 Thread Duncan Coutts
On Mon, 2006-01-30 at 18:13 +0100, Sebastian Sylvan wrote:
> Seems like a convenient feature to me.
> 
> Also, you may want to have a function which works on a list of any
> values which are both readable and showable.
> Say (mockup syntax):
> 
> foo ::  => [a]
> foo = [ 1, True, myRocketLauncher ]
> 
> Which would create a newtype called "ShowReadAble" or something with
> extistential types and also instantiate that type in both Show and
> Read.
> 
> I do agree that this is something I'd like in a lot of cases, and it
> probably would be used quite a bit more if it were convenient (and
> standardised!).
> 
> I leave it to someone else to figure out how to make this play nice
> with e.g. type inference.

I have often thought that it would be useful to have an existential
corresponding to a class.

There are several examples in Haskell where one wants to manipulate
lists of values that support a common interface but are not necessarily
the same type.

Haskell makes it very convenient to do type based static dispatch but
rather inconvenient to do runtime value dispatch. In general the
preference for type based static dispatch is good. In OOP languages
people often use the OOP value based dispatch when the Haskell style
would be more appropriate, but it is not convenient in those languages.

On the other hand there are sometimes when it really is better to do the
value base dispatch. For example an extensible IO Handle data type. It
is necessary to have lists of Handles so we can't have a Handle type
class. One could have a record of functions.

When I thought about this before I came to the conclusion that it would
be convenient to be able to have a type class and a corresponding data
type with the same name. The class gives the interface and the data type
can be made a member of the type:

class IStream s where
  readBlock :: s -> IO Block

data IStream = IStream {
  istream_readBlock :: IO Block
}

instance IStream IStream where
  readBlock s = istream_readBlock s

abstractIStream :: IStream s => s -> IStream
abstractIStream s = IStream { istream_readBlock = readBlock s }


So this allows us to have a type class so we can do ordinary type class
stuff or if we need to manipulate streams of different underlying types
only via their IStream interface then we can use abstractIStream to
convert any instance of the IStream class to its most general instance,
namely the IStream data type.

But the above translation is a bit cumbersome and could be optimised.
What's really going on is we're just converting from a class dictionary
to an explicit dictionary. If this sort of thing were supported directly
in the language then the dictionary conversion would be a no-op.

So to summarise the feature, it might be nice to make doing runtime
value-based dispatch through an interface (almost as) easy as the
existing class mechanism which allows static type-based dispatch through
an interface. Also to allow explicit conversion from one form to the
other (anything in the class to a most general instance).

Duncan

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


Re: Removal candidates in patterns

2006-01-26 Thread Duncan Coutts
On Thu, 2006-01-26 at 17:01 +, Olaf Chitil wrote:

> Why are these patterns so hard to implement for Hat? Surely the Haskell 
> report gives a translation into simple core Haskell. Well, Hat does not 
> use this translation because it does not want to be an inefficient 
> pattern matcher (leave that job to the compiler) but produce a trace of 
> the Haskell program as it is written. However, both n+k and k patterns 
> cause calls of functions ( (-), (==) etc) that Hat has to record in its 
> trace.

Does it not have to do that for character and string patterns too?

I suppose that the proposals to create a string class and have
string/character constants overloaded by that class would cause similar
problems for Hat.

Duncan

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


Re: Removal candidates in patterns

2006-01-26 Thread Duncan Coutts
On Thu, 2006-01-26 at 19:35 +, Olaf Chitil wrote:
> As response to both Aaron and Duncan,
> 
> >foo 0 = ...
> >foo n = ...
> >  
> >
> And what about the negative numbers? For negative numbers the second 
> equation matches, which in 90% of all cases in practise has never been 
> written for them. Aaron's Ackerman function disappears in infinite 
> recursion... Besides, what is ack 0.5 0.5?

Isn't the same true for:

foo n | n == 0= ...
  | otherwise = ...

It's still going to fail for negative numbers.

> The use of n+k patterns, but also the definition pattern above wrongly 
> lead programmers to believe that they are dealing with natural numbers. 
> There is no nice primitive recursion for integers. Even worse, without a 
> type signature restricting its type, foo will be defined for all numeric 
> types. For Float or Rational it makes hardly any sense.

The above example is still defined for all numeric types.

Eliminating that syntax form doesn't remove those problems.

> If Haskell had a type for natural numbers I'd be in favour of n+k and k 
> patterns (working only for this type, not any other numerical type).

I'm in favour of removing n+k patterns too.

> Using primitive recursion on integers or even arbitrary numbers is 
> misleading. You can teach primitive recursion nicely for algebraic data 
> types, because the recursive pattern of the function definition follows 
> the recursive pattern of the type definition.

Char is a type that is not constructed recursively and yet no one seems
to have problems with character literals as constructors and thus as
patterns. Each character literal is a Char constructor. Why can't each
numeric literal be a constructor for the numeric types?

I think it's a perfectly reasonable mental model for people to believe
that:
data Char = 'a' | 'b' | 'c' | ...
data Int  = ... -2 | -1 | 0 | 1 | 2 | ...

I don't see why we should remove one and not the other. Students will
ask why the can pattern match on strings, characters and booleans but
not numbers.

Perhaps primitive recursion on integers is misleading, but people will
still write

foo n | n == 0= ...
  | otherwise = ...

where they previously wrote

foo 0 = ...
foo n = ...

so what have we gained except less notational convenience?

Not all pattern matching on numeric literals is involved with recursion
on integers, where as virtually all n+k patterns is used for that
purpose. So there is some distinction between the two forms. n+k
patterns are a quirk of the numeric types. k patterns are regular with
other types in the language.

> With respect to tools of which Hat is one example: If it is hard to 
> build tools, then less tools will be built. Compare the number of tools 
> for Scheme with those for Haskell. Most tools grow out of student 
> projects  or research projects;  these have  rather limited resources.

It's partly the complexity of the language and partly because our latest
language spec (H98) is not the language that we all use (H98 + various
extensions). I'm sure Haskell-prime will help in this area.

I don't mean to belittle the difficulty of building tools. I know how
hard it is, I'm trying to build one too.

Duncan

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


RE: Removal candidates in patterns

2006-01-26 Thread Duncan Coutts
On Thu, 2006-01-26 at 17:31 +, Simon Peyton-Jones wrote:
> I agree that if (n+k) patterns go, then so should k patterns.  Both are
> overloaded, and that's the root of their complexity.

I have to say that we use 'k' patterns in teaching all the time, though
we do not teach n+k patterns. There are lots of cases where it's
convenient to say:

foo 0 = ...
foo n = ...

Intuitively it seems reasonable to me that 1 is a constructor for the
Int type just as 'c' is a constructor for type Char, and since it's a
constructor we can pattern patch on it.

To be honest, the difficulty of the internal translation needed for
tools seems less important to me than the convenience for users. I don't
think the difference that character constants are not overloaded where
as numeric constants are overloaded causes any difficult in
understanding for users.

Duncan

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


Re: Hierarchical module namespace extension not sufficiently flexible

2006-01-23 Thread Duncan Coutts
On Mon, 2006-01-23 at 19:54 +0100, Sebastian Sylvan wrote:
> On 1/23/06, Duncan Coutts <[EMAIL PROTECTED]> wrote:

> > Basically what I want is an extension which allows me to write:
> >
> > > import Graphics.UI.Gtk
> > and then use
> > > ... Button.label ...
> >
> 
> There seems to be a suggestion already which would solve this:
> http://hackage.haskell.org/trac/haskell-prime/wiki/ModuleSystem
> 
> Basically put:
> qualified module GTK.Button as Button
> 
> In the export list.

Yes this was one of the semi-formal proposals that got suggested. I'm
not sure we came to a final conclusion about what the extension exactly
meant. It would definitely be a good place to start the discussion in
the context of the Haskell' process.

Duncan

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


Hierarchical module namespace extension not sufficiently flexible

2006-01-23 Thread Duncan Coutts
To the Haskell' committee,

I think the hierarchical module namespace extension has been generally
successful.

One of the aims was to enable people to use names like Set.union rather
than everyone having to prefix the module name onto the function name
like setUnion. 

The one area where this doesn't quite work is in large packages that
consist of many many modules. Examples include Gtk2Hs and HOpenGL. The
problem with these packages is that they do use modules; they do not
consist of a flat name space. They use the same names in different
modules. This wouldn't be too much a problem except that these large
packages consist of many modules. In the case of Gtk2Hs it has more that
100 modules. So it is impractical to import each module separately.

Basically what I want is an extension which allows me to write:

> import Graphics.UI.Gtk
and then use
> ... Button.label ...

At the moment this is not possible and we have to export buttonLabel
from Graphics.UI.Gtk. This is exactly what we wanted to avoid by using
hierarchical module names.

So I'm not suggesting any particular concrete extension (though people
have suggested various things, see below). I'd be happy with anything
that would allow me to write the above code.

So that's it. That's what we want to do for large practical libs. It
seems reasonable. Every other modern language can do it (see eg the Gtk+
bindings for C++,Java,Python,Ruby,Ocaml,etc).

This issue has been discussed before and people have made various
suggestions:

I originally brought it up:
http://www.haskell.org/pipermail/haskell/2004-December/015085.html

It was discussed more a few months later:
http://www.haskell.org/pipermail/haskell/2005-March/015462.html

and the discussion moved to the libraries list:
http://www.haskell.org/pipermail/libraries/2005-March/thread.html

Duncan

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