[Haskell] Can we do better than duplicate APIs? [was: Data.CompactString 0.3]

2007-03-23 Thread Benjamin Franksen
[sorry for the somewhat longer rant, you may want to skip to the more
technical questions at the end of the post]

Twan van Laarhoven wrote:
> I would like to announce version 0.3 of my Data.CompactString library. 
> Data.CompactString is a wrapper around Data.ByteString that represents a 
> Unicode string. This new version supports different encodings, as can be 
> seen from the data type:
> 
> [...]
> 
> Homepage:  http://twan.home.fmf.nl/compact-string/
> Haddock:   http://twan.home.fmf.nl/compact-string/doc/html/
> Source:darcs get http://twan.home.fmf.nl/repos/compact-string

After taking a look at the Haddock docs, I was impressed by the amount of
repetition in the APIs. Not ony does Data.CompactString duplicate the whole
Data.ByteString interface (~100 functions, adding some more for encoding
and decoding), the whole interface is again repeated another four times,
once for each supported encoding.

Now, this is /not/ meant as a criticism of the compact-string package in
particular. To the contrary, duplicating a fat interface for almost
identical functionality is apparently state-of-the-art in Haskell library
design, viz. the celebrated Data.Bytesting, whose API is similarly
repetitive (see Data.List, Data.ByteString.Lazy, etc...), as well as
Map/IntMap/SetIntSet etc. I greatly appreciate the effort that went into
these libraries, and admire the elegance of the implementation as well as
the stunning results wrt. efficiency gains etc.. However I fear that
duplicating interfaces in this way will prove to be problematic in the long
run.

The problems I (for-)see are for maintenance and usability, both of which
are of course two sides of the same coin. For the library implementer,
maintenance will become more difficult, as ever more of such 'almost equal'
interfaces must be maintained and kept in sync. One could use code
generation or macro expansion to alleviate this, but IMO the necessity to
use extra-language pre-processors points to a weakness in the language; it
be much less complicated and more satisfying to use a language feature that
avoids the repetition instead of generating code to facilitate it. On the
other side of teh coin, usability suffers as one has to lookup the (almost)
same function in more and more different (but 'almost equal') module
interfaces, depending on whether the string in question is Char vs. Byte,
strict vs. lazy, packed vs. unpacked, encoded in X or Y or Z..., especially
since there is no guarantee that the function is /really/ spelled the same
everywhere and also really does what the user expects.(*)

I am certain that most, if not all, people involved with these new libraries
are well aware of these infelicities. Of course, type classes come to mind
as a possible solution. However, something seems to prevent developers from
using them to capture e.g. a common String or ListLike interface. Whatever
this 'something' is, I think it should be discussed and addressed, before
the number of 'almost equal' APIs becomes unmanageable for users and
maintainers.

Here are some raw ideas:

One reason why I think type classes have not (yet) been used to reduce the
amount of API repetition is that Haskell doesn't (directly) support
abstraction over type constraints nor over the number of type parameters
(polykinded types?). Often such 'almost equal' module APIs differ in
exactly these aspects, i.e. one has an additional type parameter, while yet
another one needs slightly different or additional constraints on certain
types. Oleg K. has shown that some if these limitations can be overcome w/o
changing or adding features to the language, however these tricks are not
easy to learn and apply.

Another problem is the engineering question of how much to put into the
class proper: there is a tension between keeping the class as simple as
possible (few methods, many parametric functions) for maximum usability vs.
making it large (many methods, less parametric functions) for maximum
efficiency via specialized implementations. It is often hard to decide this
question up front, i.e. before enough instances are available. (This has
been stated as a cause for defering the decision for a common interface to
list-like values or strings). Since the type of a function doesn't reveal
whether it is a normal function with a class constraint or a real class
method, I imagine a language feature that (somehow) enables me to
specialize such a function for a particular instance even if it is not a
proper class member.

Or maybe we have come to the point where Haskell's lack of a 'real' module
system, like e.g. in SML, actually starts to hurt? Can associated types
come to the rescue?

Cheers
Ben
--
(*) I know that strictly speaking a class doesn't guarantee any semantic
conformance either, but at least there is a common place to document the
expected laws that all implementations should obey. With duplicated module
APIs there is no such single place.

___
Haske

[Haskell] Re: Re: Even higher-order abstract syntax: typeclasses vs GADT

2007-01-22 Thread Benjamin Franksen
Tomasz Zielonka wrote:
> On Mon, Jan 22, 2007 at 11:34:32PM +0100, Benjamin Franksen wrote:
>> I would be interested whether you can not only /check/ well-typedness,
>> but also /establish/ it, i.e. is it possible to have the input to the
>> type-checker be an /untyped/ representation (such as obtained by parsing
>> a program in text form) and the output be a typed one (or else a type
>> error)?
>> 
>> From my very limited understanding of these issues I would say it is not
>> possible, neither with type-classes nor with G[AR]DTs because it would
>> mean the return type of the function 'typecheck' would have to vary
>> depending on the input data, hence you'd need a genuinely dependent type
>> system for such a feat.
> 
> You can do this with existential types and with higher-rank polymorphism
> (the latter if you write your parser in CPS).

Right, now as you say it I remember the CPS trick. Used it myself some time
ago, though not even knowing the term 'CPS' back then ;-) It's a bit
cumbersome to use, though.

However, I haven't the slightest clue how to do this with existentials. Any
pointers (example/paper/wiki/whatever)?

Cheers
Ben

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


[Haskell] Re: Views in Haskell

2007-01-22 Thread Benjamin Franksen
David Roundy wrote:
> Another idea is whether the syntax could be extended to indicate a failure
> to match? This would actually be useful even without views, but it's
> particularly useful with views (and especially so in the context of the
> above warnings).  I'd imagine something like (with stupidly chosen syntax
> of !!!)
> 
> foo (_:_) = True
> foo _ = False
> 
> foo' !!![] = True
> foo' _ = False
> 
> Here I've defined two identical functions to describe what I mean by
> "!!!". I didn't gain anything in this case, but might gain some clarity if
> there
> are multiple constructors.  But more to the point, if we're using views
> (of the vanilla Maybe-always variety), we could gain some efficiency this
> way.
> 
> foo ([], view -> a, []) = foo1 a
> foo (x, !!! view ->, []) = foo2 x
> foo (_, view -> a, y) = foo3 a y
> 
> This isn't a very good example, but the point is I'd like to be able to
> match on Nothing and get the same benefits you mention about the compiler
> being assumed to optimize by calling view only once.  We could achieve
> this by reordering the patterns, but I believe (although I failed to come
> up with one above) that there are sets of pattern matches that aren't
> reducible in that way, which it'd be nice to be able to express succinctly
> by matching on failure to match a pattern.
> 
> Maybe this should be
> 
> foo (x, view /->, []) = foo2 x
> 
> or something like that, to indicate failure, that view doesn't match?

AFAIU, this would be superseded by the "Possible extension 2" (which I
prefer anyway), i.e. drop the requirement that result type must be 'Maybe
a'. The 'cost' of explicitly mentioning constructors becomes an asset in
this case. For instance, your 2nd example becomes:

> foo ([], view -> Just a, []) = foo1 a
> foo (x, view -> Nothing, []) = foo2 x
> foo (_, view -> Just a, y) = foo3 a y

Clearer, IMHO.

Cheers
Ben

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


[Haskell] Re: Even higher-order abstract syntax: typeclasses vs GADT

