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 extens
> 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,
> 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 l
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
> 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
_
>> 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 con
> 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/glasg
> 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.
> 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
> 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,
>> 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 defin
> ... "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.
> 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 alto
>> 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 synta
> 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.
>> 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 replacem
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 o
> 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 h
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
> 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 }
>> : 'fo
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 sur
> 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
obv
> 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 modularizatio
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 collection
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 s
> 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
(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 sh
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
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 t
> 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-m
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 de
> > 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 th
> 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
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 `Embed
> > 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 de
> 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 =
> 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
> * 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.
> 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
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:\Progr
> 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 bi
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 wher
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
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 fo
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'
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) ->
> 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
> 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
_
> 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
> > 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
> >
> 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 sh
> 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
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
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 she
h 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 pre
> > 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
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 ligh
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
__
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
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 a
> 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
pe
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 Serve
62 matches
Mail list logo