Hello *,
As you may be aware, GHC's `{-# LANGUAGE CPP #-}` language extension
currently relies on the system's C-compiler bundled `cpp` program to
provide a "traditional mode" c-preprocessor.
This has caused several problems in the past, since parsing Haskell code
with a preprocessor mode designed for use with C's tokenizer has caused
already quite some problems[1] in the past. I'd like to see GHC 7.12
adopt an implemntation of `-XCPP` that does not rely on the shaky
system-`cpp` foundation. To this end I've created a wiki page
https://ghc.haskell.org/trac/ghc/wiki/Proposal/NativeCpp
to describe the actual problems in more detail, and a couple of possible
ways forward. Ideally, we'd simply integrate `cpphs` into GHC
(i.e. "plan 2"). However, due to `cpp`s non-BSD3 license this should be
discussed and debated since affects the overall-license of the GHC
code-base, which may or may not be a problem to GHC's user-base (and
that's what I hope this discussion will help to find out).
So please go ahead and read the Wiki page... and then speak your mind!
Thanks,
HVR
[1]: ...does anybody remember the issues Haskell packages (& GHC)
encountered when Apple switched to the Clang tool-chain, thereby
causing code using `-XCPP` to suddenly break due to subtly
different `cpp`-semantics?
Hi,
are the SHA sums of cabal-install binaries available somewhere? GHC
provides them on the download pages, but I couldn't find them anywhere for
cabal-install.
If not, would it be possible to provide them?
Thanks,
Petr
Agda sees some segmentation faults when compiled with zlib-0.6.1.x, but
not with zlib-0.5.4.2.
https://code.google.com/p/agda/issues/detail?can=2&q=1518
You might want to constrain zlib < 0.6 for now.
(I reported the issue to the maintainer a couple of weeks ago, but have
not gotten any response yet.)
Cheers,
Andreas
--
Andreas Abel <>< Du bist der geliebte Mensch.
Department of Computer Science and Engineering
Chalmers and Gothenburg University, Sweden
andreas.abel(a)gu.se
http://www2.tcs.ifi.lmu.de/~abel/
This is all well defined in the Haskell 1.4 report. Back then Haskell had
"unfailable" patterns for desugaring do notation, because there was no fail
(it was introduced in H98).
I believe a pattern is classified as unfailable there if it is irrefutable
or refutable only by bottom. Which of course is the distinction here, (x,y)
is unfailable, but not irrefutable.
And of course, it seems that GHC never actually stopped implementing
unfailable patterns, even though they were removed from the report (or
someone added it back at some point). You just have to know how to observe
this fact.
-- Dan
On Thu, Jun 11, 2015 at 12:11 PM, David Turner <
dct25-561bs(a)mythic-beasts.com> wrote:
> Quoting the Haskell 2010 Report section 3.17.2: Attempting to match a
> pattern can have one of three results: it may fail; it may succeed
> ...; or it may diverge. Then in paragraph 5:
>
> Matching the pattern con pat1 ... patn against a value, where con is a
> constructor defined by data, depends on the value:
> - If the value is of the form con v1 ... vn, sub-patterns are matched
> left-to-right against the components of the data value; if all matches
> succeed, the overall match succeeds; the first to fail or diverge
> causes the overall match to fail or diverge, respectively.
> - If the value is of the form con' v1 ... vm, where con is a different
> constructor to con', the match fails.
> - If the value is ⊥, the match diverges.
>
> In particular, matching (_,_) can only succeed or diverge: failure is
> not an option! Desugaring 'do' handles match failure with a catch-all
> case that calls 'fail' but doesn't handle ⊥.
>
>
>
> On 11 June 2015 at 16:28, Wolfgang Jeltsch <g9ks157k(a)acme.softbase.org>
> wrote:
> > Are you sure that desugaring works this way? If yes, this should be
> > considered a bug and be fixed, I would say. It is very illogical.
> >
> > All the best,
> > Wolfgang
> >
> > Am Donnerstag, den 11.06.2015, 16:23 +0100 schrieb David Turner:
> >> AIUI the point about ⊥ and (⊥, ⊥) being different doesn't matter here:
> >> a bind for a single-constructor datatype never desugars in a way that
> >> uses fail (which isn't to say that it can't be undefined)
> >>
> >> For instance:
> >>
> >> runErrorT (do { (_,_) <- return undefined; return () } :: ErrorT String
> IO ())
> >>
> >> throws an exception, even though the bind is in ErrorT where fail just
> >> returns left:
> >>
> >> runErrorT (do { fail "oops"; return () } :: ErrorT String IO ())
> >>
> >> => Left "oops"
> >>
> >> Hope that helps, and hope I understand correctly!
> >>
> >> David
> >>
> >>
> >> On 11 June 2015 at 16:08, Wolfgang Jeltsch <g9ks157k(a)acme.softbase.org>
> wrote:
> >> > Hi David,
> >> >
> >> > thank you very much for this proposal. I think having fail in Monad is
> >> > just plain wrong, and I am therefore very happy to see it being moved
> >> > out.
> >> >
> >> > I have some remarks, though:
> >> >
> >> >> A class of patterns that are conditionally failable are `newtype`s,
> >> >> and single constructor `data` types, which are unfailable by
> >> >> themselves, but may fail if matching on their fields is done with
> >> >> failable paterns.
> >> >
> >> > The part about single-constructor data types is not true. A
> >> > single-constructor data type has a value ⊥ that is different from
> >> > applying the data constructor to ⊥’s. For example, ⊥ and (⊥, ⊥) are
> two
> >> > different values. Matching ⊥ against the pattern (_, _) fails,
> matching
> >> > (⊥, ⊥) against (_, _) succeeds. So single-constructor data types are
> not
> >> > different from all other data types in this respect. The dividing line
> >> > really runs between data types and newtypes. So only matches against
> >> > patterns C p where C is a newtype constructor and p is unfailable
> should
> >> > be considered unfailable.
> >> >
> >> >> - Applicative `do` notation is coming sooner or later, `fail` might
> >> >> be useful in this more general scenario. Due to the AMP, it is
> >> >> trivial to change the `MonadFail` superclass to `Applicative`
> >> >> later. (The name will be a bit misleading, but it's a very small
> >> >> price to pay.)
> >> >
> >> > I think it would be very misleading having a MonadFail class that
> might
> >> > have instances that are not monads, and that this is a price we should
> >> > not pay. So we should not name the class MonadFail. Maybe, Fail would
> be
> >> > a good name.
> >> >
> >> >> I think we should keep the `Monad` superclass for three main reasons:
> >> >>
> >> >> - We don't want to see `(Monad m, MonadFail m) =>` all over the
> place.
> >> >
> >> > But exactly this will happen if we change the superclass of
> (Monad)Fail
> >> > from Monad to Applicative. So it might be better to impose a more
> >> > light-weight constraint in the first place. Functor m might be a good
> >> > choice.
> >> >
> >> > All the best,
> >> > Wolfgang
> >> >
> >> > _______________________________________________
> >> > ghc-devs mailing list
> >> > ghc-devs(a)haskell.org
> >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >
> >
> > _______________________________________________
> > ghc-devs mailing list
> > ghc-devs(a)haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> _______________________________________________
> ghc-devs mailing list
> ghc-devs(a)haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
Are you sure that desugaring works this way? If yes, this should be
considered a bug and be fixed, I would say. It is very illogical.
All the best,
Wolfgang
Am Donnerstag, den 11.06.2015, 16:23 +0100 schrieb David Turner:
> AIUI the point about ⊥ and (⊥, ⊥) being different doesn't matter here:
> a bind for a single-constructor datatype never desugars in a way that
> uses fail (which isn't to say that it can't be undefined)
>
> For instance:
>
> runErrorT (do { (_,_) <- return undefined; return () } :: ErrorT String IO ())
>
> throws an exception, even though the bind is in ErrorT where fail just
> returns left:
>
> runErrorT (do { fail "oops"; return () } :: ErrorT String IO ())
>
> => Left "oops"
>
> Hope that helps, and hope I understand correctly!
>
> David
>
>
> On 11 June 2015 at 16:08, Wolfgang Jeltsch <g9ks157k(a)acme.softbase.org> wrote:
> > Hi David,
> >
> > thank you very much for this proposal. I think having fail in Monad is
> > just plain wrong, and I am therefore very happy to see it being moved
> > out.
> >
> > I have some remarks, though:
> >
> >> A class of patterns that are conditionally failable are `newtype`s,
> >> and single constructor `data` types, which are unfailable by
> >> themselves, but may fail if matching on their fields is done with
> >> failable paterns.
> >
> > The part about single-constructor data types is not true. A
> > single-constructor data type has a value ⊥ that is different from
> > applying the data constructor to ⊥’s. For example, ⊥ and (⊥, ⊥) are two
> > different values. Matching ⊥ against the pattern (_, _) fails, matching
> > (⊥, ⊥) against (_, _) succeeds. So single-constructor data types are not
> > different from all other data types in this respect. The dividing line
> > really runs between data types and newtypes. So only matches against
> > patterns C p where C is a newtype constructor and p is unfailable should
> > be considered unfailable.
> >
> >> - Applicative `do` notation is coming sooner or later, `fail` might
> >> be useful in this more general scenario. Due to the AMP, it is
> >> trivial to change the `MonadFail` superclass to `Applicative`
> >> later. (The name will be a bit misleading, but it's a very small
> >> price to pay.)
> >
> > I think it would be very misleading having a MonadFail class that might
> > have instances that are not monads, and that this is a price we should
> > not pay. So we should not name the class MonadFail. Maybe, Fail would be
> > a good name.
> >
> >> I think we should keep the `Monad` superclass for three main reasons:
> >>
> >> - We don't want to see `(Monad m, MonadFail m) =>` all over the place.
> >
> > But exactly this will happen if we change the superclass of (Monad)Fail
> > from Monad to Applicative. So it might be better to impose a more
> > light-weight constraint in the first place. Functor m might be a good
> > choice.
> >
> > All the best,
> > Wolfgang
> >
> > _______________________________________________
> > ghc-devs mailing list
> > ghc-devs(a)haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
When you did the cabal install of haddock, which haddock did you get? Isn't
2.16.0 the latest? And that should be what is in the Platform.
I guess I should check that the haddock in GHC is actually 2.16.0!
I have the type
data NonEmpty f a = NonEmpty a (f a)
and want to declare an NFData instance in Haskell 98. With the existing
NFData class this is not possible because it requires a (NFData (f a))
constraint which needs FlexibleContexts. A solution would be an NFData1
class analogously to the classes in transformers:Data.Functor.Classes:
class NFData1 f where
rnf1 :: NFData a => f a -> ()
instance NFData1 [] where
rnf1 = rnf
instance (NFData1 f) => NFData1 (NonEmpty f) where
rnf1 (NonEmpty x xs) = rnf (x, rnf1 xs)
instance (NFData1 f, NFData a) => NFData (NonEmpty f a) where
rnf = rnf1