2007-01-22 Thread Benjamin Franksen
[EMAIL PROTECTED] wrote:
> We show the typeclass implementation of the example used to make the
> case for GADTs. We demonstrate the higher-order abstract-syntax-based
> embedding of a language in Haskell and implement static and dynamic
> semantics of the language. The interpreter of the language is tagless
> and statically assured: Only well-typed terms may be evaluated, and
> the evaluation of those does not get stuck. We use no tags and *no*
> run-time pattern-matching, therefore, the `eval' function has no
> possibility of raising a run-time error.  Our language is
> _non_-strongly normalizing and non-structurally inductive due to the
> presence of Fix; yet the typechecking is decidable and our typeclass
> programs always terminate.

I would be interested whether you can not only /check/ well-typedness, but
also /establish/ it, i.e. is it possible to have the input to the
type-checker be an /untyped/ representation (such as obtained by parsing a
program in text form) and the output be a typed one (or else a type error)?

>From my very limited understanding of these issues I would say it is not
possible, neither with type-classes nor with G[AR]DTs because it would mean
the return type of the function 'typecheck' would have to vary depending on
the input data, hence you'd need a genuinely dependent type system for such
a feat. (However, I am not nearly expert enough to make more than a half
educated guess here, hence posing this as a question rather than a
statement).

Cheers
Ben

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


[Haskell] Re: Announcement: cabal-test

2006-11-26 Thread Benjamin Franksen
Lemmih wrote:
> It's my great pleasure to announce cabal-test, the automatic tester
> for Cabal projects.
> [...]
> http://darcs.haskell.org/~lemmih/cabal-test

What about changing

#!/usr/bin/env runhugs

to

#!/usr/bin/env runhaskell

in your Setup.lhs?

Cheers
Ben

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


[Haskell] Re: [Haskell-cafe] SimonPJ and Tim Harris explain STM - video

2006-11-23 Thread Benjamin Franksen
[sorry for quoting so much, kinda hard to decide here where to snip]

Cale Gibbard wrote:
> On 23/11/06, Jason Dagit <[EMAIL PROTECTED]> wrote:
>> A comment on that video said:
>>
>> - BEGIN QUOTE 
>> It seems to me that  STM creates  new problems with composability.
>> You create two classes of code: atomic methods and non atomic methods.
>>
>> Nonatomic methods can easily call atomic ones ? the compiler could
>> even automatically inject the atomic block if the programmer forgot.
>>
>> Atomic methods and blocks cannot be allowed to call nonatomic code.
>> The nonatomic code could do I/O or other irrevocable things that would
>> be duplicated when the block had to retry.
>>  END QUOTE 
>>
>> I imagine an example like this (some pseudo code for a side effect
>> happy OO language):
>>
>> class Foo {
>>   protected int counter; // assume this gets initialized to 0
>>   public doSomething() {
>> atomic{
>>   counter++;
>>   Console.Write("called doSomething execution# " + counter);
>>   // something which could cause the transaction to restart
>> }
>>   }
>>   public doOtherThing() {
>> atomic{
>>   doSomething();
>>   // something which could cause the transaction to restart
>> }
>>   }
>> }
>>
>> Now imagine doSomething gets restarted, then we see the console output
>> once each time and counter gets incremented.  So one solution would be
>> to move the side effects (counter++ and the console write) to happen
>> before the atomic block.  This works for doSomething, but now what if
>> we called doOtherThing instead?  We're back to having the extra
>> side-effects from the failed attempts at doSomething, right?  We just
>> lost composability of doSomething?  I'm assuming counter is only meant
>> to be incremented once per successful run of doSomething and we only
>> want to see the output to the log file once per successful run, but it
>> needs to come before the log output inside doSomething so that the log
>> makes sense.
>>
>> I realize STM is not a silver bullet, but it does seem like
>> side-effects do not play nicely with STM.  What is the proposed
>> solution to this?  Am I just missing something simple?  Is the
>> solution to make it so that Console.Write can be rolled back too?
> 
> The solution is to simply not allow side effecting computations in
> transactions. They talk a little about it in the video, but perhaps
> that's not clear. The only side effects an atomic STM transaction may
> have are changes to shared memory.
> 
> Another example in pseudocode:
> 
> atomic
>x <- launchMissiles
>if (x < 5) then retry
> 
> This is obviously catastrophic. If launchMissiles has the side effect
> of launching a salvo of missiles, and then the retry occurs, it's
> unlikely that rolling back the transaction is going to be able to put
> them back on the launchpad. Worse yet, if some variable read in
> launchMissiles changes, the transaction would retry, possibly causing
> a second salvo of missiles to be launched.
> 
> So you simply disallow this. The content of a transaction may only
> include reads and writes to shared memory, along with pure
> computations. This is especially easy in Haskell, because one simply
> uses a new monad STM, with no way to lift IO actions into that monad,
> but atomically :: (STM a -> IO a) goes in the other direction, turning
> a transaction into IO. In other languages, you'd want to add some
> static typechecking to ensure that this constraint was enforced.

This is of course the technically correct answer. However, I suspect that it
may not be completely satisfying to the practitioner. What if you want or
even need your output to be atomically tied to a pure software transaction?

One answer is in fact "to make it so that Console.Write can be rolled back
too". To achieve this one can factor the actual output to another task and
inside the transaction merely send the message to a transactional channel
(TChan):

atomic $ do
  increment counter
  counterval <- readvar counter
  sendMsg msgChan ("called doSomething execution# " ++ show counterval)
  -- something which could cause the transaction to restart

Another task regularly takes messages from the channel and actually outputs
them. Of course the output will be somewhat delayed, but the order of
messages will be preserved between tasks sending to the same channel. And
the message will only be sent if and only if the transaction commits.

Unfortunately I can't see how to generalize this to input as well...

Cheers
Ben

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


[Haskell] RE: package mounting

2006-10-30 Thread Benjamin Franksen
Simon Peyton-Jones wrote:

> | > http://hackage.haskell.org/trac/ghc/wiki/PackageMounting
> | 
> | It looks nice, but don't you think the -package-base flag ought to
> | take both the package name *and* the mountpoint?
> | 
> | Otherwise, this looks like what I've wanted all along, if only I knew
> it ;-).
> 
> I think most of you know that GHC 6.6 made (IHMO) a significant step
> forward, by allowing a program to contain multiple modules with the same
> name, if they are from different packages.  That means that package
> authors can choose module names freely, rather than worry about
> accidentally colliding with other packages.

I think this is true only in a very technical sense. I fear that in
practice, library authors will go to great lengths to avoid such
overlapping module names, because introducing them will cause too much
difficulties for library users. The only way to make halfway sure that this
doesn't happen is to use (fixed) module hierarchy prefixes containing (more
or less) the package name, as in "Text.ParserCombinators.Parsec", even
though technically they aren't forced to do so.

> (We'd regard it as 
> unacceptable if the local variables of a function could not have the
> same name as the local variables of another procedure!)

Yes, but this analogy seems to cover only the problem with internal
(package-local, non-exposed) modules. To widen your analogy, we'd regard it
as similarly unacceptable if we had to qualify each exported entity with
the module name each time we use them, even if we are inside the module
that defines them, wouldn't we? Which is today's situation on the
package/module level: We have to completely qualify module names with their
mount point in the module hierarchy, even when refering to them from inside
the package that defines them.

I see, however, one point with Frederik's proposal that isn't clear to me:

Assume library A uses library B. Then, presumably, lib A must chose a mount
point for its use of lib B. Now imagine a program P wants to use lib A as
well as directly import some module from lib B. Is P now free to give lib B
its own mount point, independent of the one that was chosen by lib A? I
think this should definitely be possible. There may, however, be some
issues regarding implementation: Can a compilation system share code
between both 'versions' of lib B (I assume they are /not/ really different
versions but exactly the same one, only referred to via a different 'mount
point')? Hmm, maybe this isn't really a problem. The compiler could simply
alias the module names, similar as to what it does for 'import M as N'.

> That still leaves an open question, not resolved by GHC 6.6: what to do
> if you want to import module M from two different packages into the same
> module?

What if I want to import them into /different/ modules (which are
nevertheless part of the same package)? Can this be easily accomplished
with ghc-6.6?

Cheers
Ben

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


[Haskell] Re: [Haskell - I/O] Problem with 'readFile'

2006-08-27 Thread Benjamin Franksen
L. J. wrote:

>  Hi, I use the operation 'readFile' for obtain information locates on
> a file. When I try to write another information on the same file, I
> obtain this error message: "openFile: permision denied". I found this:
> "The readFile operation holds a semi-closed handle on the file until
> the entire contents of the file have been consumed. It follows that an
> attempt to write to a file (using writeFile, for example) that was
> earlier opened by readFile will usually result in failure with
> isAlreadyInUseError." in this web
> http://www.haskell.org/onlinereport/io.html.
> 
>  How can I break that semi-closed handle for to write in the
> preaviously readed file? Thank you.

Since readFile reads the file lazily (on demand), you have to make sure that
the whole file gets read by completely evaluating the result string.

BTW, I think haskell-cafe is the more appropriate forum for questions like
these.

Cheers
Ben

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


Re: [Haskell] Re: installing streams library

2006-05-26 Thread Benjamin Franksen
On Thursday 25 May 2006 11:36, Bulat Ziganshin wrote:
> Hello Ross,
>
> Wednesday, May 24, 2006, 4:50:39 PM, you wrote:
> >> Now you could make purely functional code raise I/O exceptions,
> >> but that gives rise to a few problems: imprecise exceptions are
> >> difficult to program with (need deepSeq etc.), and they aren't
> >> widely implemented (Hugs doesn't have them, JHC doesn't have them
> >> and may not get them IIUC).
> >
> > Hugs has had imprecise exceptions (but not asynchronous ones) since
> > Nov 2003.
>
> can you please explain or give a pointer - what is an imprecise
> exceptions? i thought that it the synonym for async ones

It's explained here

http://research.microsoft.com/~simonpj/Papers/except.ps.gz

Imprecise exceptions are abotu how you handle exceptions coming from 
pure code, like devide-by-zero and such. Imagine

 x = (something/0) + (something_else/0)

then which of the two subexpressions is the exception "divide by zero" 
associated with? This is not clear in a non-strict language like 
Haskell, where evaluation order is not specified. Imprecise exceptions 
are a way around that by (conceptually) including /all/ 'possible' 
exceptions into a /set/. However, this set is not observable. Only when 
catching an imprecise exception, which /must/ happen in the IO monad, 
can be consult an external 'oracle' that choses just one representing 
element of the set. Of course in a practical implementation this 
element will be determined by the actual evaluation order.

Ben
-- 
You've never looked into my eyes but don't you want to know
What the dark and the wild and the different know -- Melissa Etheridge
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Problems compiling hs-plugins

2006-03-04 Thread Benjamin Franksen
On Saturday 04 March 2006 03:32, you wrote:
> benjamin.franksen:
> > [...]
> > INSTANCE_TYPEABLE1([],listTc,"[]")
> >
> > However, I could not find any definition for these macros. Nor does
> > the package docs mention what to install in order to get them.
>
> [...]
> This Typeable macro issue is due to the Typeable.h header, which used
> to be distributed with GHC. It's not distributed with the GHC head
> anymore -- are you using ghc 6.5?

Ah, yes. This is because I want to build hIDE. The hIDE readme suggested 
to use http://scannedinavian.com/~lemmih/hs-plugins, but scannedinavian 
seems to be dead. Anyway, in the meantime the suggestion has been 
fixed, it now points to http://darcs.haskell.org/~lemmih/hs-plugins 
which I just downloaded. So, maybe all troubles go away now.

> You can work around it by copying Typeable.h from the darcs
> repository into the include/ directory of your ghc distribution, or
> using ghc 6.4.x

I'll try the version above and see what I get. If it doesn't work, I'll 
try copying the Typeable.h file from somewhere.

Many thanks!

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


[Haskell] Problems compiling hs-plugins

2006-03-03 Thread Benjamin Franksen
Please, can anyone help me with this problem:

I just downloaded hs-plugins version 1.0-rc0. (BTW, the stable version 
is not accessible). I configure it (according to the README) and 
everything seems to be ok. However when I try to build it, I get:

aare: .../haskell/hs-plugins > ./Setup.lhs build
Setup.lhs: Warning: The field "hs-source-dir" is deprecated, please use 
hs-source-dirs.
Preprocessing library plugins-1.0...
Building plugins-1.0...
Chasing modules from: 
AltData.Dynamic,AltData.Typeable,Language.Hi.Binary,Language.Hi.FastMutInt,Language.Hi.FastString,Language.Hi.Parser,Language.Hi.PrimPacked,Language.Hi.Syntax,System.Eval,System.Eval.Haskell,System.Eval.Utils,System.MkTemp,System.Plugins,System.Plugins.Consts,System.Plugins.Env,System.Plugins.Load,System.Plugins.LoadTypes,System.Plugins.Make,System.Plugins.Package,System.Plugins.PackageAPI,System.Plugins.ParsePkgConfCabal,System.Plugins.Parser,System.Plugins.Process,System.Plugins.Utils
[ 1 of 24] Compiling AltData.Typeable ( src/AltData/Typeable.hs, 
dist/build/AltData/Typeable.o )

src/AltData/Typeable.hs:452:0:
parse error (possibly incorrect indentation)


Looking at the source reveals that src/AltData/Typeable.hs contains 
macro calls to generate instances for class Typeable, e.g. 

INSTANCE_TYPEABLE1([],listTc,"[]")

However, I could not find any definition for these macros. Nor does the 
package docs mention what to install in order to get them.

Any ideas? Don?

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


[Haskell] Haddock ignores fixity declarations?

2006-02-10 Thread Benjamin Franksen
Hello,

I just wanted to check the precedence of the (.) operator from Prelude 
(http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html) 
and noticed with shock ;) that neither precedence levels nor fixity are 
documented. Is this a known limitation of haddock? How hard would it be 
to add this?

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


Re: [Haskell] Modelling languages for FP (like UML for OO)

2006-01-19 Thread Benjamin Franksen
On Thursday 19 January 2006 14:09, Mads Lindstrøm wrote:
> In object-oriented programming, UML is used to model programs. In
> functional programming (especially Haskell) we use ???

However, not everyone in the OO camp thinks that UML is really useful:

http://archive.eiffel.com/doc/manuals/technology/bmarticles/uml/page.html

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


Re: [Haskell] Simple IO Regions

2006-01-18 Thread Benjamin Franksen
On Wednesday 18 January 2006 11:33, Simon Peyton-Jones wrote:
> I really like the way you use a set of constraints
>   (IN m1 ms, IN m2 ms, IN m3 ms)
> to maintain the set of marks.  Previously I've thought of using a
> nested tuple type
>   (m1, (m2, (m3 (
> to maintain the set, but that is far less convenient.  Very neat.

Nested tuples are more or less what the previous version (the one at 
http://okmij.org/ftp/Haskell/types.html#monadic-regions) was based on. 
(HLists are really almost the same as nested tuples).

> Why do you need the
>   instance IN () b

As I understand it, one instance for some (arbitrary) type is needed so 
that an ordinary handle can be marked before passing it to a procedure 
passed as argument. For instance, in function 'withFile' the handle we 
get from openFile is marked by writing

  (Q handle) :: Q ()

Instead of '()' one could use an empty data type as well, like this:

  data Mark
  instance IN Mark b

  ...

  withFile path proc =
...
(\handle -> unIOM $ proc ((Q handle) :: Q Mark)))

or a bit nicer:

  data Mark
  instance IN Mark b

  mark :: Handle -> Q Mark
  mark h = Q h

  ...

  withFile path proc =
...
(\handle -> unIOM $ proc $ mark handle))

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


Re: [Haskell] Re: Haskell DB bindings (was Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-17 Thread Benjamin Franksen
On Tuesday 17 January 2006 16:08, Keean Schupke wrote:
> John  wrote:
> >On 2006-01-14, Keean Schupke <[EMAIL PROTECTED]> wrote:
> >>Erm, has nobody replied to this yet? I want a robust interface,
> >> that uses bracket notation all the way down, so that any error is
> >> caught and resources are freed appropriately without the use of
> >> finalizers (which may not get run and lead to resource starvation
> >> - they are not reliable
> >
> >To be sure, your only failure situation in this case is if you're
> >dealing with many connections *and* creating/destroying them
> > frequently.
> >
> >Hopefully you wouldn't be.
>
> You could be using connection pooling in the database driver or ODBC
> layer... Here the minimal
> overhead of opening/closing allows you to use a "bracket" within each
> connection, rather than around
> the whole server. Besides which the goal is not just to be safe in
> practice, but to be theoretically safe in all
> circumstances. If you allow the programmer to shoot themselves in the
> foot, then they often will (for example
> memory management and buffer overflows)... Its no good to partly
> remove responsibility, as that makes bugs
> more likely not less likely (If the programmer has to deal with an
> opaque system with flaws, unless the programmer
> is highly aware of those flaws they will take no account of them in
> their coding). The only way you can give the
> programmer a genuine black box to play with, is if it is
> theoretically safe, then the programmer can (ab)use it
> how they wish without accidentally breaking the conditions of usage.

I agree most strongly. Furthermore, as a /user/ of a library, what I 
want is simple semantics and guarantees are always simpler than side 
conditions, "take care when doing this or that", etc.. I just don't 
want to have to care about such stuff. Also, to make things easier one 
often choses bad programming style ("defensive programming") in order 
to avoid the complex reasoning necessary to ensure that the program 
"behaves well". For instance, it is tempting to encapsulate the whole 
program into the 'withDB' bracket, instead of only the part that 
actually uses the DB connection, just to be on the safe side. If the 
type system catches this kind of errors, one is encouraged to restrict 
the scope of the DB connection (or whatever), resulting in earlier 
freeing of resources and better modularity.

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


Re: [Haskell] Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-09 Thread Benjamin Franksen
On Monday 09 January 2006 10:03, Axel Simon wrote:
> On Sun, 2006-01-08 at 14:51 +, Keean Schupke wrote:
> > My solution to this when developing a database library for my own
> > use was to define the API
> > in a bracket notation style, and only provide safe functions. The
> > idea is that the function obtains the resource, calls a function
> > passed as an argument, then frees the resource, so all resouces are
> > guaranteed to be freed in the correct order... for example:
> >
> > dbConnectWith ::  DbName -> (DbHandle -> IO Result) -> Result
> > dbConnectWith name workFn = do
> > handle <- dbConnectTo name
> > workFn handle `finally` dbDisconnect handle
> >
> > In this way you avoid finalizers... and everthing is safe providing
> > you only export the "with" style functions from the library...
> > Here's an example from the library, the connect function:
>
> I suppose you meant to write "result" rather than "Result". This
> style of functions is only safe if the user ensures that DbHandle is
> never returned as part of the result. You should have that in your
> documentation.

I wanted to mention this too, but you were quicker ;)

> As far as I can tell, the only general solution is to use finalizers
> and, if you really need to enforce a sequence of finialization,
> touchForeignPtr. 

Repeat: touchForeignPtr can NOT be used to enforce finalization order.

> A practical issue with touchForeignPtr is that it 
> cannot be conveniently called from another finalizer, since the
> latter live in C. 

What do you mean "live in C"? Can't or shouldn't finalizers be written 
in Haskell, too?

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


Re: [Haskell] Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-07 Thread Benjamin Franksen
On Wednesday 04 January 2006 20:13, John Goerzen wrote:
> On 2006-01-04, Krasimir Angelov <[EMAIL PROTECTED]> wrote:
> >> I use ForeignPtrs everywhere in HDBC to try to make sure that
> >> nothing like this happens, and also that The Right Thing happens
> >> if a database handle gets garbage collected without being
> >> explicitly closed first.
> >
> > I prefer not to rely on ForeignPtrs. It isn't guaranteed that they
> > will be run. Another problem is that the order in which finalizers
> > are executed isn't specified. In this case the connection handle
> > can be
>
> Well, yes and no.  It would be impossible to garbage collect (and
> thus finalize) any object for which references to it still exist. 
> Statement handles in HDBC maintain references to the database handle
> pointers, either directly or indirectly, so I can't see how it is
> possible for a database handle to be finalized before the statement
> handle in this situation.

Hi John,

I fear it /is/ possible. This is a very unfortunate situation and one I 
had quite some difficulties to understand, when Simon Marlow explained 
it to me.

The problem is that finalization of the statement handle might be 
delayed indefinitely. The data dependencies between statement and 
connection handle only ensures that whenever the statement handle is 
alive, then too is the connection handle. But it does not say anything 
about what happens in which order after /both/ are dead (garbage). As 
soon as the connection handle to garbage, too, bothe handles can be 
finalized in /any/ order.

As I pointed out before, this is a very bad thing, because it makes 
finalizers a whole lot less useful than they could be if an order 
between finalizations could be specified (directly or indirectly). The 
arguments against such a solution are mostly: (1) it is difficult to 
implement efficienty and (2) the programmer could accidentally cause 
finalizer deadlocks by specifying circular dependencies.

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


Re: [Haskell] Making Haskell more open

2005-12-20 Thread Benjamin Franksen
On Tuesday 20 December 2005 11:13, Ketil Malde wrote:
> On e.g. Wikipedia, articles are neutral pieces of text, and it's very
> easy to improve it in any way.  In Hawiki, I feel there is a large
> degree of ownership attached to each paragraph, and it makes me a bit
> wary of modifying it.  Is it okay if I rewrite the page?  Should I
> keep the signatures?  So while Wikipedia feels like a commons, Hawiki
> much less so, and the net result is more often than not that I just
> leave it.

You are very precisely formulating the reason I, too, have largely 
hesitated to contribute to the wiki.

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


Re: [Haskell] Making Haskell more open

2005-11-11 Thread Benjamin Franksen
On Saturday 12 November 2005 02:30, Benjamin Franksen wrote:
> On Friday 11 November 2005 13:56, Wolfgang Jeltsch wrote:
> > Am Donnerstag, 10. November 2005 12:27 schrieb Simon Peyton-Jones:
> > > [...]
> > >
> > >   * The GHC user manual [currently generated using DocBook]
> >
> > I think it should continue to be written in DocBook.  (It should
> > switch to DocBook XML if it's still using SGML DocBook.)  XML
> > documents are "type-safe" in contrast to LaTeX documents, for
> > example.  XML is well supported.  DocBook stresses logical markup
> > and allows very specific markup and therefore supports conversion
> > into different formats (HTML, PDF, ...) very well. Again, what do
> > others think?
>
> Yes. In fact I like the current GHC manual as it is.

Sorry, that comment seems to miss the point. What I wanted to say is: 
However the source format is going to be changed to better support user 
contributions, I would like it to remain similar in its (processed) end 
user appearance.

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


Re: [Haskell] Making Haskell more open

2005-11-11 Thread Benjamin Franksen
On Friday 11 November 2005 13:56, Wolfgang Jeltsch wrote:
> Am Donnerstag, 10. November 2005 12:27 schrieb Simon Peyton-Jones:
> > [...]
> >
> > * The GHC user manual [currently generated using DocBook]
>
> I think it should continue to be written in DocBook.  (It should
> switch to DocBook XML if it's still using SGML DocBook.)  XML
> documents are "type-safe" in contrast to LaTeX documents, for
> example.  XML is well supported.  DocBook stresses logical markup and
> allows very specific markup and therefore supports conversion into
> different formats (HTML, PDF, ...) very well. Again, what do others
> think?

Yes. In fact I like the current GHC manual as it is.

> >   How would we make sure it stayed organised?  And avoid
> >   getting screwed up by malicious folk?
>
> At Wikipedia, you can log in and modify content and you can modify
> content while not being logged in.  In the first case, the history
> mentions your username, in the second case, it mentions your IP
> address.  I think, MediaWiki can be configured so that only logged-in
> users are able to do modifications.  As far as I can remember, I once
> saw a site using MediaWiki, which didn't allow modifications from
> non-registered users.
>
> But honestly, would we need to protect ourselfs from malicious folk? 
> At Wikipedia, they have problem with malicious people at a couple of
> articles, so they sometimes have to lock articles.  (This tells us
> that article locking obviously is another feature of WikiMedia.  As
> far as I know, this kind of locking can be done by different persons,
> not just one super user.)  But who would want to screw up pages about
> Haskell?

Spambots are the worst problem, I guess.

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


Re: [Haskell] really undecidable instances?

2005-10-30 Thread Benjamin Franksen
On Sunday 30 October 2005 21:59, David Menendez wrote:
> Benjamin Franksen writes:
> > This is the data type declaration:
> > > data Node23 tree a
> > >   = N2 (tree a) a (tree a)
> > >
> > >   | N3 (tree a) a (tree a) a (tree a)
> >
> > and this is the instance, where the error is reported:
> > > instance (Pretty a, Pretty (tree a)) => Pretty (Node23 tree a)
> > > where ...
> >
> > The class Pretty is from Daan Leijen's pprint library.
> >
> > I think that the 'non-type variable' refered to above is the
> > application (tree a) in the constraint (Pretty (tree a)), which is
> > arguably "almost" a type variable. In this case I think it is even
> > more obvious that it can't cause a loop, since the LHS clearly has
> > a type constructor removed, right?
> >
> > I mention this mainly because my module is otherwise completely H98
> > and I thought it would be nice to keep it that way. I need the
> > Pretty instance for debugging only, so it's not really a
> > show-stopper. Still I wonder if somebody knows a work-around that
> > doesn't need a language extension (some newtype trick, maybe?).
>
> I believe the "correct" way to do this is with a Pretty-promoting
> constructor class.
>
>
> class Pretty'1 f where
> pretty'1 :: Pretty a => f a -> Doc
> prettyList'1 :: Pretty a => [f a] -> Doc
>
> instance (Pretty a, Pretty'1 tree) => Pretty (Node23 tree a)
> where ...
>
> Your typical Pretty'1 instance will look like this:
>
> instance Pretty'1 T where
> pretty'1 = pretty
> prettyList'1 = prettyList

Works like a charm. Thanks a lot!

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


Re: [Haskell] really undecidable instances?

2005-10-30 Thread Benjamin Franksen
On Monday 17 October 2005 15:57, Simon Peyton-Jones wrote:
> | Wolfgang Jeltsch:
> | what ist the problem with instance declarations like the following:
> |
> | instance C Int a => D Char [a]
> |
> | Why are such declarations only allowed with
> | -fallow-undecidable-instances in
> | GHC?  How can they result in undecidability?
>
> This one can't.  But it's hard to formulate a general rule.
> -fallow-undecidable-instances simply says that you, the programmer,
> take responsibility for termination.  Without the flag, GHC uses a
> simple but sometimes over-conservative rule

Hi,

I've now been bitten by the same 'over-conservatism' of H98. In my case 
it's

Non-type variables in constraint: Pretty (tree a)
(Use -fallow-undecidable-instances to permit this)
In the context: (Pretty a, Pretty (tree a))

This is the data type declaration:

> data Node23 tree a
>   = N2 (tree a) a (tree a)
>   | N3 (tree a) a (tree a) a (tree a)

and this is the instance, where the error is reported:

> instance (Pretty a, Pretty (tree a)) => Pretty (Node23 tree a) where
>   ...

The class Pretty is from Daan Leijen's pprint library.

I think that the 'non-type variable' refered to above is the application 
(tree a) in the constraint (Pretty (tree a)), which is arguably 
"almost" a type variable. In this case I think it is even more obvious 
that it can't cause a loop, since the LHS clearly has a type 
constructor removed, right?

I mention this mainly because my module is otherwise completely H98 and 
I thought it would be nice to keep it that way. I need the Pretty 
instance for debugging only, so it's not really a show-stopper. Still I 
wonder if somebody knows a work-around that doesn't need a language 
extension (some newtype trick, maybe?).

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


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Benjamin Franksen
On Thursday 13 October 2005 13:21, Simon Peyton-Jones wrote:
> If so, than rather than invent a whole new mechanism, why not simply
> extend the existing superclass mechanism to allow a single instance
> decl to declare instances for several classes?  For example, one add
> to Haskell 98 the following:
>   an instance declaration for a class CD with superclasses C and D
> may
>   give the instances for its superclasses C and D
>
> [One could quibble about details.  E.g Should the class decl for CD
> *say* whether the instance decl *must* contain decls for the
> superclass methods?  Or can one vary it on a instance-by-instance
> basis, which might be more flexible?]

I just want to mention Robert Will's proposal for "delayed method 
definitions"; see http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/ 
sections 4.3.1 and 4.3.2, which is quite similar to yours.

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


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Benjamin Franksen
On Thursday 13 October 2005 12:22, John Meacham wrote:
> On Thu, Oct 13, 2005 at 12:08:27PM +0200, Wolfgang Jeltsch wrote:
> > > We allow new constructs of this form (the exact syntax is
> > > flexible of
> > >
> > > course):
> > > >  class alias (Foo a, Bar a) => FooBar a where
> > > >foo = ...
> > >
> > > what this does is declare 'FooBar a' as an alias for the two
> > > constraints 'Foo a' and 'Bar a'. This affects two things.
> >
> > Wouldn't it be better to write it this way:
> >
> > class alias (Foo a, Bar a) = FooBar a where ...
> >
> > (Foo a, Bar a) => FooBar a normally means that a type is an
> > instance of Foo and Bar if it is an instance of FooBar but in the
> > case of aliases, a type is also an instance of FooBar if it is an
> > instance of Foo and Bar.
>
> Yeah, I totally agree. it would also reduce confusion with
> superclasses and emphasises the fact that the two sides are
> equivalent everywhere. (except instance heads)
>
> although perhaps
>
> >   class alias FooBar a = (Foo a, Bar a)  where ...
>
> since the new name introduced usually appears to the left of an
> equals sign. This also solves the problems of where to put new
> supertype constraints.

Using '=' instead of '=>', you could even leave out the 'alias':

  class FooBar a = (Foo a, Bar a)  where ...

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


Re: [Haskell] A haddock question

2005-10-10 Thread Benjamin Franksen
On Monday 10 October 2005 15:17, Wolfgang Jeltsch wrote:
> Am Montag, 10. Oktober 2005 13:44 schrieb Benjamin Franksen:
> > [...]
> >
> > Is there a way to persuade haddock to list only instances of data
> > types that are actually visible to the user?
>
> I experienced the same problem and worked around it by enclosing the
> instance declarations for private data types with #ifndef __HADDOCK__
> and #endif.

That seems like a good work-around, for the moment. Thanks for the 
suggestion.

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


Re: [Haskell] A haddock question

2005-10-10 Thread Benjamin Franksen
On Monday 10 October 2005 14:06, Simon Marlow wrote:
> On 10 October 2005 12:44, Benjamin Franksen wrote:
> > I have a module with a public class plus some instances for public
> > data types. In addition, I use this class inside another module
> > where I declare local (module private) data types and make them
> > instances of the class. I had expected that haddock (I am using
> > 0.7) will list in the documentation only instances of data types
> > that are exported, but instead all instances are listed.
> >
> > Is there a way to persuade haddock to list only instances of data
> > types that are actually visible to the user?
>
> Haddock's support for instances is somewhat braindead - it just
> reports all the instances it can find for a given class in the entire
> set of modules it is processing.  In particular, Haddock makes no
> attempt to tell you how to bring these instances into scope: they
> might not be available from the module that exports the class, or the
> type(s), involved in the instance.
>
> Haskell makes this quite hard: an instance is available if it is
> provided by the transitive closure of an imported module.  We clearly
> don't want to report all the available instances in every module's
> documentation, however.   We probably don't want to document every
> module from which an instance is available either.  Nevertheless,
> doing one of these two would be "correct".  I'm open to suggestions.
>
> Benjamin: your example is probably more simple, Haddock probably just
> shouldn't be exposing those instances if they refer to non-exported
> types, I just wanted to point out the more general problem.

Yes, I can see that the general problem is hard to solve. I don't have 
any suggestions how to change the haddock behavior with instances in 
general (i.e apart from fixing the obvious bug regarding non-exported 
data types).

One could even argue that haddock isn't the right place to provide a 
solution and that instead the language itself should be fixed. I know 
this problem is even harder to solve. To make things worse, I don't 
even have a concrete proposal for how to do this and still enjoy all 
the nice features Haskell's type classes provide.

But since you brought up the general issue, let me just point out, that 
the interaction between type classes and the module system is arguably 
the most problematic aspect of Haskell as it stands.

As a programmer (I am not a language designer), this is the point I most 
often stumble upon. IMO, Haskell's module system is just a bit too weak 
for "programming in the large". While type classes (with the usual 
extensions) seem to provide a lot more flexibility and generality, they 
are burdened with their unfortunate interaction with the module system.

Don't get me wrong: Of course it is possible to program large systems in 
Haskell (witness ghc and a growing number of medium and large size 
projects). It is just that many of Haskell's great advantages when 
"programming in the small" do not, IMO, appropriately scale to large 
systems. Witness to this is the still missing "grand unified data 
structure library": The problem here is /not/ that there don't exist 
good implementations. The problem is how to integrate all of them into 
a common framework, with minimal redundancy between interfaces, and a 
maximum of re-use. A related problem is Haskell's weak support for 
abstract data types, at least when constrasted with the ease which with 
concrete data types can be craeted and used.

I think, this is /the/ most important point that should be addressed in 
some future Haskell2 standard. I vaguely imagine some kind of 
unification of the concepts type class/instance and module into a new 
entity that enables the programmer to talk about interfaces and their 
implementation and at the same time control how names are re-used on 
the global level (and, ideally, enable some sort of pattern-matching on 
abstract data types). I have read about proposals to allow 'named' or 
'scoped' instances and I believe that there are some interesting ideas. 
Maybe someone with the right education and experience in language/type 
system design should review such proposals and see if some coherent 
whole can be made out of them.

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


[Haskell] A haddock question

2005-10-10 Thread Benjamin Franksen
Hello,

I have a module with a public class plus some instances for public data 
types. In addition, I use this class inside another module where I 
declare local (module private) data types and make them instances of 
the class. I had expected that haddock (I am using 0.7) will list in 
the documentation only instances of data types that are exported, but 
instead all instances are listed.

Is there a way to persuade haddock to list only instances of data types 
that are actually visible to the user?

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


Re: [Haskell] Re: [Haskell-cafe] Haskell versus Lisp

2005-09-20 Thread Benjamin Franksen
On Friday 16 September 2005 18:40, Glynn Clements wrote:
> Wolfgang Jeltsch wrote:
> > In Haskell, code is data too because code in the sense of
> > imperative actions is described by IO values.  You cannot analyse
> > them.
>
> And thus they are not data.

Huh? I'd say they are not /concrete/ data, but (abstract) data they 
surely are(?)

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


Re: [Haskell] How to use STArray?

2005-08-31 Thread Benjamin Franksen
On Tuesday 30 August 2005 06:32, [EMAIL PROTECTED] wrote:
> Benjamin Franksen wrote:
> > On Thursday 25 August 2005 19:58, Udo Stenzel wrote:
> > > [...] you'll need a type signature somewhere to help ghc resolve
> > > the overloading of newArray and readArray, which is surprisingly
> > > tricky due to the "s" that must not escape.  This works:
> > >
> > > compute :: Int -> Int
> > > compute n = runST ( do
> > > arr <- newArray (-1, 1) n :: ST s (STArray s Int Int)
> > > readArray arr 1
> > >   )
> >
> > I am fighting with a similar problem. I want to use STUArray but
> > without committing to a fixed element type.
>
> That problem has been addressed in a message
>   http://www.haskell.org/pipermail/haskell-cafe/2004-July/006400.html
> which discussed several solutions. Given below is one of the
> solutions adjusted to fit the question of the original poster. His
> code is almost unchanged.

Gosh, it took me a while before I really understood /why/ your solution 
works, but now I think I got it.

The central idea is to use an intermediate data type that has the proper 
constraint on its element(s). Existential quantification is not 
strictly necessary: if we wrap runSTUArray instead of newArray_ we 
merely need a rank-2 type. This also strikes me as the more direct 
aproach and has the additional advantage that we don't have to use 
unsafeFreeze.

Below is the code of the modified solution. Note that there are no type 
signatures in the instances for class UArrayElement.

\begin{code}
{-# OPTIONS -fglasgow-exts #-}
import Data.Array.Unboxed
import Data.Array.ST
import Control.Monad.ST

copy :: (MArray a e m, IArray b e) =>
a Int e -> Int -> b Int e -> Int -> Int -> m ()
copy dest destix src srcix cnt
  | cnt <= 0  = return ()
  | otherwise = do
  writeArray dest destix (src ! srcix)
  copy dest (destix+1) src (srcix+1) (cnt-1)

append :: (IArray a e, UArrayElement e) =>
  a Int e -> a Int e -> Int -> UArray Int e
append x y low =
  case freezer of
Freezer f -> f (do
  z <-  newArray_ (low,low+len x+len y-1)
  copy z low x (first x) (len x)
  copy z (low+len x) y (first y) (len y)
  return z)
  where
len = rangeSize . bounds
first = fst . bounds

data Freezer i e = Freezer
  ((forall s. MArray (STUArray s) e (ST s) => ST s (STUArray s i e))
   -> UArray i e)

class UArrayElement e where
  freezer :: Ix i => Freezer i e

instance UArrayElement Bool where
  freezer = Freezer runSTUArray

instance UArrayElement Char where
  freezer = Freezer runSTUArray

-- ...
\end{code}

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


Re: [Haskell] ANNOUNCE: ghc-src version 0.2.0

2005-08-30 Thread Benjamin Franksen
On Tuesday 30 August 2005 13:04, Arthur Baars wrote:
> Daan is right, I wrote a parser for GHC using Doaitse Swierstra's
> parsing combinator library
> (http://www.cs.uu.nl/groups/ST/Software/UU_Parsing/index.html).

Very interesting. I tried to download it but I had no success. How 
exactly do I "checkout the whole uust tree"?

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


Re: [Haskell] How to use STArray?

2005-08-30 Thread Benjamin Franksen
On Tuesday 30 August 2005 06:32, [EMAIL PROTECTED] wrote:
> Benjamin Franksen wrote:
> > On Thursday 25 August 2005 19:58, Udo Stenzel wrote:
> > > [...] you'll need a type signature somewhere to help ghc resolve
> > > the overloading of newArray and readArray, which is surprisingly
> > > tricky due to the "s" that must not escape.  This works:
> > >
> > > compute :: Int -> Int
> > > compute n = runST ( do
> > > arr <- newArray (-1, 1) n :: ST s (STArray s Int Int)
> > > readArray arr 1
> > >   )
> >
> > I am fighting with a similar problem. I want to use STUArray but
> > without committing to a fixed element type.
>
> That problem has been addressed in a message
>   http://www.haskell.org/pipermail/haskell-cafe/2004-July/006400.html

Ups, I have missed this one. Next time I'll do a list search first.

> which discussed several solutions. Given below is one of the
> solutions adjusted to fit the question of the original poster. His
> code is almost unchanged.
>
> It would havebeen nice if the GHC library supported the second
> solution, a class Unpackable. Currently there are instances of
>   MArray (STUArray s) e (ST s)
> and
>   IArray UArray e
> for exactly the same set of types `e'. Alas, that condition is not
> stated formally, so we cannot infer that MArray (STUArray s) e (ST s)
> holds whenever IArray UArray e does.

