Re: Superclass defaults

2011-09-03 Thread Niklas Broberg
On Mon, Aug 22, 2011 at 10:05 AM, Max Bolingbroke <
batterseapo...@hotmail.com> wrote:

> On 21 August 2011 21:03, Alexey Khudyakov 
> wrote:
> > I don't completely understant how does it work. Does client need to
> enable
> > language extension to get default instances?
>
> I think that the extension would only be required to *define them*,
> not for them to be generated. The more conservative choice would
> indeed be to require the extension for both, though.
>

Please allow me to voice my not-so-humble opinion that, as a rigid
principle, any extension is ALWAYS enabled with a flag, and never enabled
silently. This is what Max calls the "conservative" choice, while I would
like to call it the "only sensible" choice.

1. In particular: adhering to this principle makes it much much easier to
achieve consistency between different compilers and tools working with
Haskell code. GHC is currently in so strong a position as to make its own
laws, but with great power comes great responsibility. Even if GHC will
always have the proper context available, it is by no means certain that
other tools will. In this particular instance, it is certainly not
inconceivable or even improbable that tools other than compilers might want
to analyse a module containing instance declarations, without knowing a
priori that some default superclass instances are assumed. Having a flag
always makes this clear.

(As an example, GHC already breaks this principle in (at least) one instance
- MPTC when used as contexts - which creates problems for haskell-src-exts).


2. If you are worried about breakage of legacy code, you can always achieve
silent enabling by having a flag and having it on by default. Then GHC can
declare that it, by default, compiles a Haskell extension and not the
standard. This could still create problems when programmers expect other
tools to work on their GHC-specific files, but then at least we have a clear
story and can put blame where blame is due (on GHC). Other tools can then
also opt to enable the same extensions by default, or by flag. Also, it
would make it possible to explicitly remove the flag in client code (with
the appropriate -XNo... flag).

>From a principle point of view this is still not a perfect solution, and I
would prefer that an explicit flag was always needed (unless and until the
extension is adopted in the proper Haskell' revision). I realise this would
break a lot of code though, and having a flag enabled by default is far, far
better than not using a flag at all.

3. I must admit I don't fully see how client code can be kept from the need
to enable the extension. In particular, if client code must use the explicit
opt-out, this is a rather obvious syntactic change - are you really
suggesting that we enable new syntax without the need to declare what
language (i.e. extensions) the file uses? Of course, there is precedent for
such a move with the ugly MPTCs-in-contexts mentioned above - a precedent
that I would very much like to see revoked. I would in any case like to
voice my very strong opinion against such a choice.


That said - I definitely like the general idea of default superclass
instances, I think the proposed extension is very elegant and fixes a
definite wart. But please let's not introduce other problems by adopting it!

To be concrete, I propose the following named extensions (exact names up for
bike-shed discussion):

* DefaultSuperInstances: Enables the full SHE-bang (pun fully intended),
including in particular the syntactic additions in class and instance
declarations.
* SilentDefaultSuperInstances: Enables ONLY the possibility for client code
to use inherited default instances. This extension is subsumed by
DefaultSuperInstances (except for error/warning behavior discussed below),
just like RankNTypes subsumes Rank2Types.

I further propose that GHC enables SilentDefaultSuperInstances by default,
as a pragmatic choice to avoid legacy issues, but not DefaultSuperInstances.


If (only) SilentDefaultSuperInstances is enabled, I propose that Option 2 is
used. It makes perfect sense to warn if you override a default instance,
just like it is sensible to warn about name shadowing. Option 3 strikes me
as strictly worse. However, if DefaultSuperInstances is enabled (which must
then be done explicitly), I propose that Option 1 is used instead.


2011/9/2 Conor McBride 

> On 2 Sep 2011, at 18:19, Jonas Almström Duregård wrote:
>
The recent discussion concerns whether option 2 should eventually be
> shifted to option 1. Everyone seems to agree that option 2 should be
> used initially.
>

With my proposal this discussion becomes moot. SilentDefaultSuperInstances
effects option 2, DefaultSuperInstances effects option 1. The discussion can
then instead turn to whether or not DefaultSuperInstances should be adopted
in Haskell', and (only) at that point there will be an automatic switch to
option 1.

A similar warning should perhaps indicate that a "hiding" clause has
> nothing to hid

Re: Question regarding the GHC users manual

2010-01-25 Thread Niklas Broberg
> type family F a b :: * -> *   -- F's arity is 2,
>                              -- although its overall kind is * -> * -> * -> *

I believe what you're missing is that with the definition F a b :: *
-> *, F needs three arguments (of kind *) in order to become kind *.
If F a b :: * -> * as stated, then F a :: * -> * -> * and F :: * -> *
-> * -> *, just like reported.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Qualified names in import lists

2009-12-28 Thread Niklas Broberg
> If ghc really does accept the example given, I would like to know what
> entity Bar.bar refers to, since it cannot possibly be exported by Foo.

In this example Bar exports bar, and Foo re-exports module Bar.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Qualified names in import lists

2009-12-28 Thread Niklas Broberg
Hi all,

I have a bug report [1] for haskell-src-exts pertaining to the use of
qualified names in import specifications, e.g.

  module Main where
  import Foo (Bar.bar)

GHC apparently accepts this code, but I can find no mention of such a
feature in the GHC docs.

Personally I don't see why this should be allowed at all, as it breaks
the abstraction layer w.r.t. re-exporting names from other, possibly
internal, modules. If there's some reasonable use for it, it should at
the very least be tied to a documented and registered extension.

I've submitted a ticket for GHC [2] to either remove this feature, or
properly document it. I'd be curious to hear what the reasoning behind
it is, if any.

Cheers,

/Niklas

ps. Why is there no "GHC accepts invalid program" option for "Type of
failure"? Too few cases? I set this ticket to Other.

[1] http://trac.haskell.org/haskell-src-exts/ticket/57
[2] http://hackage.haskell.org/trac/ghc/ticket/3792
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Three patches for cabal

2009-11-09 Thread Niklas Broberg
> I think in the end I'm with Ian on his suggestion that we should allow
> the "No" prefix to invert an extension. This would help in this case and
> also let us handle things better when the default extensions change.

I too agree with this position for the long run.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Three patches for cabal

2009-11-05 Thread Niklas Broberg
>> Second there's the constructor NoMonoPatBinds, which actually
>> describes the default Haskell 98 behavior, even if GHC has a different
>> default. It's GHC's behavior that is the extension, so the constructor
>> in cabal should really be named MonoPatBinds.
>>
>> Also, the PatternSignatures constructor has been deprecated in GHC and
>> superceded by ScopedTypeVariables.
>
> Can someone please comment on these two proposed changes. I agree with
> Niklas but I'm a bit reluctant to apply the patches without at least
> some sign of agreement from someone else.
>
> Deprecating PatternSignatures seems uncontroversial, but the
> NoMonoPatBinds is potentially controversial. GHC essentially uses
> -XMonoPatBinds by default, even in H98 mode, and the user can use
> -XNoMonoPatBinds to restore H98 behaviour. Niklas's and my point is that
> the list of language extensions in Language.Haskell.Exceptions are
> differences from H98 so it should be MonoPatBinds to get the difference
> not NoMonoPatBinds to restore H98.
>
> In practise, since ghc uses MonoPatBinds by default it'd mean that
> people who want to get back to H98 would need to use:
>
>  ghc-options: -XNoMonoPatBinds
>
> Because the extensions field is additive, not subtractive. Using the
> name MonoPatBinds allows other compilers to implement it without it
> having to be the default.

I had a look at the source for cabal HEAD and was surprised to see
that this stuff had fallen by the wayside. What's holding it up? I
can't imagine that anyone would be against the deprecation of
PatternSignatures at least.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: 6.12.1 release

2009-10-22 Thread Niklas Broberg
> Simon and I favour the RC2 option.  What do others think?

+1

Definitely preferable to the chaos that would otherwise ensue.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: ExplicitForall

2009-07-23 Thread Niklas Broberg
> Alright, let's set an actual discussion period of 2 weeks for
> ExplicitForall. If there is no opposition by then, we can add
> ExplicitForall to the registered extensions in cabal as a first step.

Slightly more than two weeks later, there has been no voices against
and at least a few in favor.

The attached patch for Cabal adds ExplicitForall to the Extension
datatype, with documentation, and adds it to knownExtensions.

Cheers,

/Niklas


ExplicitForall.dpatch
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-07-23 Thread Niklas Broberg
> Discussion period: 2 weeks

Returning to this discussion, I'm surprised that so few people have
actually commented yea or nay. Seems to me though that...
* Some people are clearly in favor of a move in this direction, as
seen both by their replies here and discussion over other channels.
* Others are wary of deprecating anything of this magnitude for
practical reasons.
* No one has commented in true support of the classic existential
syntax, only wanting to keep it for "legacy" reasons.

I'm in no particular hurry to see this deprecation implemented, and I
certainly understand the practical concerns, but I would still very
much like us to make a statement that this is the direction we intend
to go in the longer run. I'm not sure what the best procedure for
doing so would be, but some sort of soft deprecation seems reasonable
to me.

Further thoughts?

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Fwd: Generating valid Haskell code using the GHC API pretty printer

2009-07-23 Thread Niklas Broberg
> I believe, Language.Haskell.Pretty can properly output haskell code (and
> the GHC API should be able to do so, too. Does the GHC API output tabs?)

Surely you mean Language.Haskell.Exts.Pretty, right? ;-)

The haskell-src-exts library does not (yet) support full
round-tripping source-to-source, so the generated output will be
different from what was read. But it will at least produce valid
output. Hopefully in a few months' time it will do the full
round-tripping as well, at least that's the plan.

In general, unless you actually want to use any other components of
the GHC API, e.g. evaluate your code, then I see no reason to use the
GHC API for source manipulation. haskell-src-exts simply does that
better (and definitely better than haskell-src). But I couldn't tell
if that's enough for the original poster's needs. :-)