Any chance that the standard libraries will be changed along these 
lines?

> > [snip complete solution]

I almost suspected that I have to introduce some existentially 
quantified data type, but had no idea where and how.

This would make a useful wiki page, BTW.

Thanks a lot for the help.

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


[Haskell] How to use STArray?

2005-08-29 Thread Benjamin Franksen
Hmmm, no answer on cafe, maybe someone here with a good idea?

--  Forwarded Message  --

On Thursday 25 August 2005 19:58, Udo Stenzel wrote:
> [...] you'll need a type signature somewhere to help ghc resolve
> the overloading of newArray and readArray, which is surprisingly
> tricky due to the "s" that must not escape.  This works:
>
> compute :: Int -> Int
> compute n = runST ( do
> arr <- newArray (-1, 1) n :: ST s (STArray s Int Int)
> readArray arr 1
>   )

Hello,

I am fighting with a similar problem. I want to use STUArray but
without committing to a fixed element type. For instance (this is not my 
real problem, but it's similar and easier to motivate), here is a
function that appends two UArrays:

A little helper first

> copy :: (MArray a e m, IArray b e) =>
> a Int e -> Int -> b Int e -> Int -> Int -> m ()
> copy dest destix src srcix cnt
>
>   | cnt <= 0  = return ()
>   | otherwise = do
>
>   writeArray dest destix (src ! srcix)
>   copy dest (destix+1) src (srcix+1) (cnt-1)

and here is the append function

> append :: UArray Int e -> UArray Int e -> Int -> UArray Int e
> append x y low = runSTUArray (do
> z <- newArray_ (low,low+len x+len y)
> copy z low x (first x) (len x)
> copy z (low+len x) y (first y) (len y)
> return z)
>   where
> len = rangeSize . bounds
> first = fst . bounds

Of course this can't work, because 'copy' needs the MArray and IArray
contexts:

No instance for (MArray (STUArray s) e (ST s))
  arising from use of `copy' at Problem.lhs:31:7-10
  [...]
No instance for (IArray UArray e)
  arising from use of `copy' at Problem.lhs:31:7-10
  [...]

But now, when I add

> append :: (IArray UArray e, MArray (STUArray s) e (ST s)) => ...

I still get the same error message regarding the MArray constraint:

No instance for (MArray (STUArray s) e (ST s))
  arising from use of `copy' at Problem.lhs:31:7-10

What am I missing? That is, how and where do I have to specify the 
constraint?

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


Re: [Haskell] Beyond ASCII only editors for Haskell

2005-05-24 Thread Benjamin Franksen
On Tuesday 24 May 2005 18:40, Marcin 'Qrczak' Kowalczyk wrote:
> Benjamin Franksen <[EMAIL PROTECTED]> writes:
> > Please forgive me for taking this as an opportunity to rant about
> > the single misfeature of Haskell's layout syntax, which is how
> > if/then/else must be layed out.
>
> For me it's worse that I can't write like this:
>
> foo x = do
>y <- foo x
>let z = some long line which must be
>   split into two
>return (y, z)

Yes, that one has bitten me quite often, too.

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


Re: [Haskell] Beyond ASCII only editors for Haskell

2005-05-24 Thread Benjamin Franksen
On Tuesday 24 May 2005 11:26, you wrote:
> Benjamin Franksen <[EMAIL PROTECTED]> writes:
> >> It seems to me that the layout conventions work pretty well. I do
> >> not see much code where it is not used, so generally people must
> >> like it.
>
> Works for me.  It helps *a lot* to have a sensible editor that knows
> where to position things of course. I use Emacs, but should probably
> upgrade the mode, as it doesn't place 'let' in do-blocks correctly.
>
> > Please forgive me for taking this as an opportunity to rant about
> > the single misfeature of Haskell's layout syntax, which is how
> > if/then/else must be layed out. The problem is that the 'else' must
> > be indented further than the 'if', so that this:
>
> You're talking about monads and do-notation here?  I have no problems
> with this in pure code.  

Hmm. You are right. This only gives a syntax error inside a 'do...' 
block. And now as I think about why this is the case, I can't see a 
good way to fix it, other than giving if/then/else-completion a higher 
precedence than layout. H.

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


Re: [Haskell] Beyond ASCII only editors for Haskell

2005-05-24 Thread Benjamin Franksen
On Monday 23 May 2005 22:48, Mads Lindstrøm wrote:
> It seems to me that the layout conventions work pretty well. I do not
> see much code where it is not used, so generally people must like it.

Please forgive me for taking this as an opportunity to rant about the 
single misfeature of Haskell's layout syntax, which is how if/then/else 
must be layed out. The problem is that the 'else' must be indented 
further than the 'if', so that this:

  if cond then
on_true
  else
on_false

usually gives me a syntax error.

Other than this, I like layout so much that I have never actually used 
the explicit {;}-notation.

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


Re: [Haskell] Re: ANNOUNCE: The jhc Haskell compiler.

2005-04-26 Thread Benjamin Franksen
On Tuesday 26 April 2005 11:15, Tony Finch wrote:
> On Tue, 26 Apr 2005, Ashley Yakeley wrote:
> > Does that mean my program will be GPL if I compile it with jhc?
>
> No; cf. gcc.

Fr details see http://www.gnu.org/licenses/gpl-faq.html#CanIUseGPLToolsForNF

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


Re: [Haskell] haddock -cpp ? Cabal support for haddock ?

2005-04-22 Thread Benjamin Franksen
On Friday 22 April 2005 17:09, Isaac Jones wrote:
> >> > I'd certainly welcome Cabal support for other haddock features as
> >> > well (--source, --read-interface).  I am not sure where to put all
> >> > these arguments in the .cabal file.
> >>
> >> Cabal doesn't support these yet, though.  Maybe in the future.
> >
> > Dear Isaac,
> >
> > for the next release, I think *every* external program used by Cabal
> > should get a xyz-options (free form) tag to give additional options. We
> > already have them for linker, c-compiler, and hs-compiler, but not yet
> > for preprocessors and doc generators (haddock). This is very easy to
> > implement, does no harm at all, and greatly increases cabal's
> > flexibility as a build tool. (BTW, I can send you a darcs patch if you
> > are too busy at the moment.)
>
> And in the other thread you said:
> >> > I made the necessary changes for hsc2hs-options in a few minutes
>
> You added hsc2hs-options to the package description?  Cool.  I'm happy
> to get a patch to add options fields to all the preprocessors and
> haddock and anything else we may have missed.

I'll give it a try.

> There are basically 3 ways that people can customize their packages:
> - the .cabal file
> - the Setup script with UserHooks
> - flags to configure
>
> I was originally thinking of these extra flags as something to pass to
> configure, but actually putting them in the description file would be
> more consistent with what we have already...

'Flags to configure' is -- at least in my case -- not the correct solution, 
because only the package author knows what extra options are necessary. The 
user shouldn't need to bother with it. I haven't looked very deeply into 
UserHooks yet, but I think passing extra options is common enough to justify 
dot-cabal tags.

> One trick, though, is to make sure that the parser test cases for
> cabal still run when you make the changes.  It's all too common for
> someone to add a field and break the parser or pretty printer.  The
> important thing is that when you parse it, pretty print it, and parse
> it again it comes out the same.   Check out tests/ModuleTest.hs

Ok, I will add test cases and make sure all tests pass before sending 
anything.

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


Re: [Haskell] haddock -cpp ? Cabal support for haddock ?

2005-04-22 Thread Benjamin Franksen
On Friday 22 April 2005 09:12, Isaac Jones wrote:
> Johannes Waldmann <[EMAIL PROTECTED]> writes:
> > What is the preferred way to generate haddockumentation
> > from code that must be preprocessed (ghc -cpp)?
> >
> > Would Cabal support this?
>
> Cabal does support this.  If you use the CPP extension, it'll
> preprocess the code before running haddock on it.
>
> > I'd certainly welcome Cabal support for other haddock features as
> > well (--source, --read-interface).  I am not sure where to put all
> > these arguments in the .cabal file.
>
> Cabal doesn't support these yet, though.  Maybe in the future.

Dear Isaac,

for the next release, I think *every* external program used by Cabal 
should get a xyz-options (free form) tag to give additional options. We 
already have them for linker, c-compiler, and hs-compiler, but not yet 
for preprocessors and doc generators (haddock). This is very easy to 
implement, does no harm at all, and greatly increases cabal's 
flexibility as a build tool. (BTW, I can send you a darcs patch if you 
are too busy at the moment.)

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


Re: [Haskell] cabal feature request

2005-04-22 Thread Benjamin Franksen
On Friday 22 April 2005 09:17, Isaac Jones wrote:
> Benjamin Franksen <[EMAIL PROTECTED]> writes:
> > I finally succeeded using cabal for a project that uses hsc2hs. My
> > problem was/is I need to give special options to hsc2hs, for
> > instance a different template header file to use. Cabal doesn't
> > support this at the moment.
> >
> > I propose to give the user a bit more flexibility with regard to
> > preprocessors, i.e. add some more tags to the .cabal file, like
> >
> > hsc2hs-options, cpp-options, ...
> >
> > I made the necessary changes for hsc2hs-options in a few minutes
>
> Did you alter the Cabal library itself?  

Yes.

> If so, then that won't work 
> when you go to distribute it to others, since they won't have your
> altered cabal.

Yes, that's why I suggested to add such tags to the official version.

> You could do this in the UserHooks, by over-riding the hsc2hs
> preprocessor in your Setup.lhs file.  If you grab the cabal source, 
> there's an example in the tests directory called withHooks that might
> help.  That, and looking at the cabal source itself :)
>
> > Another question: Is there a proposal how to (better) support test
> > executables for a library package? (I remember that this topic has
> > been discussed but can't remember any conclusion).
>
> With the latest (darcs / cvs) version of Cabal, you can add a
> UserHook for running tests, then there's a target ./setup test
> that'll execute that hook.

Ok, I will try to find out how to use user hooks for what I need.

> We put the hook in Cabal 1.0, but forgot to add the command, so
> nothing calls it.  Feel free to add the test hook so that people
> using newer versions of cabal can run your tests :)

Yup. (Not that the stuff is ready for distribution.)

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


[Haskell] cabal feature request

2005-04-21 Thread Benjamin Franksen
I finally succeeded using cabal for a project that uses hsc2hs. My problem 
was/is I need to give special options to hsc2hs, for instance a different 
template header file to use. Cabal doesn't support this at the moment.

I propose to give the user a bit more flexibility with regard to 
preprocessors, i.e. add some more tags to the .cabal file, like

hsc2hs-options, cpp-options, ...

I made the necessary changes for hsc2hs-options in a few minutes (thanks to 
the nicely structured cabal libraries :).

Another question: Is there a proposal how to (better) support test executables 
for a library package? (I remember that this topic has been discussed but 
can't remember any conclusion).

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


Re: [Haskell] announce: wxhaskell 0.9

2005-03-16 Thread Benjamin Franksen
On Wednesday 16 March 2005 12:14, Georg Martius wrote:
> Hi Ben,
>
> Sorry for the confusing discussion. As Daan said the dependency stuff
> was not that trivial to get. However, please find my patches for 0.8
> and 0.9 attached. To apply the patches please enter the wxHaskell-0.X
> source directory and run
>
>   > patch configure < configure_0.X_ghc6.4.diff
>   > patch makefile < makefile_0.X_ghc6.4.diff
>   > patch makefile.lib < makefile.lib_0.X_ghc6.4.diff

Thanks a lot!

I'll try your patches. My current workaround is/was to disable 
dependency generation, but this is of course not a sustainable 
solution. BTW, I also had to write package description files in the new 
format. Which ones do you use?

Some of the examples under directory 'contrib' are broken in version 
0.9. I needed to make a number of (superficial) changes to get them to 
compile and run. Interestingly, and this is something I often observed 
with Haskell, as soon as I got it to compile, everything worked as 
expected. The changes where easy to make, using the haddock generated 
docs. WxHaskell is cool!

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


Re: [Haskell] announce: wxhaskell 0.9

2005-03-13 Thread Benjamin Franksen
On Sunday 13 March 2005 22:59, Benjamin Franksen wrote:
> On Friday 25 February 2005 19:14, Daan Leijen wrote:
> > Announcement: wxHaskell version 0.9
>
> Could you (or anyone else) please give me a summary on how exactly I have
> to patch the makefile[.lib] so that I can compile this 

_with_

> ghc-6.4? [...]

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


Re: [Haskell] announce: wxhaskell 0.9

2005-03-13 Thread Benjamin Franksen
On Friday 25 February 2005 19:14, Daan Leijen wrote:
> Announcement: wxHaskell version 0.9

Could you (or anyone else) please give me a summary on how exactly I have to 
patch the makefile[.lib] so that I can compile this ghc-6.4? I found the 
discussion a bit confusing, because there were so many different issues...

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


Re: [Haskell] Hierarchical module namespace extension not sufficiently flexible

2005-03-06 Thread Benjamin Franksen
On Sunday 06 March 2005 13:23, Duncan Coutts wrote:
> On Sun, 2005-03-06 at 01:29 +0100, Benjamin Franksen wrote:
> > On Saturday 05 March 2005 20:06, Duncan Coutts wrote:
> > > It does mean that as I library author I'm sort of forcing you to use
> > > qualified names when perhaps you did not want to. But for some
> > > libraries you really can't sensibly use them with a flat name space.
> > > There are dozen different things in Gtk+ that have a 'value' property.
> >
> > I'd be interested to know why you don't use classes for that.
>
> Because they don't share an interface or some common semantics. They
> just happen to use the same name.
>
> I don't think it's good design to use classes just because you want
> ad-hoc overloading.
>
> (We do use Haskell classes to model Gtk+ classes)
>
> Indeed this isn't even overloading really, the Gtk+ system we are
> wrapping uses a hierarchical module namespace itself (albeit in C
> following the naming convention namespace_class_method). We are just
> trying to model this in Haskell with Haskell modules. Every other
> language binding for Gtk+ does this: C++, Java, Perl, Python, Ruby,
> OCaml etc.
>
> We can do it too except that to use qualified names, users would have to
> import dozens of modules:
> import Graphics.UI.Gtk.This
> import Graphics.UI.Gtk.That
> import Graphics.UI.Gtk.TheOther.
>
> So at the moment we prefix the module name to everything in the module,
> "buttonLabel" so we can export everything through Graphics.UI.Gtk
> whereas we (and the designers of the hierarchical module namespace
> extension) would prefer people to be able to use "Button.label".

Ok, thanks for the detailed answer.

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


Re: [Haskell] Hierarchical module namespace extension not sufficiently flexible

2005-03-05 Thread Benjamin Franksen
On Saturday 05 March 2005 20:06, Duncan Coutts wrote:
> It does mean that as I library author I'm sort of forcing you to use
> qualified names when perhaps you did not want to. But for some libraies
> you really can't sensibly use them with a flat name space. There are
> dozen different things in Gtk+ that have a 'value' property.

I'd be interested to know why you don't use classes for that.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-03-04 Thread Benjamin Franksen
On Friday 04 March 2005 23:44, Keean Schupke wrote:
> Benjamin Franksen wrote:
> >Consider:
> >
> > class Bogus a b
> > instance Bogus Int Char
> >
> >How do you express the /instance/ in TH? Using AppT?
>
> That would be:
>
> (using 6.4 syntax)
>
> AppT (AppT (ConT (mkName "Bogus")) (ConT ''Int)) (ConT ''Char)
>
> If the instance is using type variables:
>
> instance Bogus Int a
>
> you get:
>
> AppT (AppT (ConT (mkName "Bogus")) (ConT ''Int)) (VarT (mkName "a"))

OK, I can see now that this makes sense syntactically. Still, it is strange 
that the class name is handled as if it were a type constructor.

Anyway, thanks.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-03-04 Thread Benjamin Franksen
On Friday 04 March 2005 16:32, Keean Schupke wrote:
> robert dockins wrote:
> > Is that really how this is done?  That doesn't seem like it can be right:
> >
> > instance X (a b)  -- single parameter class where 'a' has an arrow kind
> >
> > is very different from:
> >
> > instance X a b-- multiple parameter class
> >
> > I would expect a type constructed with 'appT' to correspond to the
> > first declaration, and not to the second.
>
> Yup, thats how it is done, I have some complex working TH that generates
> multi parameter classes with fundeps
> instances etc... and I can say for definite it all works fine:
>
> For the above examples
>
> appT X (appT a b) -- X is applied once (to a applied to b)
>
> appT (appT X a) b -- X is applied twice first to a then to b

But this has nothing to do with the instance question. I agree with Robert 
that

AppT a b

definitely sounds like type constructor application. How can this help with 
multi parameter class instances? Consider:

class Bogus a b
instance Bogus Int Char

How do you express the /instance/ in TH? Using AppT? AppT would make sense for

instance Show a => Show [a] where ...

where one would express the '[a]' in TH as

AppT ListT (VarT mkName "a")

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-03-04 Thread Benjamin Franksen
On Sunday 20 February 2005 14:19, Keean Schupke wrote:
> TH has supported multi-parameter classes for a while... new in 6.4 is
> support for fundeps.

Yes, but unfortunately TH cannot create instances for them which is usually 
the boilerplate you want to avoid. From Language.Haskell.TH:

data Dec =
...
ClassD Cxt Name [Name] [FunDep] [Dec]
InstanceD Cxt Type [Dec]
...

Only one 'Type' can be given for an instance.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-03-02 Thread Benjamin Franksen
On Thursday 24 February 2005 23:27, Keean Schupke wrote:
> Benjamin Franksen wrote:
> > Automatic wrapping is easy. What is not so easy and I think not even
> > possible, is automatic _un_wrapping, so that the wrapping isn't exposed
> > at all to the programmer.
>
> One way to do this is to replace the type with a pair:
>
> data Wrap a = Wrap {unwrapA :: a}
>
> wrap a = (unwrapA,Wrap a)
>
> so to unwrap do:
>
> unwrap a = (fst a) (snd a)

This is extremely cool. The type of unwrap is indeed general enough. 
Unfortunately, it doesn't help, because the result type of wrap

Wrap (forall a. a -> a)

still isn't accepted in an instance declaration. Neither is the pair

(unwrap, Wrap (forall a. a -> a))

Or maybe I have not quite understood what you proposed to do with these 
definitions.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-03-02 Thread Benjamin Franksen
On Wednesday 02 March 2005 19:51, Keean Schupke wrote:
> Infact there is a tradeoff. Records with faster read times (ie offset
> tables) have slower write times as the table needs to be copied and
> expanded. 

Which is of course the reason why extension for records is not a very common 
language feature. BTW, records in C don't even have offset tables, instead 
the offsets get directly compiled into the machine code.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-28 Thread Benjamin Franksen
On Thursday 24 February 2005 23:27, Keean Schupke wrote:
> Benjamin Franksen wrote:
> >>Well at the moment this would give an error, but remember the
> >>list is heterogeneous, so you can just not give the list a type, and
> >>simply append the specific function... admitedly this is not as
> >>type-safe.
> >>
> >>hUpdateAtLabel field2 someFunction myRecord
> >
> >That is an advantage of hLists as compared to normal records.
> >
> >A disadvantage is that each field access needs to traverse the list. I
> > wonder if this isn't rather less efficient than the random access
> > provided by normal records.
>
> Well, not quite true, because the type of the label is used to index the
> value, the selection happens at compile time. So at run time there is no
> instance selection left... it is simply the value. At least in theory!
> whether
> the particular compiler/interpreter does this is implementation dependant.
> This is why we decided that the simpler to implement list was better than
> a more complex tree structure.

Hmm. I haven't seen it from this perspective, yet! At first reading, I thought 
this is simply too good to be true. I mean, there is some sort of list 
structured thing representing the whole record, right? Then how can the 
function that selects an element *not* traverse through the list?

After thinking for some time about this, my head begins to spin badly! I tend 
to believe now, that it could indeed be possible that the compiler performs 
the traversal at compile time, but the thought still gives me headaches.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-24 Thread Benjamin Franksen
On Thursday 24 February 2005 19:51, Keean Schupke wrote:
> Benjamin Franksen wrote:
> >I still wonder if your TH generated code can handle higher ranked field
> > types; i.e. can I write
> >
> >$(ttypelift [| data Record = Record {
> >field1 :: Int,
> >field2 :: (forall a. a-> a) } |] )
> >
> >or does ghc give me an error?
>
> Well at the moment this would give an error, but remember the
> list is heterogeneous, so you can just not give the list a type, and
> simply append the specific function... admitedly this is not as
> type-safe.
>
> hUpdateAtLabel field2 someFunction myRecord

That is an advantage of hLists as compared to normal records.

A disadvantage is that each field access needs to traverse the list. I wonder 
if this isn't rather less efficient than the random access provided by normal 
records.

> Of course if the type of the function is unknown until runtime, we have
> to use existential quantification.
>
> It might be possible to automatically wrap such types, but my feeling at
> the moment is that it is best left to the programmer.

Automatic wrapping is easy. What is not so easy and I think not even possible, 
is automatic _un_wrapping, so that the wrapping isn't exposed at all to the 
programmer.

I am not a type system guru, so can anyone enlighten me on why higher ranked 
types are not allowed in instances? Is there a principle problem, or is it 
just difficult to implement? Does this have to do with this "higher order 
unification" that Haskell is alleged not to have?

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-24 Thread Benjamin Franksen
On Thursday 24 February 2005 15:01, Keean Schupke wrote:
> Having looked at the translation on page 10 of Daan's paper, I can see
> no advantage in this
> encoding, nor does it look like it supports higher ranked types in any
> way... (Infact it has the
> disadvantage of requiring a class per record, whereas the records in the
> HList paper require
> only a class per function).
>
> class Name r a | r -> a where
> get_name :: r -> a
> set_name :: r -> a -> r
>
> Perhaps you can explain how this does support higher ranked fields?

Sorry, I jumped to conclusions a bit too fast. I thought one could get rid of 
the newtype unwrapper if one "applied it away". But this is nonsense because 
one still has the class constraint involving the newtype. It just doesn't 
work.

I still wonder if your TH generated code can handle higher ranked field types; 
i.e. can I write

$(ttypelift [| data Record = Record {
field1 :: Int,
field2 :: (forall a. a-> a) } |] )

or does ghc give me an error?

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-24 Thread Benjamin Franksen
On Thursday 24 February 2005 11:56, Keean Schupke wrote:
> Benjamin Franksen wrote:
> >You mentioned that higher-ranked types are not allowed in instance
> >declarations and that this limits the usefulness of your
> > translation. This is unfortunate and applies to my translation too.
> > From what I read elsewhere, I guess the standard workaround is to
> > wrap such types in a newtype. The problem is that this newtype
> > wrapping and unwrapping cannot be made transparent (at least I
> > don't see a way to do this).
> >
> >Keean, how do you solve this problem in your TH code?
>
> Can you think of an example where a higher ranked label would be
> useful? Lookups are normally done with values.

Dear Keean,

you should read more carefully what people write. Nowhere have I stated 
that I want higher-ranked *labels*. In fact, in my translation labels 
always have the value bottom.

My concern is with higher-ranked record fields. Stupid example:

 data R = R {
  f :: (forall a. a -> a)
 }

My translation doesn't work in this case, because the compiler doesn't 
accept

 instance RecordField R Label_f (forall a. a->a) where
  ...

> Here's an example of a higher ranked type used as a non-label which
> works fine:
>
> -
>--- --{-# OPTIONS -fglasgow-exts #-}
>
> module Main where
>
> class Test a b | a -> b where
> test :: a -> b -> Bool
>
> newtype I = I (forall a . Integral a => a)
> newtype S = S (forall a . Show a => a)
>
> instance Test Int I where
> test _ _ = True
>
> instance Test String S where
> test _ _ = False
>
> main = do
> putStrLn $ show $ test (1::Int) (I undefined)
> putStrLn $ show $ test ("a"::String) (S undefined)
>
> -
>---
>
> Which shows that even though you cannot use higher ranked types as
> labels, you can use them in other fields... Effectively they cannot
> be on the LHS of a functional dependancy (for obvious reasons if you
> think about it).

Yes, you can wrap higher-ranked types into a newtype and then you can 
define instances for them.

Again, that is what I already wrote in my previous message. With the 
above stupid example:

 newtype Wrap_f = Wrap_f (forall a. a->a)

 unWrap_f (Wrap_f x) = x

However, the result of 

 getField Label_f

now has type Wrap_f and not (forall a. a->a). To really get the field, I 
have to unwrap the newtype constructor manually:

 get_f :: R -> (forall a. a->a)
 get_f = unWrap_f . getField Label_f

This means that a translation as proposed by Daan (i.e. without 
first-class labels) is feasible even with higher-ranked field types, 
but not my version.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-23 Thread Benjamin Franksen
On Sunday 20 February 2005 10:16, Daan Leijen wrote:
> Benjamin Franksen wrote:
> > This library class defines the operations on a record:
> >
> > class RecordField r l t | r l -> t where
> >   getField :: l -> r -> t
> >   putField :: l -> t -> r -> r
>
> I have once written a short note about how Haskell'98 records could
> be made more useful using a conservative extensions. The suggested
> implementation method corresponds quite closely to what you sketch
> here. Here is the url:
>
> <http://www.cs.uu.nl/~daan/download/papers/records.pdf>
>
> It should be interesting to read about the different tradeoffs of
> extending the current record system, but keep in mind that this is a
> just a quick writeup of ideas (and written two years ago!)

Yes, quite interesting, indeed.

"My" sketch (I don't claim any originality) differs from yours mostly in that 
mine has one additional argument, namely the label type, which results in 
labels becoming first class values. I really like first class record labels!

You mentioned that higher-ranked types are not allowed in instance 
declarations and that this limits the usefulness of your translation. This is 
unfortunate and applies to my translation too. From what I read elsewhere, I 
guess the standard workaround is to wrap such types in a newtype. The problem 
is that this newtype wrapping and unwrapping cannot be made transparent (at 
least I don't see a way to do this).

Keean, how do you solve this problem in your TH code?

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-23 Thread Benjamin Franksen
On Sunday 20 February 2005 14:19, Keean Schupke wrote:
> TH has supported multi-parameter classes for a while... new in 6.4 is
> support for fundeps.

That's mighty cool ;) Is this (TH in general, extensions in particular) 
documented somewhere?

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-19 Thread Benjamin Franksen
Two clarifications:

On Saturday 19 February 2005 22:33, Benjamin Franksen wrote:
>   instance RecordField R Label_field1 T1 where
> getField (Rec x _) _ = x
> putField (Rec _ y) _ v = Rec v x

s/Rec/R/

> I wonder if something similar could be done with TH. The labels would need
> to have a different name (e.g. l_field1, l_field2), so they don't collide
> with their Haskell98 definitions, but otherwise everything should be as
> above.

What I mean is: keep the record syntax and everything as it is now, but 
additionally use TH in order derive the corresponding first class labels as 
indicated above. The question is if a function 'generateLabels' can be 
defined with TH. I remember darkly that TH is (or once was) restricted to 
Haskell98, and so cannot be used to generate multi parameter class instances.

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


Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-02-19 Thread Benjamin Franksen
I think that the best solution is to define record labels as types, or rather 
type proxies, like for instance in the HList library. This fixes the most 
important deficiencies of Haskell98 records:

- labels are now first class values
- labels no longer need to be globally unique, but only unique per record
- operations to get or set a field are normal (overloaded) functions (and
  can be given operator aliases, if desired)

This library class defines the operations on a record:

class RecordField r l t | r l -> t where
  getField :: l -> r -> t
  putField :: l -> t -> r -> r

updateField :: (Field r l t) => l -> (t -> t) -> r -> r
updateField lbl fun rec = putField lbl (fun $ getField lbl rec) rec

The record declaration

data R = R {
field1 :: T1,
field2 :: T2
  }

would be syntactic sugar for

data R = R T1 T2

data Label_field1

field1 :: Label_field1
field1 = undefined

instance RecordField R Label_field1 T1 where
  getField (Rec x _) _ = x
  putField (Rec _ y) _ v = Rec v x

-- analogous definitions for field2 left out

Note that the compiler would leave out the definition of Label_field1 and 
field1 if these are already in scope.

Alexanders example

> fun rec = rec // $(u field1 fn) . $(a field2 val)

resp.

> fun rec = rec // u_field1 fn . a_field2 val

could now be written thus

fun = updateField field1 fn . putField field2 val

without any need for additional syntax or infix operator splices.

I wonder if something similar could be done with TH. The labels would need to 
have a different name (e.g. l_field1, l_field2), so they don't collide with 
their Haskell98 definitions, but otherwise everything should be as above. I 
am thinking of something like

$(generateLabels R)

(I am not very familiar with TH, so this could be wrong syntax or otherwise 
impossible to do.)

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


Re: [Haskell] Typing in haskell and mathematics

2005-02-01 Thread Benjamin Franksen
On Tuesday 01 February 2005 02:41, Jeremy Gibbons wrote:
> <[EMAIL PROTECTED]> wrote:
> > BTW, 'sigma sin' is not a function.
>
> I'm missing something here. I don't have an integral symbol to hand,
> which is what I meant by the "sigma", 

I understood it that way. But let us use '\int' or '\integral' so we 
won't get confusion with the symbol for discrete sums (although the 
latter are only a special variant of general integration).

> so perhaps I was unclear. I'd 
> say the integral of the sine function is itself a binary function,
> taking lower and upper bounds as arguments.

If you interpret it this way, you are right, of course. The problem is 
that such an interpretation is bound to functions on real numbers and 
even there it cannot be easily generalized. In Integration Theory, you 
usually integrate over an arbitrary measureable set, not only 
intervals. In general, such sets may not even be representable as a 
subset of \R^n (= finite-dimensional euclidian space). They need not 
even have a topology.

Thus, in most of the more abstract mathematical fields, 'integral f' 
means the value of the integral over the whole domain (if it exists & 
is finite). Integration over a subset is indicated by a subscript 
denoting the subset.

Ok, if you want to nitpick, you could say then that '\integral f' is a 
function from the set of measureable subsets of the domain of f to the 
codomain of f.

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


Re: [Haskell] Typing in haskell and mathematics

2005-01-31 Thread Benjamin Franksen
On Monday 31 January 2005 04:24, Jeremy Gibbons wrote:
> Despite being a fan of generic programming, I have my doubts about
> this kind of automatic lifting. It works fine in "ordinary
> mathematics", because there is no fear of confusion - one hardly ever
> deals with functions as entities in their own right. 

May I please beg to differ? When I studied math, things were quite 
different, at least. I remember whole branches of mathematics 
completely dedicated to dealing with "functions as entities in their 
own right". One notable example is Functional Analysis, of which I 
happen to know a little. And, as far as I remember, we used notation 
which reflected this, i.e. nobody wrote 'f(x)' when actually they meant 
just 'f', which is the same as '\x -> f x', which in math is usually 
written 'x |-> f(x)'.

> (Witness "sigma 
> sin(x) dx", involving a term sin(x) and a dummy variable x, rather
> than the more logical "sigma sin", involving the function.)

The notations for 'integral' and 'differential quotient' stem from a 
time when dealing with functions as entities in their own right was 
indeed not yet a common concept in mathematics, i.e. earlier than 1900.

BTW, 'sigma sin' is not a function.

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


Re: [Haskell] Newbie : How come that cyclic recursive lists are efficient ?

2005-01-24 Thread Benjamin Franksen
On Monday 24 January 2005 21:47, Francis Girard wrote:
> But I can't help thinking that the distinction between "being" a list of
> integers and "being" a function that "returns" a list of integers (without
> arguments) is not always clear in FP ... since there is not really such a
> thing as returning a value in declarative programming, neither in
> mathematical thinking.

There *is no* difference between the two if one views them as pure 
mathematical values. Questions of run time speed or memory usage, i.e. 
efficiency (which your original question was about) are clearly outside the 
realm of pure values, and thus we may perceive them as distinct in this wider 
setting.

My favourite analogy for this is the old joke about a topologist being a 
person who cannot see any difference between a cup and a doghnut.

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


Re: [Haskell] Better Exception Handling

2004-11-24 Thread Benjamin Franksen
Gosh, I shouldn't post to mailing lists after midnight. Please excuse my 
needless explanations. I didn't understand your answer at first.

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


Re: [Haskell] Real life examples

2004-11-24 Thread Benjamin Franksen
On Thursday 25 November 2004 00:38, Ben Rudiak-Gould wrote:
> John Meacham wrote:
>  >With my mdo proposal, and I think all proposals brought forth, the
>  >module system behaves identically to how it normally does for
>  >namespace control. [...] modules do not change code at all, they
>  >are pure syntantic sugar for deciding what names you can see.
>
> I'm not sure I understand your mdo proposal correctly then. A lot of
> this debate has been over what should happen when a module has a
> top-level action like
>
> x <- putStrLn "hello"
>
> Everyone agrees that "hello" should be printed at most once, [...]

And I thought at least everyone agreed that things like that should not be 
allowed. Instead, only a "safe" subset of things that are currently in IO 
should be allowed to appear at the top-level, such as creation of mutable 
reference cells.

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


Re: [Haskell] Better Exception Handling

2004-11-24 Thread Benjamin Franksen
On Thursday 25 November 2004 00:29, Scott Turner wrote:
> John Goerzen wrote:
> > I note, though, that "making an Either into a Monad" doesn't do
> > anything to deal with asynchronous exceptions.
>
> [ snip]
>
> > I was referring to exceptions generated by things such as signals,
> > interrupts, certain network errors, stack problems, etc.
>
> How would you like asynchronous exceptions to fit in?  Your original
> request mentioned that it was annoying to have to use the IO monad for all
> exceptions, particularly when the exceptions occur in deterministic code.
> But the IO monad is plainly appropriate for asynchronous exceptions.

I think the explanation was a bit misleading. Asynchronous exceptions are 
exceptions that can occur *anywhere*, even in purely functional code and even 
if the code itself is completely free of bottoms. A good example is 'heap 
overflow', i.e. insufficient memory even after the GC was run. Another 
example are interrupts and unix signals: they can occur at any time, 
regardless of what the program is doing. More generally, whenever you can 
send a message to a thread that isn't expecting one. Control.Exception 
defines 'throwTo' that gets a threadId as argument. This causes the target 
thread to be interrupted with an asynchronous exception.

Asynchronous exceptions are a rather recent addition to ghc. How they relates 
to your (very interesting) EitherMonad solution is not completely clear to 
me, either.

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


Re: [Haskell] Re: Top Level TWI's again was Re: Re: Parameterized Show

2004-11-23 Thread Benjamin Franksen
On Tuesday 23 November 2004 00:10, Aaron Denney wrote:
> On 2004-11-22, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> > On Monday 22 November 2004 09:38, Adrian Hey wrote:
> >> You have yet to
> >> explain how you propose to deal with stdout etc..
> >
> > I see absolutely no reason why stdxxx must or should be top-level mutable
> > objects. They can and should be treated in the same way as environment
> > and command line arguments, i.e.
> >
> > getArgs :: IO [String]
> > getEnv :: String -> IO String
> > getStdin, getStdout, getStderr :: IO Handle
> >
> > Note that (just like environment and command line arguments) these
> > handles may refer to completely different things on different program
> > runs.
>
> Er, no.  The handles can be considered as the same but _pointing_ to
> different things on different runs.

I wrote "may refer to", not "are", so yes.

> Keeping them outside the IO monad, 
> and only accessing them inside -- i.e. the current situation -- would be
> fine.

I beg to differ. Note, I do not claim they are unsafe.

> They're not mutable in any sense.

Well, a variable in C is not mutable in exactly the same sense: It always 
refers (="points") to the same piece of memory, whatever value was written to 
it. Where does that lead us?

Ben
-- 
Top level things with identity are evil.-- Lennart Augustsson
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-23 Thread Benjamin Franksen
On Tuesday 23 November 2004 09:10, Adrian Hey wrote:
> On Monday 22 Nov 2004 6:27 pm, Lennart Augustsson wrote:
> > Personally, I can't believe I hear people arguing for global variables.
>
> Oh dear, here we go again. I repeat, AFAIK nobody who wants a solution to
> this problem is advocating the use of "global variables"

I don't understand the difference between a "global variable"

(C code, outside main): int var = 0;

and a "top-level thing with identity"

(proposed Haskell code, outside main): var <- newIORef 0

AFAIK, "global" in C (or any other imperative language) means the same as 
"top-level" in Haskell.

Ben
-- 
Ceterum censeo: Global variabes are evil.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-23 Thread Benjamin Franksen
On Tuesday 23 November 2004 10:39, Keean Schupke wrote:
> Adrian Hey wrote:
> >This is one situation, but certainly not the only possible one. You have
> >the same problem with interfacing to any unique stateful resource (or
> >even if you have a multiple but finite supply of these resources).
>
> No you don't... Most devices have registers, those registers contain
> values, you can inspect those values to see if the device has been
> initialised. You can then write a guard on the initialisation that really
> checks if the device has (or hasn't) been initialised rather than rely
> on some
> 'shadow' copies in RAM.

Alas, unfortunately not every device is designed in this way (I can give 
examples if you want). Adrian is right in that there is not only badly 
designed C libraries but also badly designed hardware!

Ben
-- 
Top level things with identity are evil.-- Lennart Augustsson
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-22 Thread Benjamin Franksen
On Monday 22 November 2004 09:38, Adrian Hey wrote:
> On Friday 19 Nov 2004 2:27 pm, Benjamin Franksen wrote:
> > But toplevel
> > things with identity (TWI) are evil as well, *especially* if they are
> > easy to use.
>
> Just repeating this again and again doesn't make it any more true. Neither
> you or any of the other nay-sayers have provided any evidence or credible
> justification for this assertion, nor have any of you provided any workable
> alternative for even the simplest example. 

This is getting ridiculous. At least two workable alternatives have been 
presented:

- C wrapper (especially if your library is doing FFI anyway)
- OS named semaphores

Further, as for "evidence or credible justification" for the my claim, you can 
gather it from the numerous real-life examples I gave, and which you chose to 
ignore or at least found not worthy of any comment. Of course, these examples 
are only annecdotal, but I think this is better than a completely artificial 
requirement (like your "oneShot").

You have been asked more than once to present a *real-life* example to 
illustrate that

(a) global variables are necessary (and not just convenient),
(b) both above mentioned alternatives are indeed unworkable.

> You have yet to 
> explain how you propose to deal with stdout etc..

I see absolutely no reason why stdxxx must or should be top-level mutable 
objects. They can and should be treated in the same way as environment and 
command line arguments, i.e.

getArgs :: IO [String]
getEnv :: String -> IO String
getStdin, getStdout, getStderr :: IO Handle

Note that (just like environment and command line arguments) these handles may 
refer to completely different things on different program runs.

Ben
-- 
Top level things with identity are evil.-- Lennart Augustsson
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: Parameterized Show

2004-11-19 Thread Benjamin Franksen
On Friday 19 November 2004 08:54, Adrian Hey wrote:
> On Tuesday 16 Nov 2004 1:52 pm, Ben Rudiak-Gould wrote:
> > George Russell wrote:
> >  > Sorry, but I like implicit parameters, I use them, and I'm not
> >  > going to stop using them because beta conversion no longer
> >  > preserves semantics.
> >
> > You'll find that many people here don't agree with this view in
> > general (though there's been surprisingly little backlash against
> > implicit parameters in particular).
>
> I would like to lash against them. I was unaware of the problems you
> describe, but their existence doesn't surprise me. In view of the
> controversy that a certain other perfectly safe, reasonable (and
> necessary) language extension proposal has generated recently the
> ready acceptance of this kind of brokeness is surprising. Frankly,
> the idea that anyone would want to jump through hoops to add them to
> a purely functional language sounds bizarre to me. Safe beta
> conversion really ought to be a sacred cow.
>
> Still, at least they're not enabled by default. With any luck we
> won't see too many people shooting themselves in the foot because
> they're too lazy to pass their parameters explicitly.

Implicit parameters are evil, agreed. Their deficiencies should be added 
as a warning to the docs (with many exclamation marks). But toplevel 
things with identity (TWI) are evil as well, *especially* if they are 
easy to use. Implicit parameters at least have the advantage that they 
are obscure and  require changes to function signatures, so that 
(hopefully) not many people use them.

The toplevel '<-' bindings proposal encourages bad library and program 
design by making TWIs easy and (apparently) safe. It is better to make 
people think hard about how to avoid them in the first place. (BTW, 
toplevel stdin, stdout, and stderr are evil too.)

I know of exactly one good reason to use TWIs in Haskell. Which is: to 
interface C libraries that are broken because of the fact that TWIs are 
so easy to create in C.

Introducing TWIs in Haskell is like deliberately spreading a disease 
into an area that has avoided it up to now by strict quarantine 
measures. Of course these measures are often inconvenient and some 
effort is required in order to make communication with the ill populace 
possible. And of course every now and then people come along 
complaining that everything would be easier if one would just remove 
all those decontamination barriers...

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


Re: [Haskell] Re: Using implicit parameter constraints in data decl

2004-11-08 Thread Benjamin Franksen
On Sunday 07 November 2004 19:36, Benjamin Franksen wrote:
>
> data (?val::Bool) => Test = Test { name :: String }
>
> is rejected by the compiler
> [...]
> which is unfortunate since it means that you cannot put a function that
> depends on an implicit parameter into a data structure. There are probably
> technical reasons for this restriction, but it means that such functions
> are no longer first class objects.

Here is an executive summary lest anyone gets false ideas:

Functions with implicit parameters *are* first class values but only if you 
use -fglasgow-exts and not only -fimplicit-params. The version above is 
rejected nonetheless (for whatever reason I can't figure out at the moment) 
but

data Test = Test { name :: (?val::Bool) => String }

works. The compiler flag is needed because in Haskel98 contexts may not appear 
after the 'data' (i.e. the way I tried it at first) and -fglasgow-exts lifts 
this restriction. I haven't found this explicitly mentioned in the ghc docs, 
but that doesn't mean it's not there somewhere.

References:
http://www.haskell.org/onlinelibrary/decls.html

Thanks to Ben Rudiak-Gould who helped me to resolve this.

Cheers,
Ben
-- 
Top level things with identity are evil.-- Lennart Augustsson
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: Using implicit parameter constraints in data decl

2004-11-08 Thread Benjamin Franksen
On Sunday 07 November 2004 23:19, Ben Rudiak-Gould wrote:
> Benjamin Franksen wrote:
>  >data (?val::Bool) => Test = Test { name :: String }
>  >
>  >is rejected by the compiler:
>  >
>  >TestBug.hs:3:
>  >Illegal constraint ?val :: Bool
>  >In the context: (?val :: Bool)
>  >While checking the context of the data type declaration for `Test'
>  >In the data type declaration for `Test'
>  >
>  >which is unfortunate since it means that you cannot put a function that
>  >depends on an implicit parameter into a data structure.
>
> Does this do what you want?:
>
> data Test = Test { name :: (?val::Bool) => String }

Thanks for the hint, but no:

TestBug.hs:4:
Illegal constraint ?val :: Bool
In the type: ({?val :: Bool} => String) -> Test
While checking the type of constructor `Test'
In the data type declaration for `Test'

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


[Haskell] Re: Using implicit parameter constraints in data decl

2004-11-07 Thread Benjamin Franksen
On Sunday 07 November 2004 20:09, Simon Peyton-Jones wrote:
| Definitely a bug.  Could you pls make a small module that elicits the
| bug, and send it to me?

Here it is:

> module Test where
> 
> data Test = (?val::Bool) => Test { name :: String }
> 
> instance Show Test where
> show p = name p

[EMAIL PROTECTED]: .../src/testbug > ghc -fimplicit-params TestBug.hs
ghc-6.2.2: panic! (the `impossible' happened, GHC version 6.2.2):
simplCore/Simplify.lhs:1473: Non-exhaustive patterns in function 
cat_evals

BTW, I see now that the data declaration is syntactically wrong. Anyway, the 
(syntactically) correct version

data (?val::Bool) => Test = Test { name :: String }

is rejected by the compiler:

TestBug.hs:3:
Illegal constraint ?val :: Bool
In the context: (?val :: Bool)
While checking the context of the data type declaration for `Test'
In the data type declaration for `Test'

which is unfortunate since it means that you cannot put a function that 
depends on an implicit parameter into a data structure. There are probably 
technical reasons for this restriction, but it means that such functions are 
no longer first class objects.

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Benjamin Franksen
On Sunday 07 November 2004 16:18, you wrote:
> Adrian Hey wrote:
> >I'm not at all convinced, having not seen or groked either the "before" or
> >"after" code. Perhaps you could show how this would work with an even
> > simpler example, the one that I posted concerning the use of oneShot to
> > create a top level (I.E. exportable) userInit.
> >
> >AFAICS the only alternative to..
> >
> > userInit <- oneShot realInit
> >
> >is to export realInit, have users create their own userInit, and then pass
> >that around as an argument to everything that might make use of userInit.
>
> The way I would do it would be to have an init function that
> initialises an abstract data structure. Because the results of
> the init function are stateless and not in a global variable it
> does not matter if the user calls it twice.

Yes, whenever possible I would use this approach. Unfortunately, there are
libraries (or just modules) that need to do some IO action in order to
produce the (A)DT. In this case it _will_ make a difference how often you
call it. But then this is just how IO actions are by nature, isn't it?

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Benjamin Franksen
On Sunday 07 November 2004 13:36, you wrote:
> AFAICS the only alternative to..
>
>  userInit <- oneShot realInit
>
> is to export realInit, have users create their own userInit, and then pass
> that around as an argument to everything that might make use of userInit.

Yes. For instance, user code executes

handle <- YourModule.init

and in the rest of the program the handle is used as an argument to those and
only those routines that actually depend on the initialized state represented
by 'handle'. In the Haskell Web Server it turned out that after all it wasn't
that many routines that depended on initialized state.

It's a similar advantage as using the IO monad has over allowing arbitrary
side-effects in functions: The IO monad gives you a clear separation between
stuff that has (side-) effects (i.e. depends on the real word) and pure
functions (which don't). Abandoning global variables gives you a clear
separation of stuff that depends on initialized state and other stuff that
does not depend on it.

> Maybe I'm missing something, but this doesn't seem very attractive to me
> as a library writer (it means I must expose realInit and just trust
> users to only use it once).

Your realInit is an IO action, right?

Imagine you are a library user, and the library exports some IO action for
 you to use. Would you assume that it makes no difference whether you call it
 once or twice in the program?

Surely you won't: You know that IO actions have (side-) effects, so you would
take care that the actions get executed as many times as is apropriate. If
the library docs indicate that it makes no sense to call it twice, why would
you do so?

Maybe *I* am missing something, but I can't see any principle difference
between exporting 'realInit' and exporting 'putString'. In both cases the
program behaves differently depending on whether I call it once or twice.

> It doesn't seem very attractive to users either
> (considerably complicates their code and places the burden on them to
> "get it right").

It may seem so at first, but I think it's a delusion.

I found out with the HWS, that it does *not* necessarily "considerably
complicate" the (user) code. And the compiler helps you a lot to "get it
right", much more in fact than if you hide state dependency inside global
variables. In the above example, the compiler *forces* you to call
'YourModule.init' because it is the only way to produce a 'handle' and you
need some 'handle' to call the routines that depend on it. It also forces you
to call it *before* you use any of the routines that depend on it. All in all
this lifts a lot of the burdon off the user, rather than placing it on her.

At the moment I cannot imagine a well designed library interface where user
code would be considerably complicated if no global variables were used. But
maybe you have a good example at hand to prove that this is merely due to
lack of imagination on my side, and that I was extremely lucky with the
HWS? ;-)

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-06 Thread Benjamin Franksen
As an experiment, I just finished to change the Haskell Web Server with 
Plugins such that all global variables (unsafePerformIO-style) are replaced 
by standard argument passing. It wasn't difficult. The main work was

(1) get it to compile with ghc-6.2.2
(2) understand how the code is organized
(3) find out that implicit parameters have too many limitations to be usefull 
as a general replacement
(4) find appropriate pattern(s) to get rid of the globals

Overall I think the code has somewhat improved. The parts that were written 
with global variables are now shorter and more easily understood.

What I didn't expect was that modularity did *not* suffer, quite the opposite: 
the interfaces became smaller. For instance the MimeTypes module exported two 
routines:

initMimeTypes :: String -> IO ()-- argument is file path to mime.conf
mimeTypeOf:: String -> MimeType -- convert file path to mime type

where unsafePerformIO was used not only to create the global variable for the 
mime type map, but also for the conversion function (because it had to access 
teh global var).

The new interface has only one routine:

initMimeTypes :: String -> IO (String -> MimeType)
-- argument is file path to mime.conf
-- result is file path to mimetype converter

and no unsafe feature is used: the result is a pure function.

Of course, the downside is that some of the functions (not many) now have one 
or two additional arguments. OTOH one could argue that this is in fact an 
advantage, as it makes all the dependencies crystal clear. It turned out, for 
example, that of the two logging modules, ErrorLogger and AccessLogger, the 
latter had a hidden dependency on the former. That dependency is now 
expressed explicitly by giving the initialization routine for the 
AccessLogger an extra argument (namely the error logging function).

Surely this is just one example, and not a very complex one. Nevertheless, I 
am now less convinced that using global variables is in fact a good idea, 
however convenient it may seem at first.

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 22:07, Keean Schupke wrote:
> So what
> we need is a way in the type system to tell the compiler the function
> must have
> a single unique definition... Something like:
>
> myRef :: Unique (IORef Int)
> myRef = uniquePerformIO $ newIORef 0
>
> and then have:
>
> runUnique :: Unique x -> x

In Eiffel it is called 'once' istead of 'Unique', e.g. (excuse my rusty 
Eiffel, the syntax may be wrong)

class XYZ
feature
once ref : Int
do
...routine body here...
Result := ...
end
end

The semantics is that the routine body is executed at most once, namely when 
the feature is used for the first time.

Note that Eiffel allows arbitrary IO actions to be performed in the body of 
once routines, just like in your Haskell example above. It is interesting to 
note that the Eiffel community is quite aware of the problems this solution 
has, i.e. that the procedure may have side-effects that happen at some 
unpredictable moment in time -- especially when concurrent execution comes 
into play. It is regarded as a matter of programmer discipline to ensure that 
once routines do not have effects visible outside the class in which they are 
defined.

Such an appeal to programmer discipline clearly fits not well with the spirit 
of Haskell. I would argue that the actions to be performed inside such a 
'once' or 'unique' initialization must be strictly limited to harmless ones 
like allocation of reference cells. As i pointed out earlier, elements of a 
commutative sub-monad of IO are not automatically harmless. How else can we 
define "harmless" IO actions?

Maybe Ben Rudiak-Gould's idea to use (forall s . ST s) is teh right idea but I 
still don't understand it...

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 15:45, MR K P SCHUPKE wrote:
> >The point is to avoid threading global state to IO actions manually.
> >Programming langages exist in order to conveniently write programs in,
> >not only to admire their beauty.
>
> So if you are not interested in beauty, why not use the IO monad! If
> something is IO then declare it. You should not lie to the type system,
> or try to cheat it. It is your friend, and will help prevent errors
> in code.

Just to clarify (and not to take position): in order to access a global 
variable in the unsafePerformIO-newIORef-style you still need to be in the IO 
Monad.

Eiffel can dispense with global variables not least because objects contain 
mutable state. And the methods cann access this state inside their object 
without taking it as an argument.

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Benjamin Franksen
On Thursday 04 November 2004 18:54, George Russell wrote:
> John Peterson wrote (snipped):
>  > The implementer of these functions has to guarantee that the
>  > actions do not destroy the commutativity of the CIO monad.
>
> Sorry, but several of my variable initialisation actions involve
> things like starting up child processes or rapid exits from the program
> if unsuccessful, which certainly cannot be guaranteed to be
> commutative.
>
> I still think the proposal I made to this list in June
> http://www.haskell.org//pipermail/haskell/2004-June/014104.html
> is sound.  It requires nothing other than a new library, which is
> trivial to implement using the existing unsafePerformIO.  It is
> safe.  I don't think it's especially clunky.  Essentially the
> only serious limitation is that you can only access a bit of
> initialised state from an IO action, but in my experience at least
> this is not a serious issue.

The idea looks good to me. Do you have a prototype implementation?

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Benjamin Franksen
On Thursday 04 November 2004 18:28, Koen Claessen wrote:
> Ben Rudiak-Gould wrote:
>  | I think the OP is proposing the same thing, except
>  | without the ellipsis: i.e. we just write
>  |
>  | pretty :: Doc -> String
>  |
>  | and the compiler infers pretty :: (?width :: Int) => Doc
>  | -> String, or whatever. This actually sounds like a very
>  | good idea to me.
>
> I think hiding the fact that certain objects are not
> constants but functions is a bad idea, because it will break
> sharing in a lazy implementation.

You probably mean the case where the implicit parameter is the only one. I 
don't see why that would "break sharing in a lazy implementation". The 
compiler is fully aware of the complete type of all functions and can use 
sharing whenever appropriate.

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Benjamin Franksen
On Thursday 04 November 2004 17:20, Ben Rudiak-Gould wrote:
> Koen Claessen wrote:
>  >(1) Whenever a module uses an implicit parameter like that,
>  >it has to have a name that is different from all implicit
>  >parameters used by any other (future) module. (Yes, implicit
>  >paramers cannot be quantified by a module name.) This is
>  >difficult to ensure.
>
> This is one of the several ways in which the current implementation of
> implicit parameters is broken. Clearly they *should* belong to the
> module namespace, and if we modify the implementation so that they do,
> the problem you describe here goes away.

I have thought about this and I am not sure that this is possible or even 
makes sense. Remember that implicit parameters cannot be bound at the top 
level. They must be 'let' or 'where' bound. Indeed, when using them for a 
global variabe replacement, we do *not* want them at the top level, because 
we want to initialize them explicitly:

do_stuff_with_x = do
use_it ?x -- refers to the x bound in main

main = do
x <- initialize_x
do_stuff_with_x

What if do_stuff_with_x is in another module? We could say that x belongs to 
namespace Main (i.e. the module in which it is bound)

do_stuff_with_x = do
use_it ?Main.x

but then do_stuff_with_x cannot be called from any other module. This is bad. 
We could also say that x belongs to the namespace where x is used, but this 
would lead to similar problems, i.e. all usages of an implicit parm would be 
limited to one and only one module. This is bad too.

Ben (the other one)
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Benjamin Franksen
On Thursday 04 November 2004 16:16, Koen Claessen wrote:
> The problem with John's approach is that it breaks
> modularity. It does this in two ways:
>
> (1) Whenever a module uses an implicit parameter like that,
> it has to have a name that is different from all implicit
> parameters used by any other (future) module. (Yes, implicit
> paramers cannot be quantified by a module name.) This is
> difficult to ensure.

I haven't thought of this before. It is a drawback, indeed. Is there any 
convincing technical reason why implicit parameters cannot be "quantified by 
a module name" (whatever that may mean exactly).

> (2) Having the implicit parameter breaks the abstraction
> barrier. I might want to re-implement a module that does not
> make use of global variables, into one that uses a cache or
> hash-table or whatever (think BDD library), and not change
> the interface of the functions that are provided.
>
>  | What I've been asking myself is: Wouldn't it be possible
>  | for the compiler to silenty add the implicit parameter
>  | type constraints behind the scenes?
>
> You would be back at square 1, since your program will still
> look and behave exactly the same as a program that
> implicitly executes all initializations; the only difference
> is implementation.

No, not at all. "behind the scenes" refered only to adding appropriate *type 
annotations* (i.e. implicit parameter constraints). You would still need to 
perform all initialization explicitly inside main.

If this were possible, at least your critique point 2 would no longer apply.

Ben Rudiak-Gould explained very clearly what I meant.

> I have a different proposal.
>
> Imagine a commutative monad, CIO. Commutative monads have
> the property that it does not matter in what order actions
> are performed, they will have the same effect. In other
> words, for all m1 :: CIO A, m2 :: CIO B, k :: A -> B -> CIO
> C, it should hold that:
>
>   do a <- m1 do b <- m2
>  b <- m2 ===a <- m1
>  k a b  k a b
>
> Now, one could imagine an extension X of Haskell98, in which
> modules are allowed to contain definitions of the form:
>
>   p <- m
>
> Here, p is a (monomorphic) pattern, and m is of type CIO A,
> for some type A. CIO is an (abstract) monad provided in a
> library module, just like IO is today.
>
> One could wonder where the primitive actions in the monad
> CIO come from? Well, library providers (compilers) could
> provide these. For example:
>
>   newIORefCIO :: a -> CIO (IORef a)
>   newEmptyMVarCIO :: CIO (MVar a)
>
> And so on.
>
> The implementer of these functions has to guarantee that the
> actions do not destroy the commutativity of the CIO monad.
> This is done in the same way as today, compiler writers and
> users of the FFI guarantee that certain primitive operations
> such as + on Ints are pure.
>
> The FFI could even adapt CIO as a possible result type
> (instead of having just pure functions or IO functions in
> the FFI).

This proposal is very elegant and beautiful. There is one caveat, however.

Commutativity is a property of the Monad in itself. Inside the CIO monad 
everything commutes, but does that mean actions inside CIO always commute 
with all other actions in IO?

Instead of just being a commutative sub monad of IO, CIO would need to be a 
sub-monad in IO that has the property that its actions commute with every IO 
action. Only then would the order of execution be irrelevant.

CIO would surely contain actions to create MVars and IORefs. Are there other 
primitive IO actions that belong to (this) CIO?

***

On a different note, I remember that Eiffel (an imperative OO language) lacks 
global variables, too. As a replacement Eiffel has so called 'once' routines. 
These are executed only once per program run -- later calls just return the 
memoized result from the first time.

This smells a lot like the unsafePerformIO+{- NoInline-} aproach to me.

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


Re: [Haskell] Global Variables and IO initializers

2004-11-01 Thread Benjamin Franksen
Let me add a few thoughts on the global variables problem and the proposed 
solutions.

1) I strongly disagree with ideas to execute IO actions implicitly in whatever 
defined or undefined sequence before or during main for whatever reasons. If 
initialization actions are necessary, they should always be performed 
explicitly from inside main. If modules or libraries need init actions to be 
performed, then such actions should be exported (and documented) in the 
normal way. The reasons are manyfold:

a) Explicit initialization means that the end-programmer has complete control 
over when and if such actions get executed, which is a Good Thing. It may 
very well happen, for example, that a program needs to perform some init 
action on its own before doing the one for an imported library. Or that one 
doesn't want to execute the library's init action at all because what one 
wants to use from it doesn't need the initialization.

b) Only explicitly called init actions may be parameterized. This means that 
any library that needs its initialization action to be parameterized by the 
user has to use the explicit variant anyway.

c) Implicitly executed init actions make the code harder to reason about.

d) Calling user code before main() was introduced in C++ (it is not possible 
in C). It took a while for programmers (myself included) to realize that the 
apparent elegance and convenience of this has a huge cost in maintainability, 
especially (but not only) in connection with shared libraries. AFAIK, using 
static objects with non-trivial constructors in libraries is nowadays deemed 
bad practice and rightly so. I know of one case where this has been the cause 
for inexplicable crashes when porting a library from one unix variant to 
another one. This delayed the release of the port for at least a year!

e) It has already been noted that if init actions from other modules are to be 
executed implicity, then the compiler needs to determine which module init 
actions to perform. The straight forward 'solution' is to use the import 
lists. This would imply that changing the import list of a module has 
potentially far reaching side-effects. This could lead to very obscure bugs.


2) I agree that avoiding global variables is often inconvenient. Even if we 
combine all of them into a single compound value ('globals'), at least this 
one value has to be threaded through a lot of functions that aren't in the 
least interested in them. Aside from making the code fragile against changes, 
it introduces a certain amount of noise into the code, making it harder to 
read and understand. I disagree though with what

On Wednesday 13 October 2004 00:33, John Meacham wrote:
> The issues are
> [...]
> 3) do we need it?
> [...]
> 3) yes. the
> {-# noinline :: fooVar #-}
> fooVar = unsafePerformIO $ newIORef 0
> is a very common idiom in real programs, and very difficult to work
> around not having.

It may be tedious and inconvenient to add a record of 'globals' as argument to 
all the functions involved, but difficult it is not. It is in fact so simple 
that it could be easily automated.

What I originally wanted to propose was therefore some sort of 
source-to-source program transformation that adds all the intermediate extra 
function arguments. Then I realized that this is almost exactly what the so 
called 'implicit parameters' extension to Haskell is all about, and that 
using them as a replacement for global variables has already been proposed by 
John Hughes (http://www.cs.chalmers.se/~rjmh/Globals.ps).

He notes in this paper that implicit parameters, as implemented in GHC, infect 
the types of all the involved functions with extra contexts. Although in 
principle this is exactly what we want, it implies that the addition of an 
implicit parameter (or changing its type) potentially invalidates a lot of 
function signatures (if these are given explicitly). This is unfortunate 
because it makes the code fragile and partly re-introduces the tedium we 
wanted to avoid in the first place.

What I've been asking myself is: Wouldn't it be possible for the compiler to 
silenty add the implicit parameter type constraints behind the scenes? It 
already does so for functions without a signature, so why not do it for 
functions with an explicit signature, too?

I realize that this would be a break with the Haskell tradition to *either* 
infer types *or* use the programmer given type signatures. Nevertheless, if 
this would work, we'd have a very clean *and* easily usable solution to the 
global variables problem.

Ben

P.S. I like the '?identifier' syntax for implicit parameters because it 
clearly marks such entities as dynamically bound instead of statically: you 
wouldn't even try to find the definition of such a thing in the surrounding 
scope.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] ANNOUNCE: GHC version 6.2.1

2004-03-22 Thread Benjamin Franksen
On Monday 22 March 2004 16:40, Simon Marlow wrote:
>
>   - The "threaded runtime system" is included by default.  To link
> a program with this variant of the RTS, add the -threaded option
> when linking. 

After downloaded the sources i found that ./configure --help still lists the 
-threaded-rts option. Should i ignore this option or do i have to set it? 
(I'm asking because building ghc from source really takes a *lot* of time, so 
i'd rather know how to configure it before starting the build.)

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