[/shameless plug]

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-28 Thread Niklas Broberg
>> What you really want or mean when you use
>> the classic syntax with existential quantification is
>>
>>> data Foo = Foo (exists a . (Show a) => a)
>>
>> Having that would make a lot more sense, and would fit well together
>> with the intuition of the classic syntax.
>
> How would you then define
>
>  data Foo :: * where
>    Foo :: forall a. a -> a -> Foo
>
> in which the scope of existentially quantified type variable spans more than
> one field?

Good point, and one I admit I hadn't considered. Using GADT style syntax? ;-)

However, your argument certainly speaks against the style using
exists, but it doesn't do much to persuade me that the style we now
have is any less of a wart. To me it's just another point in favor of
deprecating it with the classic syntax completely.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-28 Thread Niklas Broberg
> ... "constructor Foo has the type forall a . (Show a) => a".

Eh, of course I meant "the type forall a . (Show a) => a -> Foo", but
you understood that I'm sure. :-)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-28 Thread Niklas Broberg
> I agree. But ;-) since it's obvious not possible to get rid of the classic
> syntax completely, I see no harm in having it support existentials and GADTs
> as well. In an ideal word, in which there wasn't a single Haskell program
> written yet, I'd indeed like to throw the classic syntax out altogether.

Ah, but there's the thing. The classic syntax *doesn't* support
existentials and GADTs, if by classic you mean Haskell 98. You need a
separate syntactic extension, and the one we have is ad-hoc and
unintuitive (the whole universal vs existential quantification thing
is awkward), not to mention ugly. There's simply no sense to a
declaration reading e.g.

> data Foo = forall a . (Show a) => Foo a

The entities on the right-hand side of that declaration come in the
wrong order, intuitively. What you really want or mean when you use
the classic syntax with existential quantification is

> data Foo = Foo (exists a . (Show a) => a)

Having that would make a lot more sense, and would fit well together
with the intuition of the classic syntax. If we wanted to keep support
for existential quantification together with the classic style, that
should IMNSHO be the way to do it. But for various reasons (like not
wanting to steal another keyword) we don't do it that way. Instead we
have a syntax that is meant to be understood as "constructor Foo has
the type forall a . (Show a) => a". But that's exactly what we would
express with the GADT-style syntax! :-)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-28 Thread Niklas Broberg
>> In other words, in your 2x3 grid of syntactic x expressiveness, I want
>> the two points corresponding to classic syntax x {existential
>> quantification, GADTs} to be removed from the language. My second
>> semi-proposal also makes each of the three points corresponding to the
>> new cool syntax a separate extension.
>
> I see, but why are you opposed to have the classic syntax still support
> existentials (though foralls) and GADTs (through equality constraints). I
> would make sense to me to keep this support around.

I am opposed since
a) it requires the addition of extra syntax to the language, and
b) we have another, better, way to do it.

Somewhat pointed, I don't think the C++ way of putting all imaginable
ways to do the same thing into the language is a sound design
principle. If we have two ways to do the same thing, and one of them
is considered prefered, then I see no reason at all to keep the other
around. What I'm arguing here is that the GADT style syntax is truly
preferable, and thus the other should be removed.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-28 Thread Niklas Broberg
> That's why one should really be allowed to group constructor's in a type's
> definition:
>
>  data Colour :: * where
>    Red, Green, Blue :: Colour
>
> This is consistent with what is allowed for type signatures for functions.

Totally agreed, and that should be rather trivial to implement too.

> More general, whatever way your proposal is going, I think you should have
> it reflect that there are two, more or less unrelated, issues here:
>
> 1. The expressiveness of data types: algebraic data types < existential data
> types < GADTs.
> 2. The syntax of type definitions: the classic, Haskell 98 syntax and the
> new, cool listings-of-constructor-signature syntax. (Don't call the latter
> NewTypeSyntax or anything similar in a LANGUAGE pragma; choose something
> descriptive.)
>
> These are really orthogonal issues: all three levels of expressiveness of
> types can be expressed in either syntax. Therefore: keep these issues
> separated in your proposal.

Well, I think my proposal already does reflect this fact, if
implicitly. The point of the proposal is that all three levels of
expressiveness of types can be expressed in the
listings-of-constructor-signature syntax, but to express the type
level power of existential data types or GADTs with the classic
syntax, we need to extend that syntax. And that's what I'm after,
that's we remove this rather ad-hoc add on syntax required to express
existential quantification with classic constructor declarations.

In other words, in your 2x3 grid of syntactic x expressiveness, I want
the two points corresponding to classic syntax x {existential
quantification, GADTs} to be removed from the language. My second
semi-proposal also makes each of the three points corresponding to the
new cool syntax a separate extension.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Niklas Broberg
>> I would hereby like to propose that the
>> ExistentialQuantification extension is deprecated.
>
> It is worth pointing out that all current Haskell implementations (to my
> knowledge) have ExistentialQuantification, whilst there is only one Haskell
> implementation that has the proposed replacement feature, GADTs.
>
> Of course, that in itself is not an argument to avoid desirable change to
> the language, but it is one factor to consider.

The tongue-in-cheek response is that it should be a factor to consider
only for how long a deprecation period we want... ;-)

Seriously though, it's of course a consideration that should be made.
It also ties back to the problem of the monolithic GADTs extension,
which isn't trivial to implement in other tools - but the
ExistentialQuantification *subset* of GADTs should be easy, for any
implementation that already supports the current
ExistentialQuantification extension, since then it's just a syntactic
issue.

So might as well bite that bullet then, what if we did the following
split, in the spirit of the various increasing power of the extensions
that enable forall-quantified types ((ExplicitForall <=)
PolymorphicComponents <= Rank2Types <= RankNTypes):

* NewConstructorSyntax: Lets the programmer write data types using the
GADTs *syntax*, but doesn't add any type-level power (and no forall
syntax). Could probably use a better name (bikeshed warning).

* ExistentialQuantification: Implies NewConstructorSyntax (and
ExplicitForall). Let's the programmer use existentially quantified
arguments to constructors when using the GADTs syntax. Still requires
all constructors to have the same type, which is the one given in the
header.

* GADTs: Implies ExistentialQuantification. Let's the programmer use
the full type-level power of GADTs.

It might make sense to merge NewConstructorSyntax and
ExistentialQuantification, though I'm not sure naming that merge
ExistentialQuantification would be accurate (naming is the bikeshed
though). Personally I would prefer the full 3-way split, to keep a
clean separation between syntactic and semantic extensions, but it's a
rather weak preference.

If we had something like this split, implementations that already
support ExistentialQuantification at the type level would "only" need
to change their parsers in a simple way (nothing hard, trust me), and
add what should be a simple check that the constructors all have the
declared type.

Would that be preferable?

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Niklas Broberg
Hi all,

Following the discussion on the use of 'forall' and extensions that
use it [1], I would hereby like to propose that the
ExistentialQuantification extension is deprecated.

My rationale is as follows. With the introduction of GADTs, we now
have two ways to write datatype declarations, the old simple way and
the GADTs way. The GADTs way fits better syntactically with Haskell's
other syntactic constructs, in all ways. The general style is
(somewhat simplified) "keyword type 'where' decls", where keyword can
in Haskell 98 be class or instance, but with GADTs also data. The old
simple way of defining data types is the odd one out. It certainly has
its uses though, in particular when defining some simple (but possibly
large) enum-like datatype (like cabal's Extension type incidentally),
then it obviously becomes tedious to have to restate the trivial type
signature for each constructor.

Using GADTs style syntax it is possible to allow constructors with
existentially quantified arguments with *no additional syntax needed*.
It follows nicely from the standard syntax for type signature
declarations (assuming explicit foralls), e.g. the following "normal"
datatype declaration

  data Foo =
forall a . Show a => Foo a

which uses ExistentialQuantification syntax, could be written as

  data Foo where
Foo :: forall a . Show a => a -> Foo

which is syntactically just a normal type signature.

The upside of deprecating ExistentialQuantification is thus that we
keep the syntax cleaner, and we keep the old style of datatype
declarations simple (as it should be, IMO). Anything fancier can use
the GADTs syntax, which anyone that uses something fancier should be
acquainted with anyway.

The downside is that we lose one level of granularity in the type
system. GADTs enables a lot more semantic possibilities for
constructors than ExistentialQuantification does, and baking the
latter into the former means we have no way of specifying that we
*only* want to use the capabilities of ExistentialQuantification.

My own take on that is that what we have now is a wart that should be
removed, and that if we think that the latter is a problem then the
way to go would be to split the monolithic GADTs extension into
several semantic levels. There is of course also the downside that we
break existing code, but that's a standard problem with improvement
through deprecation which I will pay no mind.


Discussion period: 2 weeks

Cheers,

/Niklas

[1] http://www.haskell.org/pipermail/glasgow-haskell-users/2009-June/017432.html
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: ExplicitForall

2009-06-24 Thread Niklas Broberg
> What you suggest would be fine with me. Presumably ExplicitForall would be 
> implied by RankNTypes and the other extensions?

Yes, that's the idea. Rank2Types, RankNTypes, PolymorphicComponents,
ScopedTypeVariables and LiberalTypeSynonyms would all imply
ExplicitForall.

> There is a danger of having too *many* choices. 
> (http://www.joelonsoftware.com/items/2006/11/21.html)  In particular, you 
> might consider making ScopedTypeVariables synonymous with ExplicitForAll.  
> Once you have given up the keyword, it seems a shame not to allow lexically 
> scoped type variables!

While I agree with you (and Joel) in principle, I think this is the
wrong level to hold that discussion. I think the long-term solution
should be to keep the registered extensions cleanly separated, and
instead supply extension *groups* as a way to limit choice.
-fglasgow-exts has fit that niche admirably for a long time, I think a
lot of people just use that without thinking twice about what
particular extensions they actually use, and nothing wrong with that.
I think the move towards LANGUAGE pragmas instead of compiler options
is a good one from a standardisation and implementation point of view,
but to avoid tedium and unnecessary choice for the programmer I
strongly feel that extension groups need to be introduced at this
level too. But as I said, that's for a different discussion...

> On ExistentialQuantification, I personally think we should deprecate the 
> entire construct, suggesting GADT-style syntax instead.

+1, though I was afraid to suggest something that radical. I might
write a separate proposal for that then, to keep the discussion here
focused on ExplicitForall.

> If you can form a consensus, go for it.

Alright, let's set an actual discussion period of 2 weeks for
ExplicitForall. If there is no opposition by then, we can add
ExplicitForall to the registered extensions in cabal as a first step.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Proposal: ExplicitForall

2009-06-23 Thread Niklas Broberg
Hi all,

(I'm writing this to several lists since it involves GHC
(implementation of extensions), cabal (registration of extensions) and
some future Haskell standard (formalisation of extensions).)

In my quest to implement all known syntactic extensions to Haskell in
my haskell-src-exts package, I've become painfully aware of the
sometimes ad-hoc nature that these extensions have been added to GHC.
This should not be taken as criticism per se, GHC is awesome and I'm
sure a lot of thought and research has gone into all of these
extensions. I think the problem (from my point of view) is rather that
most of the extensions are only really "interesting" on a type system
level, whereas the syntactic level is rather trivial, and thus the
latter has (rightly) gotten far less formal attention. I hope my
putting the light on these issues will be a help and a kickoff towards
improving the state of formalisation of the known and registered (with
Cabal) extensions.

One of the most blatant and (to me) problematic such issues is the
matter of using 'forall'. GHC has a number of extensions relating to
the use of forall-quantified types in various interesting ways. With
none of these extensions on, forall is not considered a keyword, so
the syntax with explicit forall quantification cannot be used at all
('forall' is considered a varid). However, with *any* extension on
that relates to forall-quantified types, forall is a keyword, and can
syntactically be used in types *anywhere*. This doesn't mean all such
types will pass the type checker, most of them won't in fact, but
syntactically there is really no (or at least very little) difference.

Conceptually, all of these extensions (specifically
PolymorphicComponents, Rank2Types, RankNTypes, LiberalTypeSynonyms and
ScopedTypeVariables (and strangely also ExistentialQuantification))
thus have one thing in common. They all enable syntactically
forall-quantified types. They allow different uses of these types as
far as the type system is concerned, but syntactically there is no
difference between type and type (in fact there cannot be, as I
discussed in a recent blog post [1]).

Funnily enough there are also some uses of forall-quantified types
that are common to all of these extensions - using a forall just to
make polymorphism explicit in a type doesn't change anything as far as
the type system is concerned, so e.g. the types '(Eq a) => a -> Bool'
and 'forall a . (Eq a) => a -> Bool' are equivalent. The latter type
can be given to a function when any of the listed six extensions are
given, even if most of them have nothing to do with this at all!

So, what I'm getting at is an idea that Isaac Dupree gave as a comment
to my blog post. He said:

   "I wish there was a plain old ExplicitForall extension that enabled
the keyword in types (without extending the type checker -- only like
(id :: forall a. a -> a) would be allowed)".

I think this is a really great idea. I find it conceptually appealing,
since I think it covers exactly that blind spot that is the seemingly
unintended intersection between all these extensions. And it also
makes the separation of concern between the syntactic level and the
type system more clear. Any formalisation of any of the type system
extensions would not need to bother with syntactic details, but can
simply be said to imply ExplicitForall.

I would thus like to propose the following formalisation of the
ExplicitForall extension:

=
ExplicitForall enables the use of the keyword 'forall' to make a type
explicitly polymorphic. Syntactically, it would mean the following
change to Haskell 98:

* 'forall' becomes a reserved word.
* '.' (dot) becomes a special (not reserved) operator.
* The following syntactic rule changes:

type  -> 'forall' tyvars '.' type
   | context '=>' type
   | ftype

ftype -> btype '->' type
   | btype

gendecl   -> vars '::' type

It does not allow the use of explicitly polymorphic types in any way
not already allowed by Haskell 98 for implicitly polymorphic types.
=

One thing to note is that I haven't touched the matter of
ExistentialQuantification in the above. Syntactically this is a
different beast entirely, and could well be handled separately, though
it's really an artifact of the way we (by default) write our data type
declarations. Using GADT-style declarations, existential
quantification goes nicely along with the others by following the same
syntactic rules for types, even though from a type system it is of
course still quite different from the rest. But with the ordinary
Haskell 98 declaration style, we could define the syntactic part of
the ExistentialQuantification extension as the following:

=
ExistentialQuantification allows data constructors to take
existentially quantified arguments. Syntactically, it means the
following changes to Haskell98:

* 'forall' be

Re: Strangeness in the syntax of types

2009-06-18 Thread Niklas Broberg
> You're not looking at the latest version of the code. I'm guessing
> you're looking at the stable version instead of the HEAD.

Indeed, I'm looking at the source distribution for 6.10.3, since
that's the reference version I use to test the files.

>> ctypedoc :: { LHsType RdrName }
>>       : 'forall' tv_bndrs '.' ctypedoc        { LL $ mkExplicitHsForAllTy $2 
>> (noLoc []) $4 }
>>       | context '=>' ctypedoc         { LL $ mkImplicitHsForAllTy   $1 $3 }
>>       -- A type of form (context => type) is an *implicit* HsForAllTy
>>       | ipvar '::' type               { LL (HsPredTy (HsIParam (unLoc $1) 
>> $3)) }
>>       | typedoc                       { $1 }
>
> This should accept both
>
>> multipleCtx :: (Eq a => Show a => a)
>> multipleCtx = undefined
>
> and
>
>> multipleCtx :: Eq a => Show a => a
>> multipleCtx = undefined
>
> The reason why ctypedoc and ctype were so different before, is because
> they drifted apart after ctypedoc was added. ctype was changed (I
> think during implementation of the TypeFamilies extension) without any
> changes to ctypedoc. This was fixed in HEAD not so long ago.

Thanks a lot for the information, then I know. So the correct thing to
do is to put a ctype in the recursive position after the context. I
sorely wish these things were better documented...

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Strangeness in the syntax of types

2009-06-18 Thread Niklas Broberg
Hi all,

I've had a curious bug report [1] for haskell-src-exts, pointing to a
difference in behavior between haskell-src-exts and GHC. Digging
further, it seems to me like GHC is behaving quite strange in this
instance, but since we don't have formal documentation for the
extensions I can't be sure. I'm *almost* convinced this is a bug in
GHC, but with these type extensions I can never be quite sure. Thus
I'm putting it out here in the hope that someone will either explain
why it is this way, or tell me to go file a bug report.

The gist of it is the following piece of code:

> multipleCtx :: Eq a => Show a => a
> multipleCtx = undefined

GHC accepts this code, while haskell-src-exts requires parentheses
around the latter part of the signature, i.e. Eq a => (Show a => a).
The difference is the following productions

haskell-src-exts:
> ctype :: { PType }
>   : 'forall' ktyvars '.' ctype
>   | context '=>' type
>   | type

GHC:
> ctypedoc  :: { LHsType RdrName }
>: 'forall' tv_bndrs '.' ctypedoc
>| context '=>' ctypedoc
>| gentypedoc

Notice GHC's recursive call to ctypedoc after the =>. I have no idea
what the doc suffix on the production is intended to indicate though -
and I was curious to find a separate set of rules that don't have that
suffix:

> ctype :: { LHsType RdrName }
>   : 'forall' tv_bndrs '.' ctype
>   | context '=>' type
>   | type

This one looks just like the one that haskell-src-exts uses - type
instead of ctype after the =>. So what's the difference between the
two in GHC? Looking further, the former is used in top-level type
signatures, while the latter is used for pretty much everything else.
In particular, you can't put a ctypedoc inside parentheses, there you
would have to use ctype. So while GHC accepts the above definition, it
rejects e.g. the (seemingly) equivalent

> multipleCtx :: (Eq a => Show a => a)
> multipleCtx = undefined

My guess would be that there's a bug here, and that it's the recursive
call to ctypedoc that is at fault, it should really be gentypedoc. On
the other hand there's no problem parsing either, so there's no
technical reason not to allow chained contexts without parentheses,
even though I personally think it looks quite awkward.

Enough rambling - can someone make me the wiser?

Cheers,

/Niklas

[1] http://trac.haskell.org/haskell-src-exts/ticket/37
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Three patches for cabal

2009-06-18 Thread Niklas Broberg
> hmm, that's annoying.  Is it feasible for the extensions field to allow both
> addition and subtraction that override compiler defaults?  (How does it work
> in LANGUAGE pragmas -- would NoMonoPatBinds still work in one of them?)

It would only work during the period of deprecation, and would
obviously be discouraged then. You could use OPTIONS_GHC pragmas with
-XNoMonoPatBinds instead though. Why is it annoying specifically?

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Three patches for cabal

2009-06-18 Thread Niklas Broberg
> In general I think there is a reasonable case for special treatment for
> exceptions to H98 that have been accepted for haskell-prime.

I'm not sure I agree with this. I'm not involved in the H' process,
but it was my impression that the general state of affairs was a move
towards a modularization of the standard, so instead of a single
monolithic Haskell' language we would have a series of blessed
addendums like we already have with e.g. the hierarchical module
namespace or FFI. If that's the case then having each of those
addendums enumerated as extensions makes perfect sense to me, at least
until a H' standard (in whatever form) is actually released.

That said, this really have little bearing on the current discussion,
since as you say this particular case won't make it to H' anyway. I
don't really see any good arguments why MonoPatBinds shouldn't be the
listed extension.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: FlexibleContexts and FlexibleInstances

2009-06-10 Thread Niklas Broberg
Hi Claus,

What you describe is exactly how I would *want* things to work. It's
nice to hear my wishes echoed from a user perspective. :-)

On Wed, Jun 10, 2009 at 4:43 PM, Claus Reinke wrote:
> just a few comments from a user (who would really, really, like to be
> able to define pragma collections, so that he doesn't have to switch
> on half a dozen separate extensions every time;-).
>
>> The following toy program requires MultiParamTypeClasses OR
>> FlexibleContexts in order to be accepted by GHC(i):
>>
>>> f :: (T a b) => a -> Int
>>> f _ = 0
>>
>> This of course assumes that we import the definition of T, we *must*
>> have MultiParamTypeClasses enabled if we want to declare T. Both
>> extensions thus enable classes with more than one argument to appear
>> in contexts.
>
> Only MultiParamTypeClasses does (and neither extension is needed in the
> module defining 'f', if 'T' is imported, which suggests that
> MultiParamTypeClasses is propagated to importers - this isn't true for
> most other extensions). The documentation still points to -fglasgow-exts, so
> it doesn't seem to answer these questions..

Right you are - which seems very strange to me. GHC accepts the module
defining 'f' with no flags at all, even though it is clearly not
Haskell 98. I'd go so far as to say that's a bug (as opposed to just
unwanted/unexpected behavior).

>>> f :: (T a ()) => a -> Int
>>> f _ = 0
>>
>> i.e. changing the second argument to T to () instead, means we now
>> *must* have FlexibleInstances, in order to allow the non-tyvar
>> argument. This is nothing surprising, this is what FlexibleInstances
>> are supposed to do.
>
> You mean FlexibleContexts.

Indeed I do.

>> Now, FlexibleInstances *also* lifts the restriction on contexts, just
>> like FlexibleContexts - but *only* for the contexts of instance
>> declarations.
>
> No. FlexibleInstances is about instance *heads*, FlexibleContexts is about
> contexts everywhere (in practice, there are some bugs;-).

Right, this is exactly what I *want* should happen, both as a user and
as an implementor, but that's not how GHC does it. FlexibleInstances
do enable FlexibleContexts for contexts in instance declarations -
which I think is a wart.

>   class T a b -- requires MultiParamTypeClasses   instance T a a -- requires
> FlexibleInstances   instance Eq () => T a [b] -- requires FlexibleContexts
> instance Eq [a] => T a b -- requires UndecidableInstances

Agreed - but here you avoid the tricky cases like my 'f' above. ;-)

What I would want, and what I believe you want as well, is the following:


** MultiParamTypeClasses:

Enables more than one parameter in class declarations, instance heads
and more than one argument to class assertions in contexts everywhere.
Formally, it would mean the following changes to the Haskell 98
syntax:

topdecl ->  class [scontext =>] tycls tyvar1 ... tyvarn
[where cdecls]   (n >=1)
 |   instance [scontext =>] qtycls inst1 ... instn
[where idecls]   (n >=1)

context ->  class
   |   ( class1 , ... , classn )   (n>=0)
class   ->  qtycls cls1 ... clsn(n>=1)
cls   ->  tyvar
   |   ( tyvar atype1 ... atypen )  (n>=1)

scontext->  simpleclass
   |   ( simpleclass1 , ... , simpleclassn )   (n>=0)
simpleclass ->  qtycls scls1 ... sclsn(n>=1)
scls   ->  tyvar


** FlexibleContexts:

Enables the use of non-tyvar (or tyvar applied to types) arguments to
class assertions in contexts everywhere (orthogonal to whether there
can be several arguments or just one). Formally it means the following
syntactic changes to Haskell 98:

fcontext->  fclass
   |   ( fclass1 , ... , fclassn ) (n>=0)
fclass  ->  qtycls atype1 ... atypen  (n>=1)

topdecl ->  data [fcontext =>] simpletype = constrs [deriving]
|   newtype [fcontext =>] simpletype = newconstr [deriving]
|   class [fcontext =>] tycls tyvar [where cdecls]
|   instance [fcontext =>] qtycls inst [where idecls]

gendecl ->  vars :: [fcontext =>] type

for the single-argument case. (Note that I wrote type in my proposal
in the OP, but it should of course be atype.)


** FlexibleInstances:

Enables the use of arguments other than type constructors (possibly
applied to tyvars) in instances *heads* (orthogonal to whether there
can be one or more arguments, and what the context may look like).
Formally it means the following syntactic changes to Haskell 98:

topdecl ->  instance [scontext =>] qtycls inst [where idecls]
inst   ->  atype

for the single-parameter standard-context case. (Note again that it
should be atype and not type as I wrote in the OP.)


This of course only touches the syntactic part. It doesn't attempt to
track things like 'instance (T a a) => R a b' that wou

FlexibleContexts and FlexibleInstances

2009-06-09 Thread Niklas Broberg
Dear all,

This post is partly a gripe about how poor the formal documentation
for various GHC extensions is, partly a gripe about how GHC blurs the
lines between syntactic and type-level issues as well as between
various extensions, and partly a gripe about how the Haskell 98 report
is sometimes similarly blurred where syntax is concerned (or not). All
these things make the life of a poor parser implementor quite
miserable at times. All in good jest of course, but with an edge of
truth, especially regarding (lack of) formal documentation.

The issue at hand which has caused my frustration is the
FlexibleContexts [1] and FlexibleInstances [2] extensions, which lift
restrictions imposed by Haskell 98 on the forms of contexts and
instances that may be defined. Great extensions both of them - but
what do they do, really really?

The following toy program requires MultiParamTypeClasses OR
FlexibleContexts in order to be accepted by GHC(i):

> f :: (T a b) => a -> Int
> f _ = 0

This of course assumes that we import the definition of T, we *must*
have MultiParamTypeClasses enabled if we want to declare T. Both
extensions thus enable classes with more than one argument to appear
in contexts.

Changing the program to

> f :: (T a ()) => a -> Int
> f _ = 0

i.e. changing the second argument to T to () instead, means we now
*must* have FlexibleInstances, in order to allow the non-tyvar
argument. This is nothing surprising, this is what FlexibleInstances
are supposed to do. But the question is, is this a syntactic issue or
a typing issue? In GHC proper this doesn't really matter much, as long
as it is caught *somewhere* then all is dandy. GHC's parser lets
everything pass, and it's the type checker that balks at this program.
But for someone like me with *only* a parser, this is a question that
needs a clear answer. Looking at the online report, the productions
regarding contexts are

context ->  class
|   ( class1 , ... , classn )   (n>=0)
class   ->  qtycls tyvar
|   qtycls ( tyvar atype1 ... atypen )  (n>=1)
qtycls  ->  [ modid . ] tycls
tycls   ->  conid
tyvar   ->  varid

Ok, so clearly the () is a syntactic extension enabled by
FlexibleContexts, as it is not a tyvar nor a tyvar applied to a
sequence of types. So this is something that a parser should handle.
FlexibleContexts also enables similar parses of contexts in other
places, for instance in class declarations, for which the Haskell 98
report says

topdecl ->  class [scontext =>] tycls tyvar [where cdecls]
scontext->  simpleclass
|   ( simpleclass1 , ... , simpleclassn )   (n>=0)
simpleclass ->  qtycls tyvar

The difference here is that the simpleclass doesn't allow the tyvar
applied to a sequence of types bit. FlexibleContexts lifts that
restriction too, so there should be no difference between the two
kinds of contexts. So the new formal productions for flexible contexts
should be something like

fcontext->  fclass
|   ( fclass1 , ... , fclassn ) (n>=0)
fclass  ->  qtycls type1 ... typen  (n>=1)

topdecl ->  data [fcontext =>] simpletype = constrs [deriving]
|   newtype [fcontext =>] simpletype = newconstr [deriving]
|   class [fcontext =>] tycls tyvar [where cdecls]
|   instance [fcontext =>] qtycls inst [where idecls]

gendecl ->  vars :: [fcontext =>] type

Does this seem correct?

Now let's turn to FlexibleInstances, which similarly lifts
restrictions, only to instance declarations instead of contexts. The
Haskell 98 report says on instance declarations:

topdecl ->  instance [scontext =>] qtycls inst [where idecls]
inst->  gtycon
|   ( gtycon tyvar1 ... tyvark )(k>=0, tyvars distinct)
|   ( tyvar1 , ... , tyvark )   (k>=2, tyvars distinct)
|   [ tyvar ]
|   ( tyvar1 -> tyvar2 )(tyvar1 and tyvar2 distinct)

Note the re-appearance of scontext, which is the same as above. The
instance head must be a type constructor, possibly applied to a number
of type variables, or one of three built-in syntactic cases. This is
where I consider the Haskell 98 report blurry - the fact that the
tyvars must be distinct, is that truly a syntactic issue? It might be,
it's certainly something that could be checked syntactically. But when
you take into account that with the proper extensions, they no longer
need to be distinct, at what level would we expect such a check to
happen? My gut feeling is that this check for distinctness is
something that a type checker might do better than a parser, though
it's not clear cut by any means. But since I don't do any other kind
of name resolution or checking in my parser even if it would be
possible (e.g. multiple declarations of the same symbol), I would find
it a bit anomalous to check this too.

Turning on FlexibleInstances, we shouldn't need to follo

Re: Three patches for cabal

2009-06-03 Thread Niklas Broberg
> It's called TransformListComp because the "then f" syntax transforms a
> list using f (which has type [a] -> [a]) - not because the
> implementation works by transformation or anything like that! We
> considered but rejected GeneralizedListComp because it's too vague -
> what if someone comes up with another list comprehension
> generalisation in the future?

I see, my mistake in interpreting the naming.

However, I really don't agree this is a good choice. This feature is
documented and refered to all over the place as general(ised) list
comprehension, whereas a google search for either of the terms
"transform list comprehension" or "tranformation list comprehension",
with quotes, returns zilch (and without quotes returns nothing
Haskellish). It seems clear to me that we need to either do the change
I propose, which I think goes best with the principle of least
surprise, or rewrite the GHC documentation at the very least.

I can agree that generalised list comprehension could be a bit too
vague to be future sensitive - but I'd rather cross that bridge when
we get there!

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Three patches for cabal

2009-06-03 Thread Niklas Broberg
(Trying again since my previous patches were too big for the list.)

While doing a survey[1] of the extensions registered with Cabal, I
came across two warts in the list of constructors, and one constructor
that should be deprecated.

First there's the constructor called TransformListComp, which should
really be named GeneralizedListComp, since the constructor should
describe the extension and not the implementation scheme.

Second there's the constructor NoMonoPatBinds, which actually
describes the default Haskell 98 behavior, even if GHC has a different
default. It's GHC's behavior that is the extension, so the constructor
in cabal should really be named MonoPatBinds.

Also, the PatternSignatures constructor has been deprecated in GHC and
superceded by ScopedTypeVariables.

The attached patches (three in one file) adds the proposed new
constructors, deprecates the old ones, and adds documentation.

Cheers,

/Niklas


GeneralizedListComp-et-al.dpatch
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Choosing implementation depending on class instances using rewriting rules

2009-06-03 Thread Niklas Broberg
Hi Milan,

> Is there a way to write such a rewriting rule or there is no way of acquiring
> the Ord dictionary in rewrite rule? Or does anyone know any other way
> of implementing such a nub without explicitly listing all Ord instances?

Have a look at http://okmij.org/ftp/Haskell/types.html#class-based-dispatch

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Illegal type synonym family application in instance (Was: Breakage with 6.10)

2008-10-11 Thread Niklas Broberg
On 10/11/08, Niklas Broberg <[EMAIL PROTECTED]> wrote:
> dons:
>  >  A breakdown of the remaing causes for DependencyFailed,
>  >   [...]
>  >   4 hsx-0.4.4

New version uploaded that works with both 6.8.3 and 6.10 rc1 (through
dark cpp magic). I doubt I need to show this trick to anyone else
since I seem to have been the only one brave/foolish enough to depend
on this quirk of type families in 6.8. I'm proud to say I'm off the
list now anyway. :-)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: syb changes (Re: base-3 vs base-4 (Was: Breakage with 6.10))

2008-10-11 Thread Niklas Broberg
>  So there is a compatibility module in the new syb. Unfortunately,
>  that won't tell you about the moves and rationale. Most of the time,
>  you'll want Data.Data (check "ghc -e ':browse Data.Data'" or the
>  Haddock pages, or google for "syb" in the libraries@ archives):
>
>$ ghc-pkg find-module Data.Data
>c:/ghc/ghc-6.11.20081004\package.conf:
>base-4.0.0.0

Thanks a lot Claus and José for the info. Since all I use is the Data
and Typeable classes (presumably like so many others, which I guess
was the reason to keep these in base), it would obviously be better
for me to avoid linking to the new syb package when I don't have to.

>$ ghc -ignore-dot-ghci -e ':info Data.Data.Data'

Somehow I find this name hilarious. :-)

> > .. I would prefer to use the new
> > base-4 when possible. The cabal file already includes a conditional
> > "if flag(splitBase)" to handle really old versions, I guess what I'm
> > asking for is something similar for this case. Is there a splitSyb
> > flag or some such?
> >
>
>  I was wondering whether there is a way to set user-defined flags
>  depending on whether some package is available. Then I recalled
>  that flags don't work the way I expected - instead Cabal will try
>  all flag settings to find a buildable configuration (a fact I only became
>  aware of when a different kind of flag was added recently that does
>  behave the way I expected;-). Which might be what you want in this case.
> Duncan: is this correct, and are these subtleties documented somewhere?

While these things would be good to know in general, it seems this is
not what I want in this case, since I don't want to use the syb
package after all. It seems instead what I want is to simply make a
conditional import of either Data.Generics or Data.Data based on which
version of base is available. I guess that means more CPP heresy,
sigh.

Thanks,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Illegal type synonym family application in instance (Was: Breakage with 6.10)

2008-10-10 Thread Niklas Broberg
On 10/11/08, David Menendez <[EMAIL PROTECTED]> wrote:
> On Fri, Oct 10, 2008 at 8:40 PM, Niklas Broberg
>  <[EMAIL PROTECTED]> wrote:
>  > src\HSX\XMLGenerator.hs:71:0
>  >Illegal type synonym family application in instance: XML m
>  >In the instance declaration for `EmbedAsChild m (XML m)´
>  > ---
>  >
>  > Could someone help me point out the problem here? The relevant code is:
>  >
>  > instance XMLGen m => EmbedAsChild m (XML m) where
>  >  asChild = return . return . xmlToChild
>  >
>  > class XMLGen m => EmbedAsChild m c where
>  >  asChild :: c -> GenChildList m
>  >
>  > class Monad m => XMLGen m where
>  >  type XML m
>  >  
>  >
>  > This works fine with 6.8.3, so what's new in 6.10, and what would I do
>  > to solve it?
>
>
> I'm guessing there was a bug in 6.8.3 that allowed this. (The
>  implementation of type families is present but not supported in 6.8,
>  presumably because of problems like this.)
>
>  I don't have 6.10, so I can't test anything, but you might try
>  rewriting the EmbedAsChild instances like so:
>
> instance (XMLGen m, XML m ~ x) => EmbedAsChild m x where ...

Thanks a lot David, that's indeed what I needed.

I'm not sure I see why the style I used previously was illegal though,
it seemed perfectly natural to me. And it works that way for
`EmbedAsChild m (Child m)´, where `Child m´ is a data type family and
not a synonym, so why not for a synonym too? But hey, as long as
there's a way to do what I want. :-)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


base-3 vs base-4 (Was: Breakage with 6.10)

2008-10-10 Thread Niklas Broberg
>  > Btw, I also have problems with the haskell-src-exts that imports
>  > Data.Generics.Instances (to generate Data and Typeable instances).
>  > Where would these have moved to in the new base? And how would I make
>  > the code work with both 6.8.3 and 6.10?
>
> By having it use base-3 rather than 4.

Right, and that's how I quickly fixed it up for now. But this doesn't
sound like a long-term solution to me, I would prefer to use the new
base-4 when possible. The cabal file already includes a conditional
"if flag(splitBase)" to handle really old versions, I guess what I'm
asking for is something similar for this case. Is there a splitSyb
flag or some such?

Though obviously this would only work if the module
Data.Generics.Instances was preserved under that name somewhere else.
If it was renamed or changed (which I suspect), then the hassle of
keeping up to date with older versions will probably be too much, and
I will want to update to the new agenda as soon as 6.10 is released
for real. So what happened to this module? (Is there a migration
quicksheet somewhere?)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Illegal type synonym family application in instance (Was: Breakage with 6.10)

2008-10-10 Thread Niklas Broberg
>  Could someone help me point out the problem here? The relevant code is:
>
>  instance XMLGen m => EmbedAsChild m (XML m) where
>   asChild = return . return . xmlToChild
>
>  class XMLGen m => EmbedAsChild m c where
>   asChild :: c -> GenChildList m
>
>  class Monad m => XMLGen m where
>   type XML m
>   

Eh, reading that again I realize there's a bit code needed to
understand the above. So here's *really* the relevant code:


class Monad m => XMLGen m where
 type XML m
 data Child m
 xmlToChild :: XML m -> Child m
 []

class XMLGen m => EmbedAsChild m c where
 asChild :: c -> GenChildList m

instance XMLGen m => EmbedAsChild m (XML m) where
 asChild = return . return . xmlToChild


... and just a note that GenChildList is a type synonym for a certain
monad returning a list, hence the double returns. :-)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Illegal type synonym family application in instance (Was: Breakage with 6.10)

2008-10-10 Thread Niklas Broberg
dons:
>  A breakdown of the remaing causes for DependencyFailed,
>   [...]
>   4 hsx-0.4.4

---
src/hsx$ runhaskell Setup build
[snip warnings]

src\HSX\XMLGenerator.hs:71:0
Illegal type synonym family application in instance: XML m
In the instance declaration for `EmbedAsChild m (XML m)´
---

Could someone help me point out the problem here? The relevant code is:

instance XMLGen m => EmbedAsChild m (XML m) where
 asChild = return . return . xmlToChild

class XMLGen m => EmbedAsChild m c where
 asChild :: c -> GenChildList m

class Monad m => XMLGen m where
 type XML m
 

This works fine with 6.8.3, so what's new in 6.10, and what would I do
to solve it?


Btw, I also have problems with the haskell-src-exts that imports
Data.Generics.Instances (to generate Data and Typeable instances).
Where would these have moved to in the new base? And how would I make
the code work with both 6.8.3 and 6.10?

Thanks,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Haskell-src-ext

2008-04-14 Thread Niklas Broberg
> > Except for line numbering (it inserts but doesn't read line pragmas),
> > the AST should be preserved under f = parse . pretty.
>
>  and what about (pretty . parse) = id :: String -> String ?-)

Most certainly not I'm afraid. It doesn't handle pragmas at all
(treats them as comments), and by default it inserts line pragmas in
the output (though that can be turned off). Comments are simply
discarded, and to be honest I really don't see how they could be kept
in general, except in specific pre-defined places (like for Haddock).
I'm sure you have ideas on that though. Layout is also not preserved
exactly, and do { ... ; ... } results in the same AST as if done with
layout instead of { ; }.

>  preserving everything that isn't transformed at the AST level
>  would be a necessary starting point for refactoring larger
>  code bases. having easy access to comments and layout
>  information is where most frontends tend to let us down.

Indeed, and I'm afraid haskell-src-exts will join the crowd in that
regard. But to be honest I'm not sure haskell-src-exts *should* do
those things you ask for, since the added machinery would be rather
heavy-weight for applications that just want the basic stuff, which I
guess is the vast majority of applications.

>  ps it is good to hear that src-ext is supported, follows language
> developments, and is separated from the other parts of your
> projects!-)

Thanks, and yes I try to keep them as separate as possible, knowing
their usefulness to others.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Haskell-src-ext

2008-04-14 Thread Niklas Broberg
>  Does your pretty-printer round trip?

Absolutely. I'd think a parser that can't parse what the
pretty-printer yields means you either have a broken parser or a
broken pretty-printer. :-)

Except for line numbering (it inserts but doesn't read line pragmas),
the AST should be preserved under f = parse . pretty.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Haskell-src-ext

2008-04-14 Thread Niklas Broberg
>  Hi Niklas,
>  nice to meet you.

Likewise. :-)

>  I'm planning to extend shim to get a more featured ide (vim / emacs..
>  Maybe the Eclipse supporters do join as well?)
>
>  One thing I'd like to add is adding modules/ import statements to a
>  module.
>  Do you think your' parsers / resulting abstract syntax tree is suited
>  to add some import statements? Or do you suggest hacking my own fuzzy
>  approach?

I'd say that's definitely a good use of  haskell-src-exts, and very
easy to accomplish. A fuzzy approach sounds scary to me. ;-)

>  Is it easy to explain the main difference between your output and the
>  output produced by the GHC parser?

I'd say the most striking difference is that the AST used by
haskell-src-exts is much much simpler than the GHC one. It's only an
AST, it doesn't try to cater to the different passes of a compiler to
do renaming or any such nonsense. It is also contained in a single
module so it is easy to reference (try digging up where some specific
constructor in the GHC AST is defined and you'll appreciate the merit
of this).

For any project that just needs to parse/fiddle with/print haskell
source code, I see very little reason to choose GHC API instead of
haskell-src-exts. The only reason is of course that GHC API is
guaranteed to be up to date with the latest GHC, and will be able to
parse exactly everything that GHC does. On the other hand,
haskell-src-exts allows you to handle regular patterns and literal XML
syntax a la HSP, which GHC doesn't. :-)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC API (parsing)

2008-04-14 Thread Niklas Broberg
>  * it's not exactly a drop-in replacement for Language.Haskell.* ?
>   (HsNewTypeDecl is different?)
>
>  *  for the others, number of constructor arguments does not match, e.g.
>`HsConDecl' should have 2 arguments, but has been given 3

Indeed it is like you say, these are pragmatic choices. The extensions
introduce new requirements, and the choice was between modelling only
the general case, or separating the H98 case and the extension as two
different constructors. I chose the former, since I believe anyone
using this library would want to use the extensions anyway, and
choosing the latter would have meant a lot of extra boilerplate code
(for the user, not me).

>  * how is your parser tied to ghc?
>   I.e. what happens if the next ghc release introduces new syntax?

It is not at all tied to ghc, other than that I try to keep up with
the major extensions that ghc provides. There are some things in ghc
that my library does not model, e.g. arrows syntax (patches welcome!).
But if there's anything specific that you need that isn't already in
there, drop me a feature request and I'll try to fix it for you.

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC API (parsing)

2008-04-14 Thread Niklas Broberg
>  how can I convince the Language.Haskell.Parser to accept "GHC Haskell"
>  (i.e., -fglasgow-exts, e.g. for existential types)

You use my haskell-src-exts package instead. :-)

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/haskell-src-exts-0.3.3

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Inconsistent .hi files with associated types?

2008-03-23 Thread Niklas Broberg
Hi all,

I'm getting a weird warning/error message from GHC that I don't understand:

=
$ runhaskell Setup build
Preprocessing library hsp-hjscript-0.3.4...
Building hsp-hjscript-0.3.4...
[1 of 1] Compiling HSP.HJScript ( HSP/HJScript.hs,
dist\build/HSP/HJScript.o )
C:\Program\Haskell\hsp-0.3.5\ghc-6.8.2/HSP/Monad.hi
Declaration for $f35
Unfolding of HSP.Monad.$f35:
  Can't find interface-file declaration for type constructor or class
HSP.Monad.:CoF:R32XML
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error
C:\Program\Haskell\hsp-0.3.5\ghc-6.8.2/HSP/Monad.hi
Declaration for $f6
Unfolding of HSP.Monad.$f6:
  Can't find interface-file declaration for type constructor or class
HSP.Monad.:CoF:R5SetResult
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error

C:\Program\ghc-6.8.2\bin\ar.exe: creating dist\build\libHShsp-hjscript-0.3.4.a
=

Can anyone explain to me what's up here?

I have no .hi-boot files., and -ddump-if-trace gives no further info.

Both XML and SetResult are associated types. Both of the instances in
question are defined in a different package, which compiles without
error. The classes that define the types are in yet another package,
which also compiles without error.

I note that the compilation of the package continues, so I suppose
these are error messages only, even though they sound quite fatal. But
what effect will this have on programs using the module?

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bug or not-yet-supported?

2008-03-17 Thread Niklas Broberg
> It is supposed to work in 6.9.  I am sorry, but type families are not
>  an officially supported feature in 6.8.x, and hence, any bug fixes
>  that requires invasive changes in the type checker will not be merged
>  into the 6.8 branch (and by now the 6.8 and 6.9 code bases diverged
>  quite a bit).  This is simply to ensure the stability of the stable
>  branch.  Type families will be properly supported in 6.10.

Oh, no worries, I'm in no hurry. I just wanted to know if this was
something you were helped by knowing, but I suspected it was just as
you say here. So I won't bother about a bug report, and will eagerly
await 6.10. :-)

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Bug or not-yet-supported?

2008-03-16 Thread Niklas Broberg
I haven't payed much attention to how much of type families is/should
be implemented for 6.8.2. What of equality constraints? The following
parses alright, but can't be used it seems.


module Foo where

class C a where
 proof :: a

instance (a ~ Int) => C a where
 proof = 1


%> ghci -fglasgow-exts -XUndecidableInstances Foo.hs
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling Foo  ( Foo.hs, interpreted )
Ok, modules loaded: Foo.
*Foo> proof :: Int
: panic! (the 'impossible' happened)
  (GHC version 6.8.2 for i386-unknown-mingw32):
nameModule $dC{v aoz}

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug


I would follow that last advice if I knew this was *supposed* to work. :-)

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Weird bug with FDs

2006-07-06 Thread Niklas Broberg

I encounter a strange behavior with functional dependencies. Assume we
have a class defined as

class Foo x y | x -> y where
foo :: x -> y

and another class

class Bar x y where
bar :: x -> y -> Int

and I want to write the instance declaration

instance (Foo x y, Bar y z) => Bar x z where
bar x z = bar (foo x) z

Compiling (with 6.4.2, -fallow-undecidable-instances and
-fglasgow-exts) I get the following error message:

Foo.hs:12:0:
   Context reduction stack overflow; size = 21
   Use -fcontext-stack20 to increase stack size to (e.g.) 20
   `$dBar :: Bar y z' arising from use of `bar' at Foo.hs:13:11-13
   [... same thing 20 times ...]
   `$dBar :: Bar y z' arising from use of `bar' at Foo.hs:13:11-13
   `bar :: {bar at [y z]}' arising from use of `bar' at Foo.hs:13:11-13
   When trying to generalise the type inferred for `bar'
 Signature type: forall x y z. (Foo x y, Bar y z) => x -> z -> Int
 Type to generalise: x -> z -> Int
   In the instance declaration for `Bar x z'


The declaration requires undecidable instances, but I doubt that the
problem comes from that. What makes it even more weird is that I can
get this to compile, and behave as expected, if I do one of a) declare
an instance of Bar for any type, or b) add an explicit type signature
(foo x :: y) in the definition of Bar. The first seems weird since how
could a different, unrelated instance affect the typeability of the
second instance? The second, b), is weird since by the FD x -> y we
should already know that foo x :: y.

GHC 6.4.1 shows the same behavior. Hugs (with -98 +O) accepts the code.

I've submitted a trac ticket, but it would be interesting to hear if
anyone has an explanation to this? :-)

Thanks,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Re: Packages and modules

2006-07-05 Thread Niklas Broberg

So here are some options:

   1. the proposal as it is now, keeping exposed/hidden state in the
  package database, don't support "available"

   2. Add support for "available".  Cons: yet more complexity!

   3. Drop the notion of exposed/hidden, all packages are "available".
  (except for base?).  Cons: lots more typing, very
  non-backwards-compatible, still have to list dependencies in
  .cabal files.

anyone have any more suggestions?  Is there any way to simplify?  I
rather feel this design is getting a little unwieldy.


Maybe a dumb question, but why not support only exposed and available?
Why have hidden modules that cannot be used, even when the programmer
explicitly asks for them?

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Deducing Show for GADTs

2006-06-28 Thread Niklas Broberg

On 6/28/06, David Roundy <[EMAIL PROTECTED]> wrote:

On Wed, Jun 28, 2006 at 11:52:51AM +0200, Joel Bjrnson wrote:
> Hi. I came a cross the following phenomena which, at least to me,
> occurs kind of awkward. The code below:
>
> data MyData a  where
>  DC1 :: (Show a ) => a -> MyData a

GADTs don't yet work right with classes.  :( The above, however,
doesn't need to be expressed as a GADT, I believe you can write
something like:

data MyData a = (forall a. Show a) => DC1 a

which (this is untested) should do what you want.


Only if "what he wants" is something that type checks, but doesn't do
the same thing. ;-)
In Joel's definition of MyData, values constructed with DC1 applied to
a value of type b will have type MyData b. In your definition they
will have type MyData a, for any a. In other words, your definition
would be identical to the GADT

data MyData a where
DC1 :: forall a b . (Show b) => b -> MyData a


As to Joel's question, this seems really really weird. In particular
since adding the completely useless wrapper type solves the problem.
In fact, giving DC1 any return type other than MyData a solves the
problem. This has to be a bug of some sort.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Error when ($) is used, but no error without

2006-04-26 Thread Niklas Broberg
On 4/27/06, Robin Bate Boerop <[EMAIL PROTECTED]> wrote:
> But, this code:
>
> class CC a
> type C x = CC a => a x
> f, g :: C a -> Int
> f _ = 3
> g x = f $ x  -- the only change

The problem is exactly the use of $. $ is an operator, not a built-in
language construct, and it has type (a -> b) -> a -> b. No forall's in
there, so you cannot give it a function argument that is existentially
quantified. Lots of people have been bitten by this when using the
magic runST with type "forall a. (forall s. ST s a) -> a".
Use parentheses when you have existentially quantified values and
everything should be just fine. :-)

/Niklas


>
> gives this error:
>
>  Inferred type is less polymorphic than expected
>Quantified type variable `a' escapes
>Expected type: a a1 -> b
>Inferred type: C a1 -> Int
>  In the first argument of `($)', namely `f'
>  In the definition of `g': g x = f $ x
>
> What's going on here?
>
> --
> Robin Bate Boerop
>
>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Default name of target executable

2005-10-10 Thread Niklas Broberg
> Why don't you use a small shell script for this?

These kinds of answers are all too abundant, no offense meant. :-)
There are lots of things that *can* be done already, that doesn't mean
that we can't improve them!

Using a shell script is a possible work-around, but certainly not
*the* solution. If there is no real reason for ghc to spit out a.out
files, then surely choosing the exe name from the main input file
would simplify a programmer's life. And for applications that
desperately want a.out, well, there's still the -o flag, right?

I second Tomasz suggestion.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


problems building trhsx-0.2 with ghc-6.5.20050723

2005-08-04 Thread Niklas Broberg
> Cabal hides all packages when using GHC 6.5. Add 'base' to
> build-depends in trhsx's cabal file and send a patch to the author.

Lemmih has it right, I haven't gone over and fixed this in my
packages. I guess I should...
Vadim, thanks for the patch.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: runghc badly broken

2005-04-18 Thread Niklas Broberg
> I'm trying to use runghc (6.4 release version, redhat linux), but it
> appears to be badly broken. It only processes the first argument given
> to it...
[snip]

As a friend pointed out to me, some of this behavior may not be so
strange. Clearly, if you give arguments _after_ the specified source
file, you expect these to be arguments to that source file and not to
runghc itself. Thus the example
---
> runghc Foo.hs -v1
hello
---

executes as expected, since Foo.hs makes no use of -v1. That leaves
the other case, when the argument(s) is given _before_ the file
argument. It's obviously possible to give flags to runghc, shown by
runghc being verbose in the example
---
> runghc -v1 Foo.hs
Loading package base-1.0 ... linking ... done.

:1:78:
   Failed to load interface for `Main':
   Could not find module `Main':
 it is not a module in the current program, or in any known package.
Leaving GHCi.
---

but only the first one is processed. IMHO the preferred behavior is
that any arguments given before the single file argument is given to
runghc itself, while any given after the file argument is given to the
script in that file. Comments?

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HOME: getEnv: does not exist

2005-04-18 Thread Niklas Broberg
> > when I try to use runghc to execute cgi scripts in apache (on redhat
> > linux), they all fail with with the message "HOME: getEnv: does not
> > exist". I assume this means that GHC is trying to find the HOME dir of
> > the user for some reason, and fails since apache runs as nobody. Could
> > someone shed some light on this matter for me?
> 
> The same seems to be the case with ghc itself, not only runghc. Giving
> the flags -ignore-dot-ghci and -no-user-package-conf does not solve
> the problem, I still get the same error.

Alright, after digging the the ghc source I found this to be a bug
that has been remedied in the current cvs HEAD. I guess it remains for
me to install a cvs version then.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HOME: getEnv: does not exist

2005-04-18 Thread Niklas Broberg
> when I try to use runghc to execute cgi scripts in apache (on redhat
> linux), they all fail with with the message "HOME: getEnv: does not
> exist". I assume this means that GHC is trying to find the HOME dir of
> the user for some reason, and fails since apache runs as nobody. Could
> someone shed some light on this matter for me?

The same seems to be the case with ghc itself, not only runghc. Giving
the flags -ignore-dot-ghci and -no-user-package-conf does not solve
the problem, I still get the same error.

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HOME: getEnv: does not exist

2005-04-18 Thread Niklas Broberg
> I think runghc is acting like GHCi, and trying to read the file
> $HOME/.ghci on startup.

Thanks, that may well be the case. Too bad you can't tell it not to,
see my other post about runghc and flags. :-(

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


runghc badly broken

2005-04-18 Thread Niklas Broberg
Hi all,

I'm trying to use runghc (6.4 release version, redhat linux), but it
appears to be badly broken. It only processes the first argument given
to it, so while
---
> runghc Foo.hs
hello

with Foo.hs being simply
main = putStrLn "hello"
---

works just fine, while for instance
---
> runghc -v1 Foo.hs
Loading package base-1.0 ... linking ... done.

:1:78:
Failed to load interface for `Main':
Could not find module `Main':
  it is not a module in the current program, or in any known package.
Leaving GHCi.
---

manages to be 1-verbose but doesn't find the file, and
---
> runghc Foo.hs -v1
hello
---

executes the file alright, but forgets verbosity. I can't imagine this
is the intended behavior?

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


HOME: getEnv: does not exist

2005-04-18 Thread Niklas Broberg
Hi all,

when I try to use runghc to execute cgi scripts in apache (on redhat
linux), they all fail with with the message "HOME: getEnv: does not
exist". I assume this means that GHC is trying to find the HOME dir of
the user for some reason, and fails since apache runs as nobody. Could
someone shed some light on this matter for me?

#!/usr/bin/runghc
main = do putStrLn "Content-type: application/xhtml"
  putStrLn "Content-length: 5\n"
  putStrLn "Hello"

Thanks,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Dynamic Source Loading

2004-10-26 Thread Niklas Broberg
> Please look at hs-plugins:
>http://www.cse.unsw.edu.au/~dons/hs-plugins
> 
> and the accompanying paper:
>http://www.cse.unsw.edu.au/~dons/hs-plugins/paper
> 
> hs-plugins is already being used at Chalmers for their Haskell Server
> Pages project, which sounds a lot like what you're describing. You can
> ask Niklas Broberg about this.

Indeed, we have a working server that does runtime loading of HSP
pages (i.e. Haskell apps) using hs-plugins. We'll be releasing a first
version some time really soon, but if you want a preview just send me
a mail. =)

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


Re: setCurrentDirectory and lightweight threads

2004-10-24 Thread Niklas Broberg
> > What I mean is that if one page wants to change directory using
> > setCurrentDirectory, this change affects all other (lightweight)
> > threads as well, which is not how "ordinary" system threads works.
> 
> AFAIK, this _is_ how "ordinary" system threads work. 

Hmm, I guess was confused (and is still) by the distinction between
threads and processes. The following quote comes from one of your
links:

  The current working directory is shared between all threads within the same
  process. Therefore, one thread using the chdir() or fchdir() functions
  will affect every other thread in that process.

So that means you're right, and that the current directory shouldn't
be tampered with in a multithreaded setting. I still don't understand
*why* it is like this on the OS level, but I'm not going to opt for a
change there. ;o)

I guess that leaves me to implement a add layer on top of IO that can
handle "directory state" of different threads. Oh well. =)

Thanks for the answer,

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


setCurrentDirectory and lightweight threads

2004-10-23 Thread Niklas Broberg
Hello fellow Haskelleers,

I've come upon a problem that sort of bites me. 
I'm writing a multithreaded webserver in which pages are dynamically
loaded haskell applications. The main server loop listens for incoming
requests and distributes these to request handlers, each running in a
separate lightweight thread.

Now, some of the most common operations used in dynamic web pages
relate to directory listing/manipulation. I was happily thinking that
System.Directory would provide the needed functionality. Indeed it
does, but unfortunately setCurrentDirectory breaks the thread
abstraction.
What I mean is that if one page wants to change directory using
setCurrentDirectory, this change affects all other (lightweight)
threads as well, which is not how "ordinary" system threads works.
Also it is clearly not what one would want in the kind of application
I'm writing.

Is this behavior of setCurrentDirectory intended? I can't see a
situation in which you could take advantage of it, but that doesn't
mean there can't be any. =)

If it is not intended, is there any hope of it being "fixed"? 

Regards,

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


RE: URI Typeable & Data

2004-09-16 Thread Niklas Broberg
Could we possibly have derived instances of Typeable and Data for
Network.URI.URI in the 6.3 CVS please?
I second this request, and also ask for an instance of Typeable for 
Control.Concurrent.MVar (and the other Control.Concurrent types as well).

/Niklas
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

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


Re: Prelude/main magicks?

2004-05-19 Thread Niklas Broberg
I wrote:
> Taking Lava, a hardware description language, as my example, I would 
argue
> that many users of Lava don't really care if it's embedded in Haskell or
> whereever it comes from, they would just use it.   
>
> 	lavac Main.hs
>
> where lavac is could simply be a script alias of
> 	ghc -fprelude-is Lava
>
> By using an explicit Lava compiler you declare that this is indeed a 
Lava
> program, and you don't expect it to work in any other setting, in 
particular
> not with a Haskell compiler like GHC.
>
> And in the same line of thinking, I would want a way of specifying 
suffixes
> of input source files. It would be much neater to call your files 
Foo.lava
> or similar, and be able to tell GHC to treat them as normal .hs files, 
i.e.
>
> 	lavac <== ghc -hssuf lava -fprelude-is Lava

Malcolm Wallace wrote:
Very intriguing ideas.  However, I'm sure there are easier ways
of implementing a 'lavac' (or other domain-specific compiler) than
adding new flags to ghc (and by implication, to every other Haskell
compiler as well).
All you really need is to hook up a rather simple pre-processor.
For instance,
#!/bin/sh
{ echo 'module Main where\nimport Lava\n' ; cat $1 } >`basename $1 
.lava`.hs

If you want an automatic file association based on suffix, then
something like hmake can do the mapping of .lava onto .hs via this
little pre-processor script.  This solution has the additional benefit
that it is compiler-agnostic.
Aye, it would be simpler, I sure won't argue that.
But then I might have to create another pre-processor to make it work on 
Windows, and a third for some other system. And then for the next EDSL that 
comes up, the designer of that will have to do the same thing. Is the sum of 
all that work still simpler?
Clearly it would be better for the EDSL designer to know that someone else 
has thought of these things once and for all. I'd like to see my approach as 
the high-level one where the designer just has to think about _what_ he 
wants, whereas your suggestion would be the low-level approach where the 
designer must also know _how_ to get what he wants.

From my perspective what it comes down to is, is this a recurring pattern? 
If a new EDSL comes around once in a blue moon, then one might argue that 
the work needed to add these flags to GHC would be ill-spent. But if EDSLs 
are a more common development pattern, then surely it must be the supreme 
goal of any compiler writer to make life easier on the users? =)
And if we think one step ahead, then it isn't all that difficult to imagine 
that such a feature might even encourage the design of more EDSLs, which in 
my book would be a Really Good Thing (tm).

As for being compiler agnostic, then sure, that would be a good thing for 
any library.
But there are already tons of nice extensions added to GHC that aren't 
implemented by other compilers, making any code that makes use of these 
extensions compiler-specific. Why would this be different?
And as for those users of Lava I mentioned in my example, I doubt that they 
would even know of or care about the existence of other compilers and/or 
interpreters than the one(s) the language designer provides them with. After 
all, from their perspective those other tools are for Haskell, not Lava!
That said, I sure wouldn't mind seeing these features added to other 
compilers as well. =)

I could even volunteer to try to add these features to GHC, if the team 
would accept the help. There are still the issues of update-compatibility 
for the team to deal with, but I stubbornly believe that they won't be that 
bad. ;)

I'm starting to get a bit worried though, am I completely alone in this? I 
would have thought at least someone would agree with me and support me in 
wanting such features, so please, anyone? =)

/Niklas
_
MSN Toolbar provides one-click access to Hotmail from any Web page – FREE 
download! http://toolbar.msn.click-url.com/go/onm00200413ave/direct/01/

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


RE: Prelude/main magicks?

2004-05-14 Thread Niklas Broberg
I wrote:
| Is there some simple way to make GHC treat our own base library in the
same
| magic way as the Prelude, so that it is always implicitly available?
[...]

Simon Peyton-Jones wrote:
A -fprelude-is flag would certainly be implementable.  The questions are

a) Would it be desirable?  After all, there isn't much difference
between
module Main where { ... }
ghc -fprelude-is Foo Main.hs
and
module Main where { import Foo ... }
ghc Main.hs
And arguably the latter it better because the code is more
self-describing.
Well, that all depends on your perspective. =)

Haskell is great as a host for embedded domain specific languages (DSL) and 
there are several such languages already (Lava, Pan, Fran, WASH etc.). Such 
languages could from one perspective be seen as nothing more than libraries 
for Haskell directed at helping you write programs within a certain domain. 
From this point of view, arguably it would be more descriptive to explicitly 
import these libraries into any written modules, they are after all "just 
libraries".

But if you choose the perspective that these are indeed languages in their 
own right, aimed at applications within their domains, I would argue the 
other way around.

Taking Lava, a hardware description language, as my example, I would argue 
that many users of Lava don't really care if it's embedded in Haskell or 
whereever it comes from, they would just use it. I have friends who study 
Lava solely for its application to hardware description, and these same 
friends would never dream of taking a course in Haskell (or any other 
general purpose language). From this perspective, Lava is the Language, and 
Haskell is reduced to a backend. Then it would make sense to talk of things 
like a Lava compiler, to invoke directly on your Lava source files. And said 
compiler would then preferrably be able to provide the users with the 
domain-specific functions that make up the "Prelude" of its domain, without 
the users having to import anything.

I would definitely argue that from this perspective, the former would be far 
more descriptive in the following guise:

module Main where { ... }
lavac Main.hs
where lavac is could simply be a script alias of

	ghc -fprelude-is Lava

By using an explicit Lava compiler you declare that this is indeed a Lava 
program, and you don't expect it to work in any other setting, in particular 
not with a Haskell compiler like GHC.

And in the same line of thinking, I would want a way of specifying suffixes 
of input source files. It would be much neater to call your files Foo.lava 
or similar, and be able to tell GHC to treat them as normal .hs files, i.e.

	lavac <== ghc -hssuf lava -fprelude-is Lava

In my opinion having these flags or not boils down to whether or not GHC 
aims at being "the perfect tool" for "embedded compilers", much as Haskell 
is allready "the perfect language" for embedding domain specific languages.

Simon Peyton-Jones wrote:
b) GHC has a myriad of flags. Every time we add one, even a simple one,
it costs us an hour or two, and (worse) potentially interacts with stuff
in the future.   Each one is "just one little flag" but they do add up!
Aye, there's always a trade off, isn't there?
I wouldn't claim to know how these flags could interact with things in the 
future, but seeing that there is already a -fno-implicit-prelude flag makes 
me wonder if generalising this to explicitly specified "preludes" makes it 
much worse?

For suffixes of input files, I can forsee some problems such as what happens 
if you say -hssuf lhs for instance, should the compiler then treat it as a 
literate or not-so-literate source file? But I'm sure such issues can be 
properly disambiguated, and after that it should (hopefully) be a simple 
matter of pretending that the specified suffix is actually .hs.


I'd be interested to know if lots of people thought this particular one
was very important, though.
So would I. I sure think so. =)

I wrote:
| And while I'm asking about magicks; In our language we have a special
| function, called "page", that we require be present in "executable"
modules,
| much like a main-function.
[...]

Simon Peyton-Jones wrote:
This seems less widely applicable to me; I suggest you use the ideas
suggested by others in their replies.
I agree, this is not general enough and cannot be said to be applicable to 
embedded DSL since most applications written in such languages would still 
rely on an ordinary "main :: IO ()" function.

We still have no really good solution to our problem though, so suggestions 
are more than welcome. The problem now is to know which modules that must 
have said "page" function, i.e. which are the "executables"? If we could get 
the hs-suf extension I suggested above, then we could solve it by giving 
another suffix to "executable" pages, but for now we need to hack our way 
around it.

/Niklas

_

Re: Prelude/main magicks?

2004-05-09 Thread Niklas Broberg
> I am currently co-developing a language[1] as an extension to Haskell, 
by
> means of a preprocessor to GHC. In this language we want to supply the
> programmer with a number of functions by default, as with the functions 
in
> the GHC Prelude.
> Is there some simple way to make GHC treat our own base library in the 
same
> magic way as the Prelude, so that it is always implicitly available?

Perhaps your preprocessor could just place a suitable 'import' in the
generated Haskell module?
Indeed, and that is precisely what we are doing right now. And it's not 
really all that much work for us either, but I can envision other uses for 
such a feature as well, so my question still stands.

> And while I'm asking about magicks; In our language we have a special
> function, called "page", that we require be present in "executable"
> modules, much like a main-function. Once again, is there some way of
> tweaking GHC to check this for us?
Along the same lines: put something like this in the generated module

  requirePage :: ()
  requirePage = f page
where
  f :: PageType -> ()
  f _ = ()
Hmm, this is an interesting idea. I see a problem though, since (just like 
with main) we don't require just all modules to contain such a function, 
only the "executable" ones. That would correspond to the one that we invoke 
ghc (with the preprocessor) on, but ghc in turn will invoke the preprocessor 
on all modules that are loaded. In other terms, ghc can know which module is 
the first, but the preprocessor has no idea.

Thanks for the input,

/Niklas

_
Help STOP SPAM with the new MSN 8 and get 2 months FREE*  
http://join.msn.com/?page=features/junkmail

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


Prelude/main magicks?

2004-05-09 Thread Niklas Broberg
Hello, fellow GHCees,

I am currently co-developing a language[1] as an extension to Haskell, by 
means of a preprocessor to GHC. In this language we want to supply the 
programmer with a number of functions by default, as with the functions in 
the GHC Prelude.
Is there some simple way to make GHC treat our own base library in the same 
magic way as the Prelude, so that it is always implicitly available? Note 
that we don't want to exchange the existing Prelude for our own, we want to 
leave that one as it stands, rather we want one or more other libraries to 
be treated the same way as the Prelude.
If the answer is no, that cannot be done, I would humbly request this as a 
feature in upcomming versions of GHC, I believe it's generally useful 
feature to have. =)

And while I'm asking about magicks; In our language we have a special 
function, called "page", that we require be present in "executable" modules, 
much like a main-function. Once again, is there some way of tweaking GHC to 
check this for us? We cannot simply use a 'main-is' flag since this function 
is not executed the same way that a main function would be, and its type 
should not be IO ().
I don't expect to be able to tell GHC what function must have what type with 
a command line flag, but is there some other way?

Any leads are appreciated, even if they only lead into the source code of 
GHC...

/Niklas Broberg

[1] Haskell Server Pages: http://www.dtek.chalmers.se/~d00nibro/hsp/

_
The new MSN 8: advanced junk mail protection and 2 months FREE* 
http://join.msn.com/?page=features/junkmail

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