Re: Partial type synonyms -- first-class!

2022-08-11 Thread Edward Kmett
FWIW, Gergo, I've been following what you've been doing pretty closely, so
there's at least two of us tracking it in the background. =) I might have
some clever(?) (ab)uses for it in the future in my linear haskell code.

-Edward

On Thu, Aug 11, 2022 at 10:33 PM ÉRDI Gergő  wrote:

> Hi Richard,
>
> Thanks for getting back to me! My replies are inline below.
>
> On Thu, 11 Aug 2022, Richard Eisenberg wrote:
>
> > You want a third:
> >
> > C. invisible parameters that are filled in with a fresh wildcard.
> >
> > We would need to have some way of writing out the type of such a thing
> > (i.e. what kind would `Syn` have?), but I presume this is possible.
>
> I think there's a tension between this and your suggestion to only add
> implicit parameters as a new `TyConBndrVis`, but more on that below.
>
> >> 2. Using partial type synonyms
> >>
> >>
> >
> > This bit also makes sense, but I think users will want more
> > functionality. Specifically, what if a user does not want a wildcard
> > inserted, because they know that the right choice is `Int`? Or maybe
> > they want a *named* wildcard inserted. My experience is that once
> > something can be done implicitly, folks will soon find good reasons to
> > do it explicitly on occasion.
>
> Good point, but I think we can punt on this and not close any doors ahead.
> So today, you would only be able to write `Syn T` to mean `Syn {_} T`, and
> then in the future we can add typechecker support (and new surface
> syntax!) for `Syn {S} T`, without causing any compatibility problems with
> any existing code that doesn't give explicit args for implicit params.
>
> >> 3. Implementation
> >>
> >>
> >>  * When typechecking a type application, implicit arguments get
> >>filled with the result of `tcAnonWildCardOcc`.
> >
> > What about named wildcards? Even if they're not passed in, perhaps
> someone wants
> >
> > type SomeEndo = _t -> _t
> >
> > where the two types are known to be the same, but we don't know what.
>
> This would be something to support when typechecking the definition, not a
> given application. Your example would still elaborate to
>
>  type SomeEndo {t} = t -> t
>
> it would just use the same implicitly-bound type parameter `t` twice on
> the right-hand side. But when you use `SomeEndo`, the usage would still
> elaborate into a (single) anonymous wildcard argument, i.e.
> `SomeEndo {_}`.
>
> My current implementation doesn't support your example, but I think it's
> only because the renamer rejects it. I think if I get it through the
> renamer, it should already work because that `_t` will typecheck into a
> wildcard `TauTv`.
>
> >> 3. Similar to #1, I started just pushing all the way through GHC a
> >> change to `AnonArgFlag` that adds a third `ImplArg` flag.
> >
> > I don't love adding a new constructor to AnonArgFlag, because that's
> > used in terms. Instead, it would be great to localize this new extension
> > to tycon binders somehow.
>
> OK so while I'd love to get away with only changing `TyConBndrVis`, this
> is the part of your email that I don't understand how to do :/
>
> First, when a type application is typechecked, we only have the kind of
> the type constructor, not its binders (and that makes sense, since we
> could be applying something more complex than directly a defined type
> constructor). So if I only add a new `TyConBndrVis` constructor, then I
> have no way of representing this in the `tyConKind` and so no way of
> finding out that I need to put in implicit args in `tcInferTyApps`.
>
> Second, you ask what the kind of `Syn` in e.g. `type Syn a = TC _ a` is. I
> think (supposing `TC :: K -> L -> M`) its kind should be (stealing syntax
> from Agda) something like `{K} -> L -> M`, i.e. a function kind with
> domain `K`, codomain `L -> M`, and a new kind of visibility on the arrow
> itself. But that means it's not just the binder of the implicit parameter
> that has a new visibility, but the arrow as well. And isn't that what
> `AnonArgFlag` is for?
>
> > I think the route you're taking is a reasonable route to your
> > destination, but I'm not yet convinced it's a destination I want GHC to
> > travel to. As I hint above, I think the feature would have to be
> > expanded somewhat to cover its likely use cases, and yet I worry that it
> > will not be widely enough used to make its specification and
> > implementation worthwhile. I'm happy to be convinced otherwise, though.
>
> Fair enough. Although I was hoping that with Dependent Haskell, we would
> have more situations where unification can give useful solutions, and so
> we would want the feature of implicit arguments (even for terms!).
>
> But if there's no appetite from GHC for partial type synonyms, what would
> help me a lot in keeping this maintainable / avoiding churn in chasing
> `master` would be if I can upstream two refactorings that are enablers
> for my implementation but don't actually change any existing behaviour:
>
> * Adding "does it come from a wildcard" flag 

Re: Seeking RTS experts to review delimited continuations MR

2022-04-15 Thread Edward Kmett
I'm super excited to see this, as it'll rather drastically improve the
performance I can get out of my fancy backtracking search algorithms.

-Edward

On Thu, Apr 14, 2022 at 8:33 PM Alexis King  wrote:

> Hi all,
>
> I have recently opened a draft MR with my initial implementation of
> first-class delimited continuations in the RTS, available here:
> https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7942
>
> The MR is not entirely finished—it still requires docs and tests, which I
> am gradually working on. However, barring any bugs I discover after writing
> those tests, I believe the implementation itself is feature-complete with
> respect to the proposal. Given that it is a nontrivial patch to a somewhat
> unloved portion of GHC, and given that there are a couple questions I have
> about how best to go about testing certain interactions in the first place,
> I figured I would reach out and see if anyone particularly familiar with
> the guts of the RTS would be willing to volunteer some time to give it a
> careful look.
>
> The good news is that the patch is not actually very large, and it changes
> very little existing code: the diffstats currently sit at +1,078 -48. For
> those interested in taking a look at the patch, I recommend starting with
> the Notes mentioned in the MR description. I suspect they may be a bit
> sparse at the moment, so please do not hesitate to ask questions; I will do
> my best to respond promptly.
>
> Many thanks,
> Alexis
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: convention around pattern synonyms

2021-12-29 Thread Edward Kmett
If this is just about GHC internals, then by all means carry on.

-Edward

On Wed, Dec 29, 2021 at 12:19 PM Edward Kmett  wrote:

> Please no.
>
> I use them to pun constructors between multiple types that will be in
> scope at the same time, (e.g. when I have 8 Var constructors on different
> types in scope between my core language term language and type language...)
> and often overload them on classes. I can't write the pragma, and the PS_
> destroys any utiity I get from any common name.
>
> I use them as a migration guide, when I add functionality. PS_ destroys
> that usecase, but then COMPLETE pragmas are a hacky mess in their current
> state and often simply can't be applied.
>
> All the existing pattern constructors in the lens library would fail
> either bar.
>
> So I have to say, either of these would probably destroy *every* use of
> pattern synonyms I use today.
>
> -Edward
>
> On Wed, Dec 29, 2021 at 11:55 AM Richard Eisenberg 
> wrote:
>
>> Hi devs,
>>
>> Maybe I'm just old fashioned, but I've come to find pattern synonyms
>> really confusing. Because pattern synonyms will tend to appear next to
>> proper data constructors in code (and they look just like data
>> constructors), when I see one, I think it *is* a data constructor. This
>> problem was motivated by a recent MR that introduces a new pattern
>> synonym
>> <https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7261/diffs#7dcf5b567a6cd3c9d98cf8d57323fbca1b1536e9_1128_1130>
>>  that
>> caught me off-guard.
>>
>> So, I'd like to propose the following convention: Every pattern synonym
>> satisfies one of the following two criteria:
>> 1. The pattern synonym is a member of a set of synonyms/constructors that
>> expresses a view of a type. There would naturally be a `COMPLETE` pragma
>> including the set. `GHC.Types.Var.Inferred` is an example.
>> 2. The pattern synonym begins with the prefix `PS_`.
>>
>> In the end, I'd probably prefer just (2). With Inferred, for example,
>> I've been caught in the past trying to figure just what the constructors of
>> ArgFlag were (there seemed to be too many), until I realized what was going
>> on.
>>
>> Pattern synonyms are useful abstractions. I like them. But my mental
>> model of a pattern match is that it matches the structure of the scrutinee
>> and performs no computation. Pattern synonyms violate both of these
>> assumptions, and so (as a reader) I like to know when to put these
>> assumptions to the side.
>>
>> Future IDE support that could, say, color pattern synonyms differently to
>> regular constructors would obviate the need for this convention.
>>
>> What do others think here? `PS_` is ugly. I don't need something quite so
>> loud and ugly, but it's also easy to remember and recognize.
>>
>> Thanks!
>> Richard
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: convention around pattern synonyms

2021-12-29 Thread Edward Kmett
Please no.

I use them to pun constructors between multiple types that will be in scope
at the same time, (e.g. when I have 8 Var constructors on different types
in scope between my core language term language and type language...) and
often overload them on classes. I can't write the pragma, and the PS_
destroys any utiity I get from any common name.

I use them as a migration guide, when I add functionality. PS_ destroys
that usecase, but then COMPLETE pragmas are a hacky mess in their current
state and often simply can't be applied.

All the existing pattern constructors in the lens library would fail either
bar.

So I have to say, either of these would probably destroy *every* use of
pattern synonyms I use today.

-Edward

On Wed, Dec 29, 2021 at 11:55 AM Richard Eisenberg 
wrote:

> Hi devs,
>
> Maybe I'm just old fashioned, but I've come to find pattern synonyms
> really confusing. Because pattern synonyms will tend to appear next to
> proper data constructors in code (and they look just like data
> constructors), when I see one, I think it *is* a data constructor. This
> problem was motivated by a recent MR that introduces a new pattern synonym
> 
>  that
> caught me off-guard.
>
> So, I'd like to propose the following convention: Every pattern synonym
> satisfies one of the following two criteria:
> 1. The pattern synonym is a member of a set of synonyms/constructors that
> expresses a view of a type. There would naturally be a `COMPLETE` pragma
> including the set. `GHC.Types.Var.Inferred` is an example.
> 2. The pattern synonym begins with the prefix `PS_`.
>
> In the end, I'd probably prefer just (2). With Inferred, for example, I've
> been caught in the past trying to figure just what the constructors of
> ArgFlag were (there seemed to be too many), until I realized what was going
> on.
>
> Pattern synonyms are useful abstractions. I like them. But my mental model
> of a pattern match is that it matches the structure of the scrutinee and
> performs no computation. Pattern synonyms violate both of these
> assumptions, and so (as a reader) I like to know when to put these
> assumptions to the side.
>
> Future IDE support that could, say, color pattern synonyms differently to
> regular constructors would obviate the need for this convention.
>
> What do others think here? `PS_` is ugly. I don't need something quite so
> loud and ugly, but it's also easy to remember and recognize.
>
> Thanks!
> Richard
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: To allow deriving poly-kinded Generic1 instances

2021-10-13 Thread Edward Kmett
I use the same F1 trick (with the same name and for the same reason) in the
HEAD branch of hkd and distributive, but I admit it is a bit frustrating,
because then I have to expose pattern synonyms to hide its boilerplate from
users.

e.g.

https://github.com/ekmett/hkd/blob/85cee5aa594b66f2d03d6366df776ced742e4635/src/Data/HKD.hs#L168

...

https://github.com/ekmett/hkd/blob/85cee5aa594b66f2d03d6366df776ced742e4635/src/Data/HKD.hs#L252

Adding an F1 or the like to GHC.Generics that was used automatically to
handle application of the last "1" argument to some other type in turn
would go a long way towards plugging that hole in the vocabulary of stock
GHC.Generics.

Other generics libraries exist, but they don't get quite the same attention
and user support.

-Edward

On Wed, Oct 13, 2021 at 9:49 AM Ryan Scott  wrote:

> > I figured out that this compiles:
> >
> > data HKD (f :: Type -> Type) = Foo (F1 Int f) (F1 Double f)
> >   | Bar (F1 Bool f)
> >   deriving Generic1
> >
> > newtype F1 a f = F1 { unF1 :: f a }
>
> Yes, that's a useful trick to keep in mind. For what it's worth, I think
> your `F1` is the same thing as `Barbie` [1] from the `barbies` library.
>
> > Would it be a good idea to add F1 to GHC.Generics?
>
> There's a couple of issues that make me cautious about this idea:
>
> 1. This isn't an issue that's specific to `DeriveGeneric`. Other `stock`
> deriving strategies that deal with similar classes, such as
> `DeriveFunctor`, also suffer from this problem. For instance, you can't do
> the following:
>
>> data T a = MkT (Either a Int) deriving Functor
>
>Again, the issue is that the last type parameter (`a`) appears in a
> field type in a position other than as the last argument. To make _this_
> work, you'd need something like `Flip` [2] from the `bifunctors` library:
>
>> data T a = MkT (Flip Either Int a) deriving Functor
>
>That leads into the second issue...
> 2. There are an infinite number of different type variable combinations
> you could conceivably add special support for. I've already mentioned
> `Barbie` and `Flip` above, but you could just as well put the last type
> parameter in other places as well:
>
>> data S1 a = MkS1 (a, Int, Int) deriving Generic1
>> data S2 a = MkS2 (a, Int, Int, Int) deriving Generic1
>> data S3 a = MkS3 (a, Int, Int, Int, Int) deriving Generic1
>> ...
>
>And this is only if you assume that the last type parameter only
> appears once in each field type. You'd need even more special cases if the
> last type parameter appears in multiple places in a field type:
>
>> data U1 a = MkU1 (a, a) deriving Generic1
>> data U2 a = MkU2 (a, a, a) deriving Generic1
>> ...
>
>With all of these possibilities, it's difficult to say how far we
> should go with this.
>
> Generally speaking, my recommendation for people who are dissatisfied with
> `Generic1`'s restrictions on where the last type parameter can be placed is
> to not use `Generic1` at all. There are other generic programming libraries
> that do not have the same restrictions, such as `kind-generics` [3]. Using
> something like `kind-generics` avoids the need to use things like `Barbie`,
> `Flip`, etc. in the first place.
>
> Best,
>
> Ryan
> -
> [1]
> https://hackage.haskell.org/package/barbies-2.0.3.0/docs/Barbies.html#t:Barbie
> [2]
> https://hackage.haskell.org/package/bifunctors-5.5.11/docs/Data-Bifunctor-Flip.html#t:Flip
> [3] https://hackage.haskell.org/package/kind-generics
>
> On Wed, Oct 13, 2021 at 9:26 AM Fumiaki Kinoshita 
> wrote:
>
>> Oh, I drew a conclusion too early when fiddling with a hypothetical
>> Generic1 instance. I now think it's not possible to define an instance with
>> the current kit.
>>
>> I figured out that this compiles:
>>
>> data HKD (f :: Type -> Type) = Foo (F1 Int f) (F1 Double f)
>>   | Bar (F1 Bool f)
>>   deriving Generic1
>>
>> newtype F1 a f = F1 { unF1 :: f a }
>>
>> Problem solved, thanks!
>>
>> Would it be a good idea to add F1 to GHC.Generics? Omitting metadata,
>> it'd derive something like
>>
>> instance Generic1 HKD where
>>   type Rep1 HKD = F1 Int :*: F1 Double :+: F1 Bool
>>   from1 (Foo a b) = L1 (F1 a :*: F1 b)
>>   from1 (Bar c) = R1 (F1 c)
>>   to1 (L1 (F1 a :*: F1 b)) = Foo a b
>>   to1 (R1 (F1 c)) = Bar c
>>
>> I suppose it doesn't affect existing Generic1 instances and uses, so I
>> don't expect breakages by adding this
>>
>> ...
>>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: How to use Lexer.lexer to produce closing braces as well?

2021-08-18 Thread Edward Kmett
Unfortunately, the current parsing rules for Haskell aren't fully
phase-separable like this.

If you look at the rules for Layout token insertion in the Haskell report
the 9th rule requires that in the event the parser encounters a parse
error it should insert a virtual close brace and continue on!

Otherwise you couldn't parse things like *let **{** foo = bar **}** in
baz *where
the {}'s are virtual without reframing *let* and *in* as a different kind
of paired opening and closing brace or using other hacks in the grammar. It
is quite difficult to hack around all the ways parses can go wrong.

The main downside this has from a language standpoint is you simply can't
properly lex Haskell without more or less fully parsing Haskell.

-Edward

On Wed, Aug 18, 2021 at 7:22 AM Kwanghoon Choi  wrote:

>
> Hi,
>
> I have recently been playing with GHC's Lexer.lexer in the ghc-parser-lib
> package.
>
> Given
>
>module HelloWorld where
>
>main = putStrLn "Hello World!\n"
>
> it produces
>
>stack exec -- lexer-exe ./examples/HelloWorld.hs
>Lexing: ./examples/HelloWorld.hs
>module at (1, 1): module
>CONID at (1, 8): CONID
>where at (1, 19): where
>vocurly at (3, 1): vocurly< { is inserted automatically!!
>VARID at (3, 1): VARID
>= at (3, 6): =
>VARID at (3, 8): VARID
>STRING at (3, 17): STRING
>; at (4, 1): ;
>
> By the example above, the lexer automatically inserts an opening brace
> (i.e. vocurly) right after 'where'. But it does not insert a matching
> closing brace (i.e., vccurly), which would lead to a failure in parsing a
> list of tokens produced by the lexer.
>
> My question is how to use the GHC lexer to produce closing braces as well.
>
> All my code is available
>  - https://github.com/kwanghoon/hslexer
>
> To save your time, the relevant part of the code is as follows:
>
> In app/HaskellLexer.hs,
>
> singleHaskellToken :: P (Located Token)
> singleHaskellToken =
>   Lexer.lexer False
> (\locatedToken -> P (\pstate -> POk pstate locatedToken))
>
> tokInfos :: [Terminal Token] -> P (Line, Column, [Terminal Token])
> tokInfos s = do
>   locatedToken <- singleHaskellToken
>   case locatedToken of
> L srcspan ITeof ->
>   let (start_line, start_col, end_line, end_col) =
> srcSpanToLineCol srcspan in
>   return (end_line, end_col, s)
>
> L srcspan tok ->
>   let (start_line, start_col, end_line, end_col) =
> srcSpanToLineCol srcspan in
>   tokInfos (Terminal (fromToken tok) start_line start_col (Just
> tok) : s)
>
> Thanks in advance
>
> Best regards,
>
> Kwanghoon
>
>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`?

2021-07-12 Thread Edward Kmett
There's always pattern synonyms as an option for cases like this, free of
backwards compat issues.

-Edward

On Tue, Jul 6, 2021 at 3:00 AM Alfredo Di Napoli 
wrote:

>
> Hello Simon,
>
> Yes, renaming and perhaps keeping `RecordPuns` as a pattern synonym to not
> break backward-compat, if that's feasible to define as we are in
> `ghc-boot-th` here. Not sure if `PatternSynonyms` and `COMPLETE` would be
> available there.
>
> I am not sure how many libs that depend on the ghc API would break (I
> haven't grepped on Hackage yet), but that might tip the benefits/troubles
> ratio towards keeping the status quo.
>
> This is not a "problem" I have to solve today, and it might not be
> considered a problem by others (just an inconsistency I guess): as a
> colleague of mine pointed out, GHC is not necessarily "lying" here. It's
> still the same underlying extension, it just happens that there are two
> names that refer to it.
>
> Perhaps I could think about adding to `GhcHint` some kind of mapping which
> would give to IDEs or third-party libs the correct extension name given an
> input `LangExt.Extension`, the problem then becomes making sure that we
> keep this mapping in sync with the information contained in
> `GHC.Driver.Session`.
>
> I will let it simmer.
>
> Thanks!
>
> A.
>
> On Tue, 6 Jul 2021 at 11:19, Simon Peyton Jones 
> wrote:
>
>> 1. What prevents us from adding `NamedFieldPuns` as a proper constructor
>> for the `Extension` type and in principle remove `RecordPuns`? Backward
>> compatibility I assume?
>>
>> You mean, essentially, rename `LangExt.RecordPuns` to `NamedFieldPuns`.
>>
>>
>>
>> I’d be fine with that.  There might be back-compat issues, but only with
>> other plugins, and probably with vanishingly few of them.  Grep in Hackage!
>>
>>
>>
>> Simon
>>
>>
>>
>> *From:* ghc-devs  *On Behalf Of *Alfredo
>> Di Napoli
>> *Sent:* 06 July 2021 10:14
>> *To:* Simon Peyton Jones via ghc-devs 
>> *Subject:* Can NamedFieldPuns be added to
>> `GHC.LanguageExtensions.Types.Extension`?
>>
>>
>>
>> Dear all,
>>
>>
>>
>> As some of you might know, for the past few months I have been working on
>> changing GHC's diagnostic messages from plain SDocs to richer Haskell types.
>>
>>
>>
>> As part of this work, I have added a mechanism to embed hints into
>> diagnostics, defined in `GHC.Types.Hint` in `HEAD`. One of the main
>> workhorse of this `GhcHint` type is the `SuggestExtension
>> LangExt.Extension` constructor, which embeds the extension to enable to use
>> a particular feature. The `LangExt.Extension` type comes from
>> `GHC.LanguageExtensions.Types`, and up until now there has always been a
>> 1:1 mapping between the language pragma for the extension and the type
>> itself.
>>
>>
>>
>> Today I was working on turning this error into a proper Haskell type:
>>
>>
>>
>> badPun :: Located RdrName -> TcRnMessage
>>
>> badPun fld = TcRnUnknownMessage $ mkPlainError noHints $
>>
>>   vcat [text "Illegal use of punning for field" <+> quotes (ppr fld),
>>
>> text "Use NamedFieldPuns to permit this"]
>>
>>
>>
>> I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I
>> discovered that there is no `NamedFieldPuns` constructor. Rather, there is
>> a `RecordPuns` , which refer to a deprecated flag, and we simply map
>> `NamedFieldPuns` back to it in `GHC.Driver.Session`:
>>
>>
>>
>> ...
>>
>>   depFlagSpec' "RecordPuns"   LangExt.RecordPuns
>>
>> (deprecatedForExtension "NamedFieldPuns"),
>>
>> ...
>>
>>   flagSpec "NamedFieldPuns"   LangExt.RecordPuns,
>>
>> ...
>>
>>
>>
>> This is problematic for the `GhcHint` type, because now if I was to yield
>> `SuggestExtension LangExt.RecordPuns` to the user, I could still
>> pretty-print the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but
>> this means that IDEs or third-party library would have access to the
>>
>> "raw" Haskell datatype, and at that point they will be stuck with a
>> suggestion to enable a deprecated extension! (or best case scenario they
>> will have to transform the suggestion into something more sensible, which
>> partially defeats the point of this refactoring work I have been doing).
>>
>>
>>
>> I am not sure this behaviour is unique for just `NamedFieldPuns`, but my
>> question is:
>>
>>
>>
>> 1. What prevents us from adding `NamedFieldPuns` as a proper constructor
>> for the `Extension` type and in principle remove `RecordPuns`? Backward
>> compatibility I assume?
>>
>>
>>
>>
>>
>> Many thanks,
>>
>>
>>
>> Alfredo
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Breaking changes to the base library

2021-06-20 Thread Edward Kmett
The breakage concern is why Data.List wound up in its limbo-like state of
re-exporting the Foldable-polymorphic combinators since 7.10 -- while
"weird", it was the only option that didn't have to choose between removing
the names from Data.List exports entirely and breaking unqualified imports
of Data.List.

With the monomorphized combinators in place, Data.List should be considered
a 'qualified' import like Data.Map. We definitely need to do more to
communicate that this is changing and how users should adjust their code to
suit. After all, by far the most common intended import from Data.List is
the humble 'sort', which doesn't conflict.

-Edward

On Sun, Jun 20, 2021 at 4:45 AM Chris Smith  wrote:

> Yikes, this is going to break nearly everything.  Definitely good to let
> people know.
>
> On Sun, Jun 20, 2021 at 7:43 AM Ben Gamari  wrote:
>
>> Harendra Kumar  writes:
>>
>> > I see the following errors when compiling with ghc head version:
>> >
>> > $ ghc-stage2 --version
>> > The Glorious Glasgow Haskell Compilation System, version 9.3.20210608
>> >
>> > $ cabal build --with-compiler ghc-stage2 --allow-newer
>> >
>> > Data/Colour/CIE.hs:80:12: error:
>> > Ambiguous occurrence ‘sum’
>> > It could refer to
>> >either ‘Prelude.sum’,
>> >   imported from ‘Prelude’ at Data/Colour/CIE.hs:25:8-22
>> >   (and originally defined in ‘Data.Foldable’)
>> >or ‘Data.List.sum’,
>> >   imported from ‘Data.List’ at Data/Colour/CIE.hs:41:1-16
>> >   (and originally defined in ‘GHC.List’)
>> >|
>> > 80 |total = sum $ map fst l
>> >|^^^
>> >
>> > Can someone briefly describe this change and what's the recommended way
>> of
>> > fixing this? Just hide the Data.List definition? I do not see this
>> > mentioned in the release notes of 9.2/9.4 here:
>> > https://ghc.gitlab.haskell.org/ghc/doc/users_guide/9.2.1-notes.html
>> >
>> Indeed, this is due to the monomorphic Data.List proposal, which the
>> CLC decided would accompany the addition of Data.List.singleton. The
>> correct fix here is to either qualify the import of `Data.List` or add
>> an explicit import list. I'll try to remember to add a note about this
>> to the release notes and migration guide.
>>
>>
>> Cheers,
>>
>> - Ben
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: magicDict

2021-04-26 Thread Edward Kmett
Indeed.

Sent from my iPhone

> On Apr 26, 2021, at 2:22 PM, Simon Peyton Jones  wrote:
> 
> 
> You mean you like ‘withDict’ with that name,  as well as the argument order K 
> suggests?   i.e. not reifyDict?
>  
> Simon
>  
> From: Edward Kmett  
> Sent: 26 April 2021 21:34
> To: Simon Peyton Jones 
> Cc: Krzysztof Gogolewski ; Spiwack, Arnaud 
> ; GHC developers ; Ryan Scott 
> 
> Subject: Re: magicDict
>  
> I like withDict a lot. It is direct, easy to chain/use, avoids fighting about 
> direction completely, and even matches the argument order used by reify in 
> the reflection library.
> 
>  
> 
> +1 from me.
> 
>  
> 
> On Mon, Apr 26, 2021 at 7:49 AM Simon Peyton Jones  
> wrote:
> 
> |  I would like to propose one more option:
> |  
> |  withDict :: dt -> (ct => a) -> a
> 
> Ah, you mean simply: swap the argument order.   I can see your logic about 
> chaining etc.  I'd be fine with this.
> 
> Simon
> 
> |  -Original Message-
> |  From: Krzysztof Gogolewski 
> |  Sent: 26 April 2021 15:35
> |  To: Simon Peyton Jones 
> |  Cc: Spiwack, Arnaud ; Edward Kmett
> |  ; GHC developers 
> |  Subject: Re: magicDict
> |  
> |  I would like to propose one more option:
> |  
> |  withDict :: dt -> (ct => a) -> a
> |  
> |  1. This is less symmetric than '(ct => a) -> dt -> a'
> | but in existing applications magicDict gets the arguments
> | in the reverse order.
> |  2. Easier to chain 'withDict d1 (withDict d2 ...)'.
> |  3. The name is similar to 'withTypeable' or 'withFile',
> | and avoids arguing which is reify or reflect.
> |  
> |  On Mon, Apr 26, 2021 at 9:41 AM Simon Peyton Jones via ghc-devs  |  d...@haskell.org> wrote:
> |  >
> |  > Can we just agree a name, then?   Please correct me if I'm wrong,
> |  but
> |  >
> |  > I think Ed prefers 'reifyDict',
> |  > That is compatible with the existing reflection library Arnaud
> |  > disagrees but isn't going to die in the trenches for this one
> |  > Virtually anything is better than 'magicDict'.
> |  >
> |  >
> |  >
> |  >
> |  >
> |  > So: reifyDict it is?
> |  >
> |  >
> |  >
> |  > Simon
> |  >
> |  >
> |  >
> |  > From: Spiwack, Arnaud 
> |  > Sent: 26 April 2021 08:10
> |  > To: Edward Kmett 
> |  > Cc: Simon Peyton Jones ; GHC developers
> |  > 
> |  > Subject: Re: magicDict
> |  >
> |  >
> |  >
> |  >
> |  >
> |  >
> |  >
> |  > On Sun, Apr 25, 2021 at 2:20 AM Edward Kmett 
> |  wrote:
> |  >
> |  > I speak to much this same point in this old stack overflow response,
> |  though to exactly the opposite conclusion, and to exactly the opposite
> |  pet peeve.
> |  >
> |  >
> |  >
> |  >
> |  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fstac
> |  >
> |  koverflow.com%2Fa%2F5316014%2F34707data=04%7C01%7Csimonpj%40micro
> |  >
> |  soft.com%7C87da21fdcc8e4ed6bef508d908c071fb%7C72f988bf86f141af91ab2d7c
> |  >
> |  d011db47%7C1%7C0%7C637550444930791696%7CUnknown%7CTWFpbGZsb3d8eyJWIjoi
> |  >
> |  MC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000
> |  >
> |  sdata=VlRrIEROGj%2BE6%2FuLXBEdfa%2BPWVlHh50dahgjIrw4tQU%3Dreserve
> |  > d=0
> |  >
> |  >
> |  >
> |  > :-)
> |  >
> |  >
> |  >
> |  > I do not feel that I chose the vocabulary without due consideration
> |  of the precise meaning of the words used.
> |  >
> |  >
> |  >
> |  > I didn't mean to imply that you did. Sorry if I did so: written
> |  communication is hard. For what it's worth, I didn't really think that
> |  I would change your mind, either.
> |  >
> |  >
> |  >
> |  > Though it still seems to me that the name `ReifiedMonoid` uses the
> |  word for a different thing than the `reifyMonoid` function does.
> |  >
> |  >
> |  >
> |  > To be explicit:
> |  >
> |  >
> |  >
> |  > Viewing a type as a space, 'reify' in the reflection library takes
> |  some space 'a' and splits it into individual fibers for each term in
> |  'a', finding the appropriate one and handing it back to you as a fresh
> |  type 's' that captures just that singular value. The result is
> |  significantly less abstract, as we gained detail on the type, now
> |  every point in the original space 'a' is a new space. At the type
> |  level the fresh 's' in s `Reifies` a now concretely names exactly one
> |  inhabitant of 'a'.
> |  >
> |  >
> |  >
> |  > On the flip side

Re: magicDict

2021-04-26 Thread Edward Kmett
I like withDict a lot. It is direct, easy to chain/use, avoids fighting
about direction completely, and even matches the argument order used by
reify in the reflection library.

+1 from me.

On Mon, Apr 26, 2021 at 7:49 AM Simon Peyton Jones 
wrote:

> |  I would like to propose one more option:
> |
> |  withDict :: dt -> (ct => a) -> a
>
> Ah, you mean simply: swap the argument order.   I can see your logic about
> chaining etc.  I'd be fine with this.
>
> Simon
>
> |  -Original Message-
> |  From: Krzysztof Gogolewski 
> |  Sent: 26 April 2021 15:35
> |  To: Simon Peyton Jones 
> |  Cc: Spiwack, Arnaud ; Edward Kmett
> |  ; GHC developers 
> |  Subject: Re: magicDict
> |
> |  I would like to propose one more option:
> |
> |  withDict :: dt -> (ct => a) -> a
> |
> |  1. This is less symmetric than '(ct => a) -> dt -> a'
> | but in existing applications magicDict gets the arguments
> | in the reverse order.
> |  2. Easier to chain 'withDict d1 (withDict d2 ...)'.
> |  3. The name is similar to 'withTypeable' or 'withFile',
> | and avoids arguing which is reify or reflect.
> |
> |  On Mon, Apr 26, 2021 at 9:41 AM Simon Peyton Jones via ghc-devs  |  d...@haskell.org> wrote:
> |  >
> |  > Can we just agree a name, then?   Please correct me if I'm wrong,
> |  but
> |  >
> |  > I think Ed prefers 'reifyDict',
> |  > That is compatible with the existing reflection library Arnaud
> |  > disagrees but isn't going to die in the trenches for this one
> |  > Virtually anything is better than 'magicDict'.
> |  >
> |  >
> |  >
> |  >
> |  >
> |  > So: reifyDict it is?
> |  >
> |  >
> |  >
> |  > Simon
> |  >
> |  >
> |  >
> |  > From: Spiwack, Arnaud 
> |  > Sent: 26 April 2021 08:10
> |  > To: Edward Kmett 
> |  > Cc: Simon Peyton Jones ; GHC developers
> |  > 
> |  > Subject: Re: magicDict
> |  >
> |  >
> |  >
> |  >
> |  >
> |  >
> |  >
> |  > On Sun, Apr 25, 2021 at 2:20 AM Edward Kmett 
> |  wrote:
> |  >
> |  > I speak to much this same point in this old stack overflow response,
> |  though to exactly the opposite conclusion, and to exactly the opposite
> |  pet peeve.
> |  >
> |  >
> |  >
> |  >
> |  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fstac
> |  >
> |  koverflow.com%2Fa%2F5316014%2F34707data=04%7C01%7Csimonpj%40micro
> |  >
> |  soft.com%7C87da21fdcc8e4ed6bef508d908c071fb%7C72f988bf86f141af91ab2d7c
> |  >
> |  d011db47%7C1%7C0%7C637550444930791696%7CUnknown%7CTWFpbGZsb3d8eyJWIjoi
> |  >
> |  MC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000
> |  >
> |  sdata=VlRrIEROGj%2BE6%2FuLXBEdfa%2BPWVlHh50dahgjIrw4tQU%3Dreserve
> |  > d=0
> |  >
> |  >
> |  >
> |  > :-)
> |  >
> |  >
> |  >
> |  > I do not feel that I chose the vocabulary without due consideration
> |  of the precise meaning of the words used.
> |  >
> |  >
> |  >
> |  > I didn't mean to imply that you did. Sorry if I did so: written
> |  communication is hard. For what it's worth, I didn't really think that
> |  I would change your mind, either.
> |  >
> |  >
> |  >
> |  > Though it still seems to me that the name `ReifiedMonoid` uses the
> |  word for a different thing than the `reifyMonoid` function does.
> |  >
> |  >
> |  >
> |  > To be explicit:
> |  >
> |  >
> |  >
> |  > Viewing a type as a space, 'reify' in the reflection library takes
> |  some space 'a' and splits it into individual fibers for each term in
> |  'a', finding the appropriate one and handing it back to you as a fresh
> |  type 's' that captures just that singular value. The result is
> |  significantly less abstract, as we gained detail on the type, now
> |  every point in the original space 'a' is a new space. At the type
> |  level the fresh 's' in s `Reifies` a now concretely names exactly one
> |  inhabitant of 'a'.
> |  >
> |  >
> |  >
> |  > On the flip side, 'reflect' in the reflection library forgets this
> |  finer fibration / structure on space, losing the information about
> |  which fiber the answer came from, being forgetful is precisely the
> |  justification of it being the 'reflect' half of the reify -| reflect
> |  pairing.
> |  >
> |  >
> |  >
> |  > I confess I don't necessarily anticipate this changing your mind but
> |  it was not chosen blindly, reflect is the forgetful mapping here,
> |  reification is free and left adjoint to it, at least 

Re: magicDict

2021-04-24 Thread Edward Kmett
I speak to much this same point in this old stack overflow response, though
to exactly the opposite conclusion, and to exactly the opposite pet peeve.

https://stackoverflow.com/a/5316014/34707

Let me see if I can try to explain why I think reasonable people can
disagree here and why I ultimately adopted the "wrong" vocabulary from your
perspective.

To be explicit:

Viewing a type as a space, 'reify' in the reflection library takes some
space 'a' and splits it into individual fibers for each term in 'a',
finding the appropriate one and handing it back to you as a fresh type 's'
that captures just that singular value. The result is significantly less
abstract, as we gained detail on the type, now every point in the original
space 'a' is a new space. At the type level the fresh 's' in s `Reifies` a
now concretely names exactly one inhabitant of 'a'.

On the flip side, 'reflect' in the reflection library forgets this finer
fibration / structure on space, losing the information about which fiber
the answer came from, being forgetful is precisely the justification of it
being the 'reflect' half of the reify -| reflect pairing.

I confess I don't necessarily anticipate this changing your mind but it was
not chosen blindly, reflect is the forgetful mapping here, reification is
free and left adjoint to it, at least in the context of
reflection-the-library, *where a quantifier is being injected to track the
particular member*.

This gets more muddled when you remove the quantifier, like here, now
everything becomes the same size, nothing is being forgotten when you use
"magicDict" to transform 5 :: Natural into dictionary for KnownNat (5 ::
Nat) or use the single member of the dictionary to get your value back. If
anything it goes the other way, because you _could_ evilly produce a
dictionary from 6 :: Natural and nothing but your conscience stops you. But
when used in a way that doesn't violate coherence of instance resolution,
no finer fibration was introduced, reflect isn't forgetful, neither is
reify, you produce singleton instances in a thin category from singleton
types. In that framework, really neither term seems fully appropriate here
-- or rather both do depending on your chosen perspective. This is where I
believe the religious wars about which is concrete and which is abstract
start up, because both uses satisfy that definition in this narrow case of
isomorphism, no information is lost on either end.

It is only when you actually introduce a quantifier to ensure 's' is fresh
(as it is used in the reflection library to ensure this doesn't compromise
instance resolution safety in general) that there is a bias introduced and
'reflect' forgets this hallucinated structure, finally forcing a
'handedness' on the terminology to use.

I do not feel that I chose the vocabulary without due consideration of the
precise meaning of the words used.

-Edward

On Thu, Apr 22, 2021 at 11:16 PM Spiwack, Arnaud 
wrote:

> While I do value consistency, let me pet-peeve for a minute here (sorry in
> advance Edward for the rant). The word “reify” comes from the latin “res”,
> which means object/thing. It should always mean something along the line of
> “making more concrete”. In normalisation by evaluation, for instance, you
> reify a semantic value as syntax (an object of the language of study), and
> you reflect values of the language into the semantic domain.
>
> To me, the reflection library uses the terms inconsistently. For instance
> you have the type ReifiedMonoid for the concrete type representing a
> monoid instance. This is, in my opinion, the right terminology. However, a
> ReifiedMonoid should be the product of reification, but in the reflection
> library it actually gets reify-d further. This doesn’t seem to work at
> the grammar level. I contend that the function should have been reflect
> all along: you reflect a concrete dictionary object into the nebulous,
> untouchable world of type class instances.
>
> It’s probably too late to fix the reflection library, hence me never
> complaining about it (in public :-) ). But I vote we don’t perpetuate this
> situation, and still call the function reflectDict.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: magicDict

2021-04-22 Thread Edward Kmett
Happy to see progress being made here. I think Ryan and others have spoken
to any issues I would otherwise raise with the implementation itself.
Currently I find myself reaching for unsafeCoerce over magicDict in most
situations, and I'd really like to be able to stop doing that!

I'm +1 on the name being something `reify`-ish, to avoid flipping the
direction on the vocabulary. It is reifying a value as a dictionary.
Something like `reifyValue` or `reifyAsDict` would avoid confusion as the
dict isn't being reified, the value is. Both are a little clunky, but it is
a very rare operation. It is also worth considering possibly mangling the
name with a # or an 'unsafe' in the name to give casual users pause.

-Edward

On Thu, Apr 22, 2021 at 12:18 PM Krzysztof Gogolewski <
krz.gogolew...@gmail.com> wrote:

> How about 'reifyDict'? The reflection library uses 'reify' to create a
> dictionary and 'reflect' to extract a value out of it.
>
>
> https://hackage.haskell.org/package/reflection-2.1.6/docs/Data-Reflection.html#v:reify
>
> On Thu, Apr 22, 2021 at 3:27 PM Spiwack, Arnaud 
> wrote:
> >
> > Let me upvote `reflectDict`.
> >
> > On Thu, Apr 22, 2021 at 12:41 PM Simon Peyton Jones via ghc-devs <
> ghc-devs@haskell.org> wrote:
> >>
> >> Ed, and other ghc-devs
> >>
> >> We are busy tidying up magicDict, and making it much more type-safe: see
> >>
> >> https://gitlab.haskell.org/ghc/ghc/-/issues/16646
> >> https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5573
> >>
> >> As part of that change we’re think of changing its
> currently-rather-obscure name.  I rather favour “reflectDict”.  Any other
> views?
> >>
> >> Simon
> >>
> >> ___
> >> ghc-devs mailing list
> >> ghc-devs@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >
> > ___
> > ghc-devs mailing list
> > ghc-devs@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: GHC 9.1?

2021-03-02 Thread Edward Kmett
In the past I've gained non-zero utility from having the spacer there to
allow me to push patches in to allow HEAD builds while features are still
in flux. Some of those in flux changes -- to my mild chagrin -- made it out
to hackage, but were handled robustly because I wasn't claiming in the code
that it worked on the next major release of GHC. Admittedly this was in the
before-times, when it was much harder to vendor specific versions of
packages for testing. Now with stack.yaml and cabal.project addressing that
detail it is much reduced concern.

That isn't to say there is zero cost to losing every other version number,
but if we want to allow GHC versions and PVP versions to mentally "fit in
the same type" the current practice has the benefit that it doesn't require
us either doing something like bolting tags back into Data.Version to
handle the "x.y.nightly" or forcing everyone to move to the real next
release the moment the new compiler ships with a bunch of a jump, or
generally forcing more string-processing nonsense into build systems. Right
now version numbers go up and you can use some numerical shenanigans to
approximate them with a single integer for easy ifdefs.

I'm ever so slightly against recoloring the bikeshed on the way we manage
the GHC  version number, just because I know my tooling is robust around
what we have, and I don't see marked improvement in the status quo being
gained, while I do foresee a bit of complication around the consumption of
ghc as a tool if we change

-Edward

On Mon, Mar 1, 2021 at 8:30 PM Richard Eisenberg  wrote:

> Hi devs,
>
> I understand that GHC uses the same version numbering system as the Linux
> kernel did until 2003(*), using odd numbers for unstable "releases" and
> even ones for stable ones. I have seen this become a point of confusion, as
> in: "Quick Look just missed the cutoff for GHC 9.0, so it will be out in
> GHC 9.2" "Um, what about 9.1?"
>
> Is there a reason to keep this practice? Linux moved away from it 18 years
> ago and seems to have thrived despite. Giving this convention up on a new
> first-number change (the change from 8 to 9) seems like a good time.
>
> I don't feel strongly about this, at all -- just asking a question that
> maybe no one has asked in a long time.
>
> Richard
>
> (*) I actually didn't know that Linux stopped doing this until writing
> this email, wondering why we needed to tie ourselves to Linux. I
> coincidentally stopped using Linux full-time (and thus administering my own
> installation) in 2003, when I graduated from university.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Weekly show & tell video meeting

2021-02-15 Thread Edward Kmett
I'd be happy to go with one and see how it goes and plan from there if that
works for you.

-Edward

On Mon, Feb 15, 2021 at 7:06 AM Csaba Hruska  wrote:

> Hello,
> Would you be interested in a weekly show & tell video meeting?
> The topic would be Haskell & compilers in general. Either GHC or non-GHC
> related.
>
> Regards,
> Csaba
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Newtype over (~#)

2021-02-04 Thread Edward Kmett
A similar unlifted constraint style newtype that would be very valuable to
me would be to be able to talk about unlifted implicit parameters.

type GivenFoo = (?foo :: Int#)

(hopefully properly inhabiting TYPE 'IntRep)

This would go a long way towards removing the last bit of overhead when
using implicit parameters to automatically dispatch *just* the portions of
the environment/state/etc. that you need to handle effect systems without
incurring unnecessary boxes. Right now when I work with a custom Monad I
can of course unbox the argument to by reader or state, but when I move it
into an implicit parameter to get it automatically thinned down to just
what portions of the environment I actually need, I lose that level of
expressiveness.

-Edward

On Thu, Feb 4, 2021 at 4:52 PM Igor Popov  wrote:

> Hello list!
>
> Recently I've had this idea of letting Haskell source handle unboxed
> equalities (~#) by the means of an unboxed newtype. The idea is pretty
> straightforward: in Core Constraint is Type and (=>) is (->), so a
> datatype like
>
> data Eq a b = (a ~ b) => Refl
>
> could become a newtype because it only has a single "field": (a ~ b).
> Furthermore now that we have unlifted newtypes, we could write it as a
> newtype over (~#), of kind TYPE (TupleRep []).
>
> Defining such a datatype is of course impossible in source Haskell, but
> what I came up with is declaring a plugin that magically injects the
> necessary bits into the interface file.
>
> Sounds like it should be straightforward: define a newtype (:~:#) with a
> constructor whose representation type is:
>
> forall k (a :: k) (b :: k). (a ~# b) -> a :~:# b
>
> The worker constructor is implemented by a coercion (can even be
> eta-reduced):
>
> axiom N::~:# :: forall {k}. (:~:#) = (~#)
> Refl# = \ (@ k) (@ (a :: k)) (@ (b :: k)) (v :: a ~# b) ->
>v `cast` (Sym (N::~:#) _N) _N _N
>
> And the wrapper constructor has a Haskell-ish type:
>
> $WRefl# :: forall k (b :: k). b :~:# b
> $WRefl# = \ (@ k) (@ (b :: k)) ->
>Refl# @ k @ a @ b @~ _N
>
> Caveat: we don't actually get to specify the unwrappings ourselves, and
> we have to rely on mkDataConRep generating the right wrapper based on
> the types and the EqSpec (because this will have to be done every time
> the constructor is loaded from an iface). In this case the machinery is
> not convinced that a wrapper is required, unless we ensure that
> dataConUserTyVarsArePermuted by fiddling around with ordering of
> variables. This is a minor issue (which I think I can work around) but
> could be addressed on the GHC side.
>
> I've indeed implemented a plugin that declares these, but we run into a
> more major issue: the simplifier is not ready for such code! Consider a
> simple utility function:
>
> sym# :: a :~:# b -> b :~:# a
> sym# Refl# = Refl#
>
> This gets compiled into:
>
> sym# = \ (@ k) (@ (a :: k)) (@ (b :: k)) (ds :: a :~:# b) ->
>case ds `cast` N::~:# _N _N _N of
>co -> $WRefl# @ k @ b `cast` ((:~:#) _N  (Sym co))_R
>
> which seems valid but then the simplifier incorrectly inlines the
> unfolding of $WRefl# and arrives at code that is not even well-scoped
> (-dcore-lint catches this):
>
> sym# = \ (@ k) (@ (a :: k)) (@ (b :: k)) (ds :: a :~:# b) ->
>case ds `cast` N::~:# _N _N _N of
>co -> v `cast` (Sym (N::~: _N)) _N _N
>; ((:~:#) _N _N (Sym co))_R
>
> Actually the problem manifests itself even earlier: when creating an
> unfolding for the wrapper constructor with mkCompulsoryUnfolding we run
> the unfolding term through simpleOptExpr once before memorizing the
> unfolding, and this produces an unfolding for $WRefl# that is broken
> (ill-scoped) in a similar fashion:
>
> $WRefl = \ (@ k) (@ (b :: k)) ->
>v `cast` Sym (N::~:# _N) _N _N
>
> And we can verify that the issue is localized here: applying
> simpleOptExpr to:
>
> (\ (v :: a ~# a) -> v `cast` _R)
>@~ _N
>
> results in:
>
> v
>
> The former term is closed and the latter is not.
>
> There is an invariant on mkPrimEqPred (though oddly not on
> mkReprPrimEqPred) that says that the related types must not be
> coercions (we're kind of violating this here).
>
> I have several questions here:
> - Is there a good reason for the restriction that equalities should not
>   contain other equalities?
> - Should this use case be supported? Coercions are almost first class
>   citizens in Core (are they?), makes sense to let source Haskell have a
>   bit of that?
> - Does it make sense to include this and a few similar types (unboxed
>   Coercion and Dict) as a wired in type packaged with GHC in some form?
>
> -- mniip
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: COMPLETE pragmas

2020-09-03 Thread Edward Kmett
You are my hero.

On Thu, Sep 3, 2020 at 9:22 AM Sebastian Graf  wrote:

> Hi folks,
>
> I implemented what I had in mind in
> https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3959. CI should turn
> green any hour now, so feel free to play with it if you want to.
> With the wonderful https://github.com/mpickering/ghc-artefact-nix it will
> just be `ghc-head-from 3959`.
>
> Cheers,
> Sebastian
>
> Am Di., 1. Sept. 2020 um 22:09 Uhr schrieb Joachim Breitner <
> m...@joachim-breitner.de>:
>
>> Am Dienstag, den 01.09.2020, 10:11 +0200 schrieb Sebastian Graf:
>> > > 2.) Another scenario that I'd really love to see supported with
>> > > COMPLETE pragmas is a way to use | notation with them like you can
>> > > with MINIMAL pragmas.
>> >
>> > (2) is a neat idea, but requires a GHC proposal I'm not currently
>> > willing to get into. I can also see a design discussion around
>> > allowing arbitrary "formulas" (e.g., not only what is effectively
>> > CNF).
>> >
>> > A big bonus of your design is that it's really easy to integrate into
>> > the current implementation, which is what I'd gladly do in case such
>> > a proposal would get accepted.
>>
>> in the original ticket where a COMPLETE pragma was suggested (
>> https://gitlab.haskell.org/ghc/ghc/-/issues/8779) the ability to
>> specify arbitrary boolean formulas was already present:
>>
>> “So here is what I think might work well, inspired by the new MINIMAL
>> pragma: … The syntax is essentially the same as for MINIMAL, i.e. a
>> boolean formula, with constructors and pattern synonyms as atoms. In
>> this case”
>>
>> So one _could_ say that this doesn’t need a proposal, because it would
>> just be the implementation finishing the original task ;-)
>>
>>
>> Cheers,
>> Joachim
>>
>> --
>> Joachim Breitner
>>   m...@joachim-breitner.de
>>   http://www.joachim-breitner.de/
>>
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: COMPLETE pragmas

2020-08-31 Thread Edward Kmett
I'd be over the moon with happiness if I could hang COMPLETE pragmas on
polymorphic types.

I have 3 major issues with COMPLETE as it exists.

1.) Is what is mentioned here:

Examples for me come up when trying to build a completely unboxed 'linear'
library using backpack. In the end I want/need to supply a pattern synonym
that works over, say, all the 2d vector types, extracting their elements,
but right now I just get spammed by incomplete coverage warnings.

type family Elem t :: Type
class D2 where
  _V2 :: Iso' t (Elem t, Elem t)

pattern V2 :: D2 t => Elem t -> Elem t -> t
pattern V2 a b <- (view _V2 -> (a,b)) where
  V2 a b = review _V2 (a,b)

There is no way to hang a COMPLETE pragma on that.

2.) Another scenario that I'd really love to see supported with COMPLETE
pragmas is a way to use | notation with them like you can with MINIMAL
pragmas.

If you make smart constructors for a dozen constructors in your term type
(don't judge me!), you wind up needing 2^12 COMPLETE pragmas to describe
all the ways you might mix regular and start constructors today.

{# COMPLETE (Lam | LAM), (Var | VAR), ... #-}

would let you get away with a single such definition. This comes up when
you have some kind of monoid that acts on terms and you want to push it
down through
the syntax tree invisibly to the user. Explicit substitutions, shifts in
position in response to source code edits, etc.

3.) I had one other major usecase where I failed to be able to use a
COMPLETE pragma:

type Option a = (# a | (##) #)

pattern Some :: a -> Option a
pattern Some a = (# a | #)

pattern None :: Option a
pattern None = (# | (##) #)

{-# COMPLETE Some, None #-}

These worked _within_ a module, but was forgotten across module boundaries,
which forced me to rather drastically change the module structure of a
package, but it sounds a lot like the issue being discussed. No types to
hang it on in the interface file. With the ability to define unlifted
newtypes I guess this last one is less of a concern now?

-Edward

On Mon, Aug 31, 2020 at 2:29 PM Richard Eisenberg  wrote:

> Hooray Sebastian!
>
> Somehow, I knew cluing you into this conundrum would help find a solution.
> The approach you describe sounds quite plausible.
>
> Yet: types *do* matter, of course. So, I suppose the trick is this: have
> the COMPLETE sets operate independent of types, but then use types in the
> PM-checker when determining impossible cases? And, about your idea for
> having pattern synonyms store pointers to their COMPLETE sets: I think data
> constructors can also participate. But maybe there is always at least one
> pattern synonym (which would be a reasonable restriction), so I guess you
> can look at the pattern-match as a whole and use the pattern synonym to
> find the relevant COMPLETE set(s).
>
> Thanks for taking a look!
> Richard
>
> On Aug 31, 2020, at 4:23 PM, Sebastian Graf  wrote:
>
> Hi Richard,
>
> Am Mo., 31. Aug. 2020 um 21:30 Uhr schrieb Richard Eisenberg <
> r...@richarde.dev>:
>
>> Hi Sebastian,
>>
>> I enjoyed your presentation last week at ICFP!
>>
>
> Thank you :) I'm glad you liked it!
>
> This thread (
>> https://ghc-devs.haskell.narkive.com/NXBBDXg1/suppressing-false-incomplete-pattern-matching-warnings-for-polymorphic-pattern-synonyms)
>> played out before you became so interested in pattern-match coverage. I'd
>> be curious for your thoughts there -- do you agree with the conclusions in
>> the thread?
>>
>
> I vaguely remember reading this thread. As you write there
> 
>
> And, while I know it doesn't work today, what's wrong (in theory) with
>>
>> {-# COMPLETE LL #-}
>>
>> No types! (That's a rare thing for me to extol...)
>>
>> I feel I must be missing something here.
>>
>
> Without reading the whole thread, I think that solution is very possible.
> The thread goes on to state that we currently attach COMPLETE sets to type
> constructors, but that is only an implementational thing. I asked Matt (who
> implemented it) somewhere and he said the only reason to attach it to type
> constructors was because it was the easiest way to implement serialisation
> to interface files.
>
> The thread also mentions that type-directed works better for the
> pattern-match checker. In fact I disagree; we have to thin out COMPLETE
> sets all the time anyway when new type evidence comes up, for example. It's
> quite a hassle to find all the COMPLETE sets of the type constructors a
> given type can be "represented" (I mean equality modulo type family
> reductions here) as. I'm pretty sure it's broken in multiple ways, as
> #18276  points out.
>
> Disregarding a bit of busy work for implementing serialisation to
> interface files, it's probably far simpler to give each COMPLETE set a
> Name/Unique and refer to them from the pattern synonyms that mention them
> 

Re: Question about negative Integers

2019-11-15 Thread Edward Kmett
> Question is: do we need/want to keep this behavior?

I think we really do want to keep this behavior.

And not just because I for one have a decent cross-section of code that
would just become horribly broken (and would have to find some way to
jerry-rig the existing behavior anyways) if we randomly changed it.

The current underlying representation if more directly exposed would be
quite surprising to users and doesn't at all fit the mental model of what
an Int-like thing is.

Other examples: Conor McBride's work on co-deBruijn syntax exploits the
current Bits instance heavily (and can be greatly streamlined by making
more use of it that he doesn't, quite yet.)

-Edward

On Fri, Nov 15, 2019 at 9:34 PM Sylvain Henry  wrote:

> Hi GHC devs,
>
> As some of you may know, I am working on fixing several longstanding
> issues with GHC's big numbers implementation (Integer, Natural). You can
> read more about it here:
>
> https://gitlab.haskell.org/hsyl20/ghc/raw/hsyl20-integer/libraries/ghc-bignum/docs/ghc-bignum.rst
>
> To summarize, we would have a single `ghc-bignum` package with different
> backends (GMP, pure Haskell, etc.). The backend is chosen with a Cabal
> flag and new backends are way easier to add. All the backends use the
> same representation which allows Integer and Natural types and datacons
> to be wired-in which has a lot of nice consequences (remove some
> dependency hacks in base package, make GHC agnostic of the backend used,
> etc.).
>
> A major roadblock in previous attempts was that integer-simple doesn't
> use the same representations for numbers as integer-gmp. But I have
> written a new pure Haskell implementation which happens to be faster
> than integer-simple (see perf results in the document linked above) and
> that uses the common representation (similar to what was used in
> integer-gmp).
>
> I am very close to submit a merge request but there is a remaining
> question about the Bits instance for negative Integer numbers:
>
> We don't store big negative Integer using two's complement encoding,
> instead we use signed magnitude representation (i.e. we use constructors
> to distinguish between (big) positive or negative numbers). It's already
> true today in integer-simple and integer-gmp. However integer-gmp and
> integer-simple fake two's complement encoding for Bits operations. As a
> consequence, every Bits operation on negative Integers does *a lot* of
> stuff. E.g. testing a single bit with `testBit` is linear in the size of
> the number, a logical `and` between two numbers involves additions and
> subtractions, etc.
>
> Question is: do we need/want to keep this behavior? There is nothing in
> the report that says that Integer's Bits instance has to mimic two's
> complement encoding. What's the point of slowly accessing a fake
> representation instead of the actual one? Could we deprecate this? The
> instance isn't even coherent: popCount returns the negated numbers of 1s
> in the absolute value as it can't return an infinite value.
>
> Thanks,
> Sylvain
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Why do Constraint Tuple data constructors exist?

2019-09-17 Thread Edward Kmett
I'm not sure if this is directly relevant to your issues around
GHC.Classes.(%,%), but there are some issues with using tuples for
Constraints. Namely that they can only be fully applied, and do not exist
naked as

(,) :: Constraint -> Constraint -> Constraint.

With UndecidableInstances, etc. you can fabricate a class like

class (a,b) => a & b
instance (a,b) => a & b

and then use (&) partially applied, and modulo a little bit of plumbing on
the backend.

Maybe this would be enough to unblock you?

-Edward

On Tue, Sep 17, 2019 at 9:15 AM Joe Crayne  wrote:

> My question arrised in the following context:
>
> ```
> module ForEachHelper where
>
> import Data.Kind
> import GHC.TypeLits
>
> type family ForEach (c :: k -> Constraint) (xs :: [k]) :: Constraint where
> ForEach c '[] = ()
> ForEach c (x:xs) = (c x, ForEach c xs)
>
> type family Replicate n x where
> Replicate 0 x = '[]
> Replicate n x = x : Replicate (n-1) x
>
> data ForEachHelper n c x where
> ForEachHelper :: ForEach c (Replicate n x) => ForEachHelper n c x
>
> -- The following solve function was actually in another module from the
> definitions above:
>
> solve :: ( KnownNat n, c x
>  -- Solved via plugin:
>  -- , ForEach c (Replicate n x)
>  ) => p c -> q x -> ForEachHelper n c x
> solve pc px = ForEachHelper
> ```
>
> I was trying to write a plugin that could solve the (ForEach c (Replicate
> n x)) constraint.
> I need an EvTerm that this constraint.  The first thing I tried was to use
> the given EvTerm
> for the (c x) constraint without change.  This causes the program to
> compile but ultimately
> and, perhaps not surprisingly, it segfaults when code relies upon the
> constraint.
>
> Then I decided that (ForEach c (Replicate n x)) is a constraint tuple and
> the
> proof term should be a tuple constructed using a constraint tuple data
> constructor.  However, this is apparently not possible.  When I tried the
> following code in the initialization of my plugin:
>
> cpairCon <- tcLookupDataCon (cTupleDataConName 2)
>
> it triggers an error:
>
> Can't find interface-file declaration for data constructor
> GHC.Classes.(%,%)
>
> Searching GHC source, I cannot find where or how constraint data
> constructors
> are used and notes on commit ffc21506894c7887d3620423aaf86bc6113a1071 were
> not
> helpful to me either.  Why do constraint tuple data constructor names
> exist at
> all if we cannot use them for anything?  Is it possible for a plugin to
> solve
> the (ForEach c (Replicate n x)) constraint by some other means?
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [core libraries] Re: Add taggedTrace to Debug.Trace

2018-06-07 Thread Edward Kmett
What different users would do with such a prefix, how to display it, etc. 
varies just enough that i’m somewhat hesitant to grow the API. I’m a very weak 
-1. But I’d happily let anybody else on the committee override that if they had 
a strong preference.

-Edward

> On Jun 7, 2018, at 5:40 PM, Ben Gamari  wrote:
> 
> Yuji Yamamoto  writes:
> 
>> Nice to meet you, GHC Developers!
>> I'm new to contributing to GHC.
>> 
> Hi Yuji!
> 
> Thanks for your proposal.
> 
> I think this is likely best handled by the Core Libraries Committee
> (CC'd). Let's see what they say.
> 
> 
> 
>> Today let me suggest new APIs of the Debug.Trace
>> 
>> module, named:
>> 
>>   - taggedTraceShowId :: Show a => String -> a -> a
>>   - taggedTraceWith :: (a -> String) -> String -> a -> a
>> 
>> These are inspired by Elm's Debug.log
>> 
>> function.
>> The prefix "tagged" is named after its argument
>> .
>> 
>> I mean, these new APIs prepend a string as a tag to the output by
>> traceShowId etc.
>> It helps us recognize what the printed values stand for.
>> I frequently want such functions and write them manually or copy-and-paste
>> from the Debug.TraceUtils.
>> I'm tired of that. That's why I made this suggestion.
>> 
>> *Comparison with the existing solution*
>> 
>>   - Debug.TraceUtils
>>   
>> 
>>   :
>>  - Essentially, this suggestion is to add APIs already implemented by
>>  TraceUtils.
>>  - As the document of TraceUtils suggests, we can copy and paste the
>>  functions from its source, but it's still tiresome.
>>   - Combine Debug.Trace.traceShowId with Debug.Trace.trace:
>>  - e.g. trace "Tag" $ traceShowId x
>>  - A bit hard to type.
>>  - trace always prints a newline, which makes it difficult to tell the
>>  tags from the printed value.
>> 
>> After receiving some feedback here, I'm going to submit to
>> https://github.com/ghc-proposals/ghc-proposals
>> Thanks in advance!
>> 
> 
> Personally, I do like the "With" variant as I regularly find myself
> needing things like this. I'm a bit unsure of whether we want to bake
> the "tag" notion into the interface, however.
> 
> Cheers,
> 
> - Ben
> 
> -- 
> You received this message because you are subscribed to the Google Groups 
> "haskell-core-libraries" group.
> To unsubscribe from this group and stop receiving emails from it, send an 
> email to haskell-core-libraries+unsubscr...@googlegroups.com.
> For more options, visit https://groups.google.com/d/optout.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: accuracy of asinh and atanh

2018-06-03 Thread Edward Kmett
Note: From skimming your readme it is worth noting that  log1p _is_ in base
now (alongside expm1, log1pexp, and log1mexp). We added them all a couple
of years back as a result of the very thread linked in your README.

You need to `import Numeric` to see them, though.

Switching to more accurate functions for doubles and floats for asinh,
atanh, etc. to exploit this sort of functionality at least seems to make a
lot of sense.

That can be done locally without any user API impact as the current
definitions aren't supplied as defaults, merely as pointwise
implementations instance by instance. Things will just become more accurate.

In that same spirit, we can probably crib a better version for complex
numbers from somewhere as well, as it follows the same general simplistic
formula right now, even if it can't be plugged directly into the equations
you've given. For that matter, the log1p definition we're using for complex
numbers was the best I could come up with, but there may well be a more
accurate version you can find down in the mines of libm or another math
library written by real analysts.

log1p 

x 
@(a

:+ 

b 
)
 | abs 

a 

< 0.5 && abs 

b 

< 0.5  , u 

<- 2* 
a

+ 
a 
*
a

+ 
b 
*
b

= log1p 

(u 
/
(1
+ 
sqrt 
(u
+
1)))
:+ 

atan2 

(1 + 

a 
)
b 

 | otherwise

= log 

(1 + 

x 
)


So, here's a +1 from the libraries committee side towards improving the
situation.

>From there, it's a small matter of implementation.

Here's where I'd usually get Ben involved. Hi Ben!

-Edward

On Sat, Jun 2, 2018 at 1:23 AM, Matt Peddie  wrote:

> Hi devs,
>
> I tried to use  asinh :: Double -> Double  and discovered that it's
> inaccurate compared to my system library (GNU libm), even returning
> -Infinity in place of finite values in the 

Re: User constructed types with new Data.Typeable and Data.Reflection

2018-02-10 Thread Edward Kmett
Did you mean Type.Reflection?

(reflection's Data.Reflection offers a completely unrelated notion of
Typeable reflection, hence my confusion.)

-Edward

On Sat, Feb 10, 2018 at 5:16 AM, Development  wrote:

> Hey guys I have a (hopefully quick) question.
>
> With the new `Data.Typeable` and `Data.Reflection` in base 4.10 have we
> really lost the ability for users to compose `TypeRep`’s?
>
> I was using `Data.Typeable` before (mainly `mkTyConApp`). But in the new
> base 4.10 I cannot find any way to achieve the same goal.
> I have read the wiki page Typeable and Typeable/BenGamari and neither
> explicitly mentions the removal of `mkTyConApp` and similar facilities. In
> fact the latter mentions potential implementations for user constructed
> type applications twice with `mkTrApp` at the beginning of the page and
> `mkApp` at the end.
> Furthermore the documentation for `Typeable` (and `Reflection`) also never
> mentions the fact that this functionality was removed.
>
> My question is this: Is this intentional? Is there now a consensus that
> there should not be user constructed types? Or is there some subtile issue
> that I’m missing wich prevents user constructed types for now or always?
>
> Thanks in advance guys.
>
> Best regards.
>
> Justus
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Deprecating STM invariant mechanism

2017-10-08 Thread Edward Kmett
I only have two uses of it at present and come to think of it I'm now
dubious about if they were doing anything, so I can pretty readily work
around its removal!

+1

No objection here.

-Edward

On Thu, Oct 5, 2017 at 7:02 PM, Ben Gamari  wrote:

> tl;dr. Do you use Control.Monad.STM.always? If so say so on
>this [1] proposal otherwise the interface may be removed.
>
>
> Hello everyone,
>
> GHC's STM subsystem has long had the ability to run user-specified
> invariant checks when committing transactions, embodied by the
> Control.Monad.STM.always and alwaysSucceeds functions.
>
> However, if Hackage is any indication this feature has seen very little
> use of the past ten years. In fact, it has very likely been quite broken
> (#14310) for this entire duration.
>
> Consequently, I suggest that we begin deprecating the mechanism. See
> the deprecation Proposal [1] for full details. Please leave a comment if
> you object.
>
> Cheers,
>
> - Ben
>
>
> [1] https://github.com/ghc-proposals/ghc-proposals/pull/77
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: How lose can we be with strictness

2017-05-22 Thread Edward Kmett


Sent from my iPad

> On May 20, 2017, at 1:13 PM, Joachim Breitner  
> wrote:
> 
> Hi,
> 
> yes, of course. What GHC is doing now is correct, safe and what an
> (exprienced) programmer expects. Especially if he is using `x==x` to
> deeply force x…

Well, deeply force until it runs into a Float that happens to be a NaN. ;)


___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: DeriveFoldable treatment of tuples is surprising

2017-03-21 Thread Edward Kmett
As I recall, Richard Eisenberg has been pushing, off and on, for us to get
a better vocabulary to specify "how" something is derived, via
DeriveAnyClass, generalized newtype deriving, DeriveFoldable, etc.

In general I think the current behavior is the least surprising as it
"walks all the a's it can" and is the only definition compatible with
further extension with Traversable. Right now there are no instances
provided by base that violate the "walk all the a's" intuition and there is
a fair bit of user code for things like vector types that do things like

newtype V3 a = V3 (a,a,a,a)

replacing that with a data type isn't without cost because now converting
back and forth between that and a tuple could no longer be done for zero
cost with coercions. This style of code is more common among the
ML-turned-haskeller crowd, whom -- in my experience -- tend to think of it
as just giving the constructor paren around its arguments rather than as a
tuple.

Destroying Foldable for that and making working code not work just for
users to have to manually specify multiple tedious instances that should be
easily derivable shouldn't be a thing we do lightly. DeriveFunctor doesn't
consider that functors involved may be contravariant either. DeriveFoo
generally does something that is a best effort.

I'm more inclined to leave it on the list of things that DeriveFoo does
differently than GND, and as yet another argument pushing us to find a
better vocabulary for talking about deriving.

-Edward


On Tue, Mar 21, 2017 at 5:11 PM, David Feuer  wrote:

> The point is that there are two reasonable ways to do it, and the
> deriving mechanism, as a rule, does not make choices between
> reasonable alternatives.
>
> On Tue, Mar 21, 2017 at 5:05 PM, Jake McArthur 
> wrote:
> > I think it's a question of what one considers consistent. Is it more
> > consistent to treat tuples as transparent and consider every component
> with
> > type `a`, or is it more consistent to treat tuples as opaque and reuse
> the
> > existing Foldable instance for tuples even if it might cause a compile
> time
> > error?
> >
> >
> > On Tue, Mar 21, 2017, 4:34 PM David Feuer  wrote:
> >>
> >> This seems much too weird:
> >>
> >> *> :set -XDeriveFoldable
> >> *> data Foo a = Foo ((a,a),a) deriving Foldable
> >> *> length ((1,1),1)
> >> 1
> >> *> length $ Foo ((1,1),1)
> >> 3
> >>
> >> I've opened Trac #13465 [*] for this. As I write there, I think the
> >> right thing is to refuse to derive Foldable for a type whose Foldable
> >> instance would currently fold over components of a tuple other than
> >> the last one.
> >>
> >> I could go either way on Traversable instances. One could argue that
> >> since all relevant components *must* be traversed, we should just go
> >> ahead and do that. Or one could argue that we should be consistent
> >> with Foldable and refuse to derive it.
> >>
> >> What do you all think?
> >>
> >> [*] https://ghc.haskell.org/trac/ghc/ticket/13465
> >> ___
> >> Glasgow-haskell-users mailing list
> >> glasgow-haskell-us...@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
> ___
> Glasgow-haskell-users mailing list
> glasgow-haskell-us...@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: LLVM calling convention for AVX2 and AVX512 registers

2017-03-15 Thread Edward Kmett
Currently if you try to use a DoubleX4# and don't have AVX2 turned on, it
deliberately crashes out during code generation, no? So this is very
deliberately *not* a problem with the current setup as I understand it. It
only becomes one if we reverse the decision and decide to add terribly
inefficient shims for this functionality at the primop level rather than
have a higher level make the right call to just not use functionality that
isn't present on the target platform.

-Edward


On Wed, Mar 15, 2017 at 10:27 AM, Ben Gamari  wrote:

> Siddhanathan Shanmugam  writes:
>
> >> I would be happy to advise if you would like to pick this up.
> >
> > Thanks Ben!
> >
> >> This would mean that Haskell libraries compiled with different flags
> >> would not be ABI compatible.
> >
> > Wait, can we not maintain ABI compatibility if we limit the target
> > features using a compiler flag? Sometimes (for performance reasons)
> > it's reasonable to request the compiler to only generate SSE
> > instructions, even if AVX2 is available on the target. On GCC we can
> > use the flag -msse to do just that.
> >
> I think the reasoning here is the following (please excuse the rather
> contrived example): Consider a function f with two variants,
>
> module AvxImpl where
> {-# OPTIONS_GHC -mavx #-}
> f :: DoubleX4# -> DoubleX4# -> Double
>
> module SseImpl where
> {-# OPTIONS_GHC -msse #-}
> f :: DoubleX4# -> DoubleX4# -> Double
>
> If we allow GHC to pass arguments with SIMD registers we now have a bit
> of a conundrum: The calling convention for AvxImpl.f will require that
> we pass the two arguments in YMM registers, whereas SseImpl.f will
> be via passed some other means (perhaps two pairs of XMM registers).
>
> In the C world this isn't a problem AFAIK since intrinsic types map
> directly to register classes. Consequently, I can look at a C
> declaration type,
>
> double f(__m256 x, __m256 y);
>
> and tell you precisely the calling convention that would be used. In
> GHC, however, we have an abstract vector model and therefore the calling
> convention is determined by which ISA the compiler is targetting.
>
> I really don't know how to fix this "correctly". Currently we assume
> that there is a static mapping between STG registers and machine
> registers. Giving this up sounds quite painful.
>
> Cheers,
>
> - Ben
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: LLVM calling convention for AVX2 and AVX512 registers

2017-03-14 Thread Edward Kmett
Hrmm. In C/C++ I can tell individual functions to turn on additional ISA
feature sets with compiler-specific __attribute__((target("avx2"))) tricks.
This avoids complains from the compiler when I call builtins that aren't
available at my current compilation feature level. Perhaps pragmas for the
codegen along those lines is what we'd ultimately need? Alternately, if we
simply distinguish between what the ghc codegen produces with one set of
options and what we're allowed to ask for explicitly with another then
user-land tricks like I employ would remain sound.

-Edward

On Mon, Mar 13, 2017 at 7:26 PM, Ben Gamari <b...@well-typed.com> wrote:

> Edward Kmett <ekm...@gmail.com> writes:
>
> > That, rather tangentially, reminds me: If we do start to teach the code
> > generator about how to produce these sorts of things from simpler parts,
> > e.g. via enabling something like LLVM's vectorization pass, or some
> > internal future ghc compiler pass that checks for, say, Superword-Level
> > Parallelism
> > <http://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.
> 106.4663=rep1=pdf>
> > in the style of Jaewook Shin, then we need to differentiate between flags
> > for what ghc/llvm is allowed to produce via optimization, etc. and what
> the
> > end user is allowed to explicitly emit. e.g. in my own code I can safely
> > call avx2 primitives after I set up guards to check that I'm on a CPU
> that
> > supports them, but I can only currently emit that code after I tell GHC
> > that I want it to allow the avx2 instructions. If I build a complicated
> > dispatch mechanism in Haskell for picking the right ISA and emitting code
> > for several of them, I'm going to need to tell ghc to let me build with
> all
> > sorts of instruction sets that the machine the final executable runs on
> may
> > not fully support. We should be careful not to conflate these two things.
> >
> Indeed this is tricky.
>
> The obvious stop-gap solution is to simply move your various platform
> dependent implementations into multiple modules. However, as you say
> this quickly breaks down once GHC itself starts to learn vectorisation.
> At that point you will need to draw the distinction you mention,
> separating the ISA available to the user and that available to the
> compiler.
>
> Another related question is whether you eventually want a way to specify
> an ISA per-function (via pragma, for instance). This would allow you to
> set a conservative `-march` for the module on the whole, but allow use
> of ISA extensions precisely when necessary. This is a bit tricky in the
> face of inlining; perhaps you want to require only `NOINLINE` functions
> can be decorated with such a thing.
>
> I suspect in the case of LLVM this will require breaking modules up into
> multiple compilation units and linking together the resulting objects.
> This will certainly require a fair bit of engineering effort but nothing
> terribly difficult.
>
> Regarding dispatch, GCC has a function multi-versioning mechanism [1]
> which is seems relevant to mention here. However, it's not entirely
> clear to me whether the complexity here is worthwhile for GHC.
>
> Anyways, there are plenty of possible options here; it would be helpful
> to have a feature request ticket for the "user/compiler ISA" idea you
> propose where we can collect ideas. Perhaps you could open one?
>
> Cheers,
>
> - Ben
>
>
> [1] https://lwn.net/Articles/691666/
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: LLVM calling convention for AVX2 and AVX512 registers

2017-03-13 Thread Edward Kmett
That, rather tangentially, reminds me: If we do start to teach the code
generator about how to produce these sorts of things from simpler parts,
e.g. via enabling something like LLVM's vectorization pass, or some
internal future ghc compiler pass that checks for, say, Superword-Level
Parallelism

in the style of Jaewook Shin, then we need to differentiate between flags
for what ghc/llvm is allowed to produce via optimization, etc. and what the
end user is allowed to explicitly emit. e.g. in my own code I can safely
call avx2 primitives after I set up guards to check that I'm on a CPU that
supports them, but I can only currently emit that code after I tell GHC
that I want it to allow the avx2 instructions. If I build a complicated
dispatch mechanism in Haskell for picking the right ISA and emitting code
for several of them, I'm going to need to tell ghc to let me build with all
sorts of instruction sets that the machine the final executable runs on may
not fully support. We should be careful not to conflate these two things.

-Edward

On Mon, Mar 13, 2017 at 2:44 PM, Ben Gamari  wrote:

> Siddhanathan Shanmugam  writes:
>
> >> It would be even better if we could *also* teach the native back end
> about
> > SSE instructions. Is there anyone who might be willing to work on that?
> >
> > Yes. Though, it would be better if someone with more experience than me
> > decides to pick this up instead.
> >
> I would be happy to advise if you would like to pick this up. I think it
> would be great if the NCG were to learn about SSE and GHC could really
> use more people knowledgable about its backend. The best way to learn is
> by doing.
>
> Cheers,
>
> - Ben
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: LLVM calling convention for AVX2 and AVX512 registers

2017-03-09 Thread Edward Kmett
If we only turn on ymm and zmm for passing explicit 256bit and 512bit
vector types then changing the ABI would have basically zero effect on any
code anybody is actually using today. Everything would remain abi
compatible unless it involves the new types that nobody is using.

This also has the benefit that turning on avx2 or avx512 wouldn't change
the calling convention of any code, making it much safer to link code
compiled with it on with code compiled with it off. That seems like a big
deal.

Moreover, if we start passing normal floats, etc. through them then our
lack of shuffles and ways to get data in/out of them becomes quite a pain
point.

As for passing int/word data, passing the vectors of them through the ymm
and zmm registers should be sufficient for the same reasons.

-Edward

On Thu, Mar 9, 2017 at 3:55 PM, Carter Schonwald <carter.schonw...@gmail.com
> wrote:

> zooming out:
>
> what *should* the new ABI be?
>
> Ed was suggesting we make all 16 xmm/ymm/ lower 16 zmm registers
> (depending on how they're being used) caller save,
>
> (what about all 32 zmm registers? would they be float only, or also for
> ints/words? simd has lots of nice int support!)
>
> a) if this doesn't cause any perf regressions i've no objections
>
> b) currently we only support passing floats/doubles and simd vectors of ,
> do we wanna support int/word data there too? (or are the GPR / general
> purpose registers enough for those? )
>
> c) other stuff i'm probably overlooking
>
> d) lets do this!
>
> On Thu, Mar 9, 2017 at 3:31 PM, Carter Schonwald <
> carter.schonw...@gmail.com> wrote:
>
>> the patch is still on TRAC,
>>
>> https://ghc.haskell.org/trac/ghc/ticket/8033
>>
>> we need to do changes to both the 32bit and 64bit ABIs, and I think thats
>> where I got stalled from lack of feedback
>>
>> that aside:
>>
>> heres the original email thread on the llvm commits thread
>> http://lists.llvm.org/pipermail/llvm-commits/Week-of-Mon-
>> 20130708/180264.html
>>
>> and theres links from there to the iterating on the test suite plus the
>> original patch
>>
>> i'm more than happy to take a weekend to do the leg work, it was pretty
>> fun last time.
>>
>> BUT, we need to agree on what ABI to do, and make sure that those ABI
>> changes dont create a performance regression for some unexpected reason.
>>
>> On Thu, Mar 9, 2017 at 3:11 PM, Geoffrey Mainland <mainl...@apeiron.net>
>> wrote:
>>
>>> We would need to get a patch to LLVM accepted to change the GHC calling
>>> convention.
>>>
>>> Now that we commit to a particular version of LLVM, this might be less
>>> of an issue than it once was since we wouldn't have to support versions
>>> of LLVM that didn't support the new calling convention.
>>>
>>> So...how do we get a patch into LLVM? I believe I once had such a patch
>>> ready to go...I will dig around for it, but the change is very small and
>>> easily recreated.
>>>
>>> It would be even better if we could *also* teach the native back end
>>> about SSE instructions. Is there anyone who might be willing to work on
>>> that?
>>>
>>> Geoff
>>>
>>> On 3/9/17 2:30 PM, Edward Kmett wrote:
>>> > Back around 2013, Geoff raised a discussion about fixing up the GHC
>>> > ABI so that the LLVM calling convention could pass 256 bit vector
>>> > types in YMM (and, i suppose now 512 bit vector types in ZMM).
>>> >
>>> > As I recall, this was blocked by some short term concerns about which
>>> > LLVM release was imminent or what have you. Four years on, the exact
>>> > same sort of arguments could be dredged up, but yet in the meantime
>>> > nobody is really using those types for anything.
>>> >
>>> > This still creates a pain point around trying to use these wide types
>>> > today. Spilling rather than passing them in registers adds a LOT of
>>> > overhead to any attempt to use them that virtually erases any benefit
>>> > to having them in the first place.
>>> >
>>> > I started experimenting with writing some custom primops directly in
>>> > llvm so I could do meaningful amounts of work with our SIMD vector
>>> > types by just banging out the code that we can't write in haskell
>>> > directly using llvm assembly, and hoping I could trick LLVM to do link
>>> > time optimization to perhaps inline it, but I'm basically dead in the
>>> > water over the overhead of our current calling convention, before I
>>> > even start, it seems, as if we're spilling them there is no way that
>>> > inlining / LTO could hope to figure out what we're doing out as part
>>> > of the spill to erase that call entirely.
>>> >
>>> > It is rather frustrating that I can't even cheat. =/
>>> >
>>> > What do we need to do to finally fix this?
>>> >
>>> > -Edward
>>>
>>>
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


LLVM calling convention for AVX2 and AVX512 registers

2017-03-09 Thread Edward Kmett
Back around 2013, Geoff raised a discussion about fixing up the GHC ABI so
that the LLVM calling convention could pass 256 bit vector types in YMM
(and, i suppose now 512 bit vector types in ZMM).

As I recall, this was blocked by some short term concerns about which LLVM
release was imminent or what have you. Four years on, the exact same sort
of arguments could be dredged up, but yet in the meantime nobody is really
using those types for anything.

This still creates a pain point around trying to use these wide types
today. Spilling rather than passing them in registers adds a LOT of
overhead to any attempt to use them that virtually erases any benefit to
having them in the first place.

I started experimenting with writing some custom primops directly in llvm
so I could do meaningful amounts of work with our SIMD vector types by just
banging out the code that we can't write in haskell directly using llvm
assembly, and hoping I could trick LLVM to do link time optimization to
perhaps inline it, but I'm basically dead in the water over the overhead of
our current calling convention, before I even start, it seems, as if we're
spilling them there is no way that inlining / LTO could hope to figure out
what we're doing out as part of the spill to erase that call entirely.

It is rather frustrating that I can't even cheat. =/

What do we need to do to finally fix this?

-Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Deriving Data for poly-kinded datatypes

2017-02-23 Thread Edward Kmett
That is a right mess.

I've now stepped a bit outside of what I think is a practical
recommendation, but let's just keep playing for the fun of it.

This is going to be hard to do without access to GHC at the moment but here
goes:

If phantom was of kind * then dataCast1 would need the (Data phantom), so
we need some sort of way to supply it.

Looks like we'd need some 'Data if *'. We don't have exponentials in the
type checker though. They are admissable, just not a thing GHC does today.
We could fake it with some nastiness perhaps:

class (Typeable t, Typeable k) => DataIfStar (k :: t) where
  dataIf :: (t ~ Type) => proxy k -> (Data k => r) -> r

You might be able to make a couple of overlapping instances, as much as it
pains me to consider. (Here be dragons, I haven't thought this through.

instance Data k => DataIfStar k where -- overlapping
  dataIf _ r = r

instance DataIfStar k where -- overlapped
  dataIf _ _ = undefined

Then after you check k ~ Type in the instance you could invoke dataIf using
the knowledge that k ~ Type to pull the Data phantom instance into scope.
You'd get a type signature like:

dataCast1T :: forall k c t (phantom :: k).
  (Typeable t, DataIfStar phantom)
   => (forall d. Data d => c (t d))
   -> Maybe (c (T phantom))

which would mean the Data instance for T phantom would get a constraint
like:

instance DataIfStar phantom => Data (T phantom)

Does that make sense?

-Edward




On Thu, Feb 23, 2017 at 10:30 PM, Ryan Scott <ryan.gl.sc...@gmail.com>
wrote:

> > Supplying the default shouldn't lock our data instance to the form T a.
> If for some reason adding this default would break the instance We can make
> a more interesting default that does something like look at the kind of the
> argument first to determine if it is kind * before proceeding after casting
> to ensure the kinds match.
>
> Interesting. Do you happen to know how to write this "more interesting
> default"? I've tried various things, but sadly I can't escape past the
> typechecker. My attempt that made it the furthest was this:
>
> {-# LANGUAGE GADTs #-}
> {-# LANGUAGE PolyKinds #-}
> {-# LANGUAGE RankNTypes #-}
> {-# LANGUAGE ScopedTypeVariables #-}
> {-# LANGUAGE TypeInType #-}
> {-# LANGUAGE TypeOperators #-}
> module DataCast where
>
> import Data.Data
> import Data.Kind (Type)
>
> data T (phantom :: k) = T
>
> dataCast1T :: forall k c t (phantom :: k).
>   (Typeable k, Typeable t, Typeable phantom)
>=> (forall d. Data d => c (t d))
>-> Maybe (c (T phantom))
> dataCast1T f = case eqT :: Maybe (k :~: Type) of
>  Nothing   -> Nothing
>  Just Refl -> gcast1 f
>
> This would work were it not for the constraints involved:
>
> Could not deduce (Data phantom) arising from a use of ‘f’
>
> It seems that applying f is forcing the type parameter to T (phantom)
> to be a Data instance, which obviously can't happen if (phantom :: k).
> I don't know a way around this, though, as I'm not aware of a way to
> "defer" a class constraint (unlike equality constraints, which can be
> deferred via Typeable).
>
> Ryan S.
>
> On Thu, Feb 23, 2017 at 5:49 PM, Edward Kmett <ekm...@gmail.com> wrote:
> > Some thoughts on the topic: admittedly, probably not very useful.
> >
> > A couple of obvious statements:
> >
> >
> >
> > 1)
> >
> > gcast1 itself operationally makes sense regardless of the kind of the
> > argument you're skipping past.
> >
> > gcast1 :: forall c t t' a. (Typeable t, Typeable t') => c (t a) -> Maybe
> (c
> > (t' a))
> >
> > This is an operation we can define pretty easily, however we want. It
> works
> > more or less by definition. It was included in the original paper.
> >
> >
> >
> > 2)
> >
> > dataCast1 on the other hand is an member of the class, and it needs that
> > 'Data d' constraint or it can't do its job.
> >
> > dataCast1 :: (Data a, Typeable t) => (forall d. Data d => c (t d)) ->
> Maybe
> > (c a)
> >
> > Attempting to weaken the Data d constraint there doesn't work, because
> then
> > dataCast1 wouldn't be able to do its job. Without it you can't write
> ext1Q
> > in terms of dataCast1, as noted in the but about 'bogusDataCast' in the
> > original paper: Scrap More Boilerplate: Reflection, Zips and Generalized
> > Casts
> >
> >
> >
> >
> > Since then we obviously picked up polymorphic kinds, which muddled the
> story
> > about when a data instance is 

Re: Deriving Data for poly-kinded datatypes

2017-02-23 Thread Edward Kmett
Some thoughts on the topic: admittedly, probably not very useful.

A couple of obvious statements:



1)

gcast1 itself operationally makes sense regardless of the kind of the
argument you're skipping past.

gcast1 :: forall c t t' a. (Typeable t, Typeable t') => c (t a) -> Maybe (c
(t' a))

This is an operation we can define pretty easily, however we want. It works
more or less by definition. It was included in the original paper.



2)

dataCast1 on the other hand is an member of the class, and it needs that
'Data d' constraint or it can't do its job.

dataCast1 :: (Data a, Typeable t) => (forall d. Data d => c (t d)) -> Maybe
(c a)

Attempting to weaken the Data d constraint there doesn't work, because then
dataCast1 wouldn't be able to do its job. Without it you can't write ext1Q
in terms of dataCast1, as noted in the but about 'bogusDataCast' in the
original paper: Scrap More Boilerplate: Reflection, Zips and Generalized
Casts





Since then we obviously picked up polymorphic kinds, which muddled the
story about when a data instance is for a type that looks like `T d`.

On the other hand, the user will be the one calling this method, and
they'll have to take Data instances for d and use them to generate c (t
d).  Knowledge of if argument is of kind * is purely local, though. If t is
Typeable and d is Data, then (t d), d is kind *, t :: * -> *. So to call
dataCast1, the user has to already know the argument is kind *, and that
the type t that they are trying to use (maybe not the T in the data
instance itself) is of kind * -> *.

There is no contradiction in trying to call this on a data type with the
wrong kind for it to succeed. T is not necessarily t. It is our job to
check if it is.

Supplying the default shouldn't lock our data instance to the form T a. If
for some reason adding this default would break the instance We can make a
more interesting default that does something like look at the kind of the
argument first to determine if it is kind * before proceeding after casting
to ensure the kinds match.

*tl;dr** yes, it would seem it would be worth fixing the instances of Data
produced to supply dataCast1 when the kind of the argument is polymorphic.
Otherwise turning on PolyKinds in a package will simply break dataCast1 for
basically all of its data types.*

-Edward

P.S. Ultimately, in a perfect world we'd be able to unify dataCast1 and
dataCast2 with some tricky base case for kind k1 = * and induction over k
-> k1. Off hand, I don't see how to do it. I played for a while with trying
to write a higher kinded Data to support this, but my scribbles didn't
cohere into usable code. gfoldl pretty much locks you into kind *. I even
tried playing with profunctors and powers here to no real avail. I do have
some old Data1 code in an syb-extras package that I use to write a few
'impossible' Data instances, but that seems to be solving a different, if
related, problem, and doesn't scale up to arbitrary kinds. Ideally there'd
be a plausible Data that makes sense for other kinds k, and everything
could become dataCast1, w/ dataCast2, and the missing higher versions just
an iterated application of it. I just don't see that there is a way to turn
it into code.


On Thu, Feb 23, 2017 at 2:51 PM, Ryan Scott  wrote:

> Hi Pedro,
>
> I'm quite confused by a peculiarity of deriving Data (more info in
> Trac #13327 [1]). In particular, if you write this:
>
> data T phantom = T
>   deriving Data
>
> Then the derived Data instance is NOT this:
>
> instance Typeable phantom => Data (T phantom) where
>   ...
>
> But instead, it's this:
>
> instance Data phantom => Data (T phantom) where
>   ...
>   dataCast1 f = gcast1 f
>
> The gcast1 part is why it requires the stronger (Data phantom)
> context, as you noted in Trac #4028 [2].
>
> What confuses me, however, is that is apparently does not carry over
> to poly-kinded datatypes. For instance, if you write this:
>
> data T (phantom :: k) = T
>   deriving Data
>
> Then you do NOT get this instance:
>
> instance Data (phantom :: *) => Data (T phantom) where
>   ...
>   dataCast1 f = gcast1 f
>
> But instead, you get this instance!
>
> instance (Typeable k, Typeable (phantom :: k)) => Data (T phantom)
> where
>   ...
>   -- No implementation for dataCast1
>
> This is quite surprising to me. I'm not knowledgeable enough about
> Data to know for sure if this is an oversight, expected behavior, or
> something else, so I was hoping you (or someone else highly
> knowledgeable about SYB-style generic programming) could help me out
> here.
>
> In particular:
>
> 1. Does emitting "dataCast1 f = gcast1 f" for datatypes of kind (k ->
> *) make sense? Or does it only make sense for types of kind (* -> *)?
> 2. Is there an 

Re: Superclasses

2017-02-20 Thread Edward Kmett
I'm rather incapacitated at the moment as I just got out of major surgery,
so I'm not in a good place to check particulars right now.

I can definitely say I'd like some way to attain an equivalent result, but
I accept that it may not be possible with the machinery we have.

-Edward

On Mon, Feb 20, 2017 at 10:16 AM, Simon Peyton Jones 
wrote:

> Edward
>
> In comment:23 of https://ghc.haskell.org/trac/ghc/ticket/11523 I claim
> that there is an infinite tower of superclasses, so that GHC can
> legitimately spin.
>
> You have not responded for nearly a year.
>
> Do you agree?
>
> Simon
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Magical function to support reflection

2017-01-17 Thread Edward Kmett
That is the paper the reflection library API is based on.

However, doing it the way mentioned in that paper (after modifying it to
work around changes with the inliner for modern GHC) is about 3 orders of
magnitude slower. We keep it around in reflection as the 'slow' path for
portability to non-GHC compilers, and because that variant can make a form
of Typeable reflection which is needed for some Exception gimmicks folks
use.

The current approach, and the sort of variant that David is pushing above,
is basically free, as it costs a single unsafeCoerce. To make the
reflection library work in a fully type-safe manner would take 1-3
additional wired ins that would consist of well-typed core. The stuff David
is proposing above would be more general but less safe.

-Edward

On Tue, Jan 17, 2017 at 10:45 AM, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> David says that this paper is relevant
>
> http://okmij.org/ftp/Haskell/tr-15-04.pdf
>
>
>
> Simon
>
>
>
> *From:* David Feuer [mailto:david.fe...@gmail.com]
> *Sent:* 14 January 2017 00:50
> *To:* Simon Peyton Jones <simo...@microsoft.com>
> *Cc:* ghc-devs <ghc-devs@haskell.org>; Edward Kmett <ekm...@gmail.com>
> *Subject:* RE: Magical function to support reflection
>
>
>
> I need to look through a bit more of this, but explicit type application
> certainly can be avoided using Tagged. Once we get the necessary magic,
> libraries will be able to come up with whatever interfaces they like. My
> main concern about the generality of
>
>
>
> reify# :: forall r. (RC a => r) -> a -> r
>
>
>
> (as with the primop type Edward came up with) is that it lacks the `forall
> s` safety mechanism of the reflection library. Along with its key role in
> ensuring class coherence[*], that mechanism also makes it clear what
> specialization is and is not allowed to do with reified values. Again, I'm
> not sure it can mess up the simpler/more general form you and Edward
> propose, but it makes me nervous.
>
>
>
> [*] Coherence: as long as an instance of Reifies S A exists for some
> concrete S::K, users can't incoherently write a polymorphic Reifies
> instance for s::K.
>
>
>
> On Jan 13, 2017 7:33 PM, "Simon Peyton Jones" <simo...@microsoft.com>
> wrote:
>
> David, Edward
>
> Here’s my take on this thread about reflection.   I’ll ignore Tagged and
> the ‘s’ parameter, and the proxy arguments, since they are incidental.
>
> I can finally see a reasonable path; I think there’s a potential GHC
> proposal here.
>
> Simon
>
>
>
> *First thing*: PLEASE let's give a Core rendering of whatever is
> proposed. If it's expressible in Core that's reassuring.  If it requires an
> extension to Core, that's a whole different thing.
>
>
>
> *Second*.  For any *particular* class, I think it's easy to express reify
> in Core.  Example (in Core):
>
> reifyTypeable :: (Typeable a => b) -> TypeRep a -> b
>
> reifyTypable k = k |> co
>
> where co is a coercion that witnesses
>
>   co :: (forall a b. Typeable a => b) ~ forall a b. (TypeRep a -> b)
>
>
>
> *Third.  *This does not depend, and should not depend, on the fact that
> single-method classes are represented with a newtype.  E.g. if we changed
> Typeable to be represented with a data type thus (in Core)
>
> data Typeable a = MkTypeable (TypeRep a)
>
> using data rather than newtype, then we could still write reifyTypable.
>
> reifyTypeable :: (Typeable a => b) -> TypeRep a -> b
>
> reifyTypable = /\ab. \(f :: Typeable a => b). \(r :: TypeRep a).
>
>f (MkTypeable r)
>
> The efficiency of newtype is nice, but it’s not essential.
>
>
>
> *Fourth*.   As you point out, reify# is far too polymorphic. *Clearly you
> need reify# to be a class method!*  Something like this
>
> class Reifiable a where
>
>   type RC a :: Constraint  -- Short for Reified Constraint
>
>   reify# :: forall r. (RC a => r) -> a -> r
>
> Now (in Core at least) we can make instances
>
> instance Reifiable (TypeRep a) where
>
>   type RC (TypeRep a) = Typeable a
>
>   reify# k = k |> co  -- For a suitable co
>
> Now, we can’t write those instances in Haskell, but we could make the
> ‘deriving’ mechanism deal with it, thus:
>
> deriving instance Reifiable (Typeable a)
>
> You can supply a ‘where’ part if you like, but if you don’t GHC will fill
> in the implementation for you.  It’ll check that Typeable is a
> single-method class; produce a suitable implementation (in Core, as above)
> for reify#, and a suitable instance for RC. Pretty simple.   Now the solver
> can use those instances.
>
> There ar

Re: Github repos for boot libraries

2017-01-02 Thread Edward Kmett
For reference, the master repository for transformers is at

http://hub.darcs.net/ross/transformers

We should probably edit the 'website' link for that github repository to at
least point there.

I don't have access to do so, however.

Subtly pinging Herbert, by adding him here. =)

-Edward

On Mon, Jan 2, 2017 at 1:45 PM, Erik de Castro Lopo 
wrote:

> Hi all,
>
> Currently if I go to the Github mirror for a boot library like
> transformers:
>
> https://github.com/ghc/packages-transformers
>
> I see the text:
>
> Mirror of packages-transformers repository. DO NOT SUBMIT PULL
> REQUESTS HERE
>
> This may well be true, but it is far less that useful, because although it
> tells me I can't submit I pull request, It doesn't tell me what I should do
> to get my issue addressed.
>
> Would it be possible to get these messages updated for all of these
> mirrored
> repos?
>
> Thanks,
> Erik
> --
> --
> Erik de Castro Lopo
> http://www.mega-nerd.com/
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Magical function to support reflection

2016-12-23 Thread Edward Kmett
I wasn't referring to Tagged itself being evil. I was referring to giving
an excessively general type to reify# that can be used to generate
segfaults as being evil.

The existing reify combinator doesn't have that property, but can't be used
to build KnownNat and KnownSymbol dictionaries. (Hence why there are
specialized combinators for those in reflection.)

-Edward

On Thu, Dec 22, 2016 at 6:55 PM, David Feuer <david.fe...@gmail.com> wrote:

> On Thu, Dec 22, 2016 at 4:58 PM, Edward Kmett <ekm...@gmail.com> wrote:
> > On Mon, Dec 12, 2016 at 1:31 PM, David Feuer <david.fe...@gmail.com>
> wrote:
> >>
> >> On Dec 12, 2016 1:15 PM, "Edward Kmett" <ekm...@gmail.com> wrote:
> >>
> >> A few thoughts in no particular order:
> >>
> >> Unlike this proposal, the existing 'reify' itself as core can actually
> be
> >> made well typed.
> >>
> >>
> >> Can you explain this?
> >
> > I mean just that. If you look at the core generated by the existing
> 'reify'
> > combinator, nothing it does is 'evil'. We're allowing it to construct a
> > dictionary. That isn't unsound where core is concerned.
>
> So what *is* evil about my Tagged approach? Or do you just mean that
> the excessive polymorphism is evil? There's no doubt that it is, but
> the only ways I see to avoid it are to bake in a particular Reifies
> class, which is a different kind of evil, or to come up with a way to
> express the constraint that the class has exactly one method, which is
> Extreme Overkill.
>
> > Where the surface language is concerned the uniqueness of that
> dictionary is
> > preserved by the quantifier introducing a new type generatively in the
> local
> > context, so the usual problems with dictionary construction are defused.
>
> >>  On the other other hand, if you're going to be magic, you might as well
> >> go all the way to something like:
> >>
> >> reify# :: (p => r) -> a -> r
> >>
> >>
> >> How would we implement reify in terms of this variant?
> >
> > That I don't have the answer to. It seems like it should work though.
>
> I think it does. I've changed the reify# type a bit to avoid an
> ambiguity I couldn't resolve.
>
> newtype Constrain p r = Constrain (p => r)
>
> reify# :: Constrain p r -> a -> r
>
> Using my Tagged definition of Reifies, we get
>
> reify' :: forall a r . (forall s . Reifies s a => Tagged s r) -> a -> r
> reify' f = reify# (Constrain (unTagged (f :: Tagged s r)) :: forall s
> . Constrain (Reifies s a) r)
>
> reify :: forall a r . a -> (forall s . Reifies s a => Proxy s -> r) -> r
> reify a f = reify# (Constrain (f (Proxy :: Proxy s)) :: forall s .
> Constrain (Reifies s a) r) a
>
> Using your proxy version, things are trickier, but I think it's
>
> reify :: forall a r . a -> (forall s . Reifies s a => Proxy s -> r) -> r
> reify a f = (reify# (Constrain (f (Proxy :: Proxy s)) :: forall s .
> Constrain (Reifies s a) r)) (const a :: forall proxy s . proxy s -> a)
>
> David
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Magical function to support reflection

2016-12-22 Thread Edward Kmett
On Mon, Dec 12, 2016 at 1:31 PM, David Feuer <david.fe...@gmail.com> wrote:

> On Dec 12, 2016 1:15 PM, "Edward Kmett" <ekm...@gmail.com> wrote:
>
> A few thoughts in no particular order:
>
> Unlike this proposal, the existing 'reify' itself as core can actually be
> made well typed.
>
>
> Can you explain this?
>

I mean just that. If you look at the core generated by the existing 'reify'
combinator, nothing it does is 'evil'. We're allowing it to construct a
dictionary. That isn't unsound where core is concerned.

Where the surface language is concerned the uniqueness of that dictionary
is preserved by the quantifier introducing a new type generatively in the
local context, so the usual problems with dictionary construction are
defused.

Tagged in the example could be replaced with explicit type application if
> backwards compatibility isn't a concern. OTOH, it is.
>
>
> Would that help Core typing?
>

It doesn't make a difference there. The only thing is it avoids needing to
make up something like Tagged.

>
>  On the other other hand, if you're going to be magic, you might as well
> go all the way to something like:
>
> reify# :: (p => r) -> a -> r
>
>
> How would we implement reify in terms of this variant?
>

That I don't have the answer to. It seems like it should work though.

and admit both fundep and TF forms. I mean, if you're going to lie you
> might as well lie big.
>
>
> Definitely.
>


> There are a very large number of instances out there scattered across
> dozens of packages that would be broken by switching from Proxy to Tagged
> or explicit type application internally. (I realize that this is a lesser
> concern that can be resolved by a major version bump and some community
> friction, but it does mean pragmatically that migrating to something like
> this would need a plan.)
>
>
> I just want to make sure that we do what we need to get Really Good Code,
> if we're going to the trouble of adding compiler support.
>

That makes sense to me.

-Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Retro-Haskell: can we get seq somewhat under control?

2016-12-21 Thread Edward Kmett
Actually, if you go back to the original form of Seq it would translate to

data Seq a => Foo a = Foo !Int !a

which requires resurrecting DatatypeContexts, and not

data Foo a = Seq a => Foo !Int !a

The former requires Seq to call the constructor, but doesn't pack the
dictionary into the constructor. The latter lets you get the dictionary out
when you pattern match on it. meaning it has to carry the dictionary around!

Unfortunately, non-trivial functionality is lost. With the old
DatatypeContext translation you can't always unpack and repack a
constructor. Whereas with a change to an existential encoding you're
carrying around a lot of dictionaries in precisely the structures that
least want to carry extra weight.

Both of these options suck relative to the status quo for different reasons.

-Edward

On Wed, Dec 21, 2016 at 2:14 PM, Index Int  wrote:

> There's a related GHC Proposal:
> https://github.com/ghc-proposals/ghc-proposals/pull/27
>
> On Wed, Dec 21, 2016 at 10:04 PM, David Feuer 
> wrote:
> > In the Old Days (some time before Haskell 98), `seq` wasn't fully
> > polymorphic. It could only be applied to instances of a certain class.
> > I don't know the name that class had, but let's say Seq. Apparently,
> > some people didn't like that, and now it's gone. I'd love to be able
> > to turn on a language extension, use an alternate Prelude, and get it
> > back. I'm not ready to put up a full-scale proposal yet; I'm hoping
> > some people may have suggestions for details. Some thoughts:
> >
> > 1. Why do you want that crazy thing, David?
> >
> > When implementing general-purpose lazy data structures, a *lot* of
> > things need to be done strictly for efficiency. Often, the easiest way
> > to do this is using either bang patterns or strict data constructors.
> > Care is necessary to only ever force pieces of the data structure, and
> > not the polymorphic data a user has stored in it.
> >
> > 2. Why does it need GHC support?
> >
> > It would certainly be possible to write alternative versions of `seq`,
> > `$!`, and `evaluate` to use a user-supplied Seq class. It should even
> > be possible to deal with strict data constructors by hand or
> > (probably) using Template Haskell. For instance,
> >
> > data Foo a = Foo !Int !a
> >
> > would translate to normal GHC Haskell as
> >
> > data Foo a = Seq a => Foo !Int !a
> >
> > But only GHC can extend this to bang patterns, deal with the
> > interactions with coercions, and optimize it thoroughly.
> >
> > 3. How does Seq interact with coercions and roles?
> >
> > I believe we'd probably want a special rule that
> >
> > (Seq a, Coercible a b) => Seq b
> >
> > Thanks to this rule, a Seq constraint on a type variable shouldn't
> > prevent it from having a representational role.
> >
> > The downside of this rule is that if something *can* be forced, but we
> > don't *want* it to be, then we have to hide it a little more carefully
> > than we might like. This shouldn't be too hard, however, using a
> > newtype defined in a separate module that exports a pattern synonym
> > instead of a constructor, to hide the coercibility.
> >
> > 4. Optimize? What?
> >
> > Nobody wants Seq constraints blocking up specialization. Today, a
> function
> >
> > foo :: (Seq a, Foldable f) => f a -> ()
> >
> > won't specialize to the Foldable instance if the Seq instance is
> > unknown. This is lousy. Furthermore, all Seq instances are the same.
> > The RTS doesn't actually need a dictionary to force something to WHNF.
> > The situation is somewhat similar to that of Coercible, *but more so*.
> > Coercible sometimes needs to pass evidence at runtime to maintain type
> > safety. But Seq carries no type safety hazard whatsoever--when
> > compiling in "production mode", we can just *assume* that Seq evidence
> > is valid, and erase it immediately after type checking; the worst
> > thing that could possibly happen is that someone will force a function
> > and get weird semantics. Further, we should *unconditionally* erase
> > Seq evidence from datatypes; this is necessary to maintain
> > compatibility with the usual data representations. I don't know if
> > this unconditional erasure could cause "laziness safety" issues, but
> > the system would be essentially unusable without it.
> >
> > 4. What would the language extension do, exactly?
> >
> > a. Automatically satisfy Seq for data types and families.
> > b. Propagate Seq constraints using the usual rules and the special
> > Coercible rule.
> > c. Modify the translation of strict fields to add Seq constraints as
> required.
> >
> > David Feuer
> > ___
> > ghc-devs mailing list
> > ghc-devs@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>

Re: Help needed: Restrictions of proc-notation with RebindableSyntax

2016-12-21 Thread Edward Kmett
The S parser I was referring to was based on tracking FIRST sets, and
provided a nice linear time parsing bound for (infinite) LL(1) grammars.
(You can't really compute FOLLOW sets without knowing the grammar has a
finite number of productions, but FIRST sets work perfectly well with
infinite grammars.) By doing so you can transform parsing into more or less
a series of map lookups for dispatch.

You need to carry a set of all characters that a parser will consume in the
case of legal parses, and whether or not the parser accepts the empty
parse. http://www.cse.chalmers.se/~rjmh/afp-arrows.pdf mentions this style
of FIRST-set tracking parser as the original motivation for arrows.

Of course, they didn't see fit to stop puttering around with parsers after
1998, so referring to "the S parser" is quite ambiguous! =)

-Edward

On Wed, Dec 21, 2016 at 4:00 AM, Henrik Nilsson <
henrik.nils...@nottingham.ac.uk> wrote:

> Hi Edward,
> CC Others,
>
> On 12/21/2016 05:15 AM, Edward Kmett wrote:
>
>> Arrows haven't seen much love for a while. In part this is because many
>> of the original applications for arrows have been shown to be perfectly
>> suited to being handled by Applicatives. e.g. the Swiestra/Duponcheel
>> parser that sort of kickstarted everything.
>>
>
> Thanks for a very thorough reply.
>
> A quick side-remark: a parser library due to Sweistra (and maybe
> Dupncheel, I can't remember) used an applicative structure a long time
> before applicatives became apkicatives and even idioms. (I used a
> variation of this library myself for the Freja compiler around 1995.
> Freja was part of my PhD work and was close to what Haskell looked like at
> the time.)
>
> I've never used arrows for parsing, or seen the need for arrows in that
> context, but find arrows a very good fit for many EDSLs, including
> stream-processing/FRP/Yampa of course, along with other circuit-like
> abstractions, which I'd say were the original motivation for arrows.
> Altenkirch have also used arrow-like notions in the context of quantum
> computation. More recently for probabilistic programming and
> Bayesian inference. Except then that the current hard-wired "pseudo-
> product" in particular often gets in the way. Along with the fact
> that there is no good support for constrained arrows (or monads).
>
> Best,
>
> /Henrik
>
>
>
>
>
> This message and any attachment are intended solely for the addressee
> and may contain confidential information. If you have received this
> message in error, please send it back to me, and immediately delete it.
> Please do not use, copy or disclose the information contained in this
> message or in any attachment.  Any views or opinions expressed by the
> author of this email do not necessarily reflect the views of the
> University of Nottingham.
>
> This message has been checked for viruses but the contents of an
> attachment may still contain software viruses which could damage your
> computer system, you are advised to perform your own checks. Email
> communications with the University of Nottingham may be monitored as
> permitted by UK legislation.
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Help needed: Restrictions of proc-notation with RebindableSyntax

2016-12-20 Thread Edward Kmett
Arrows haven't seen much love for a while. In part this is because many of
the original applications for arrows have been shown to be perfectly suited
to being handled by Applicatives. e.g. the Swiestra/Duponcheel parser that
sort of kickstarted everything.

There are several options for improved arrow desugaring.

Megacz's work on GArrows at first feels like it should be applicable here,
as it lets you change out the choice of pseudo-product while preserving the
general arrow feel. Unfortunately, the GArrow class isn't sufficient for
most arrow desguaring, due to the fact that the arrow desugaring inherently
involves breaking apart patterns for almost any non-trivial use and nothing
really requires the GArrow 'product' to actually even be product like.

Cale Gibbard and Ryan Trinkle on the other hand like to use a more CCC-like
basis for arrows. This stays in the spirit to the GArrow class, but you
still have the problems around pattern matching. I don't think they
actually wrote anything to deal with the actual arrow notation and just
programmed in the alternate style to get better introspection on the
operations involved. I think the key insight there is that much of the
notation can be made to work with weaker categorical structures than full
arrows, but the existing class hierarchy around arrows is very coarse.

As a minor data point both of these sorts of encodings of arrow problems
start to drag in language extensions that make the notation harder to
standardize. Currently they work with bog standard Haskell 98/2010.

If you're looking for an interesting theoretical direction to extend Arrow
notation:

An arrow is a strong monad in the category of profunctors [1].

Using the profunctors library [2] (Strong p, Category p) is equivalent in
power to Arrow p.

Exploiting that, a profunctor-based desugaring could get away with much
weaker constraints than Arrow depending on how much of proc notation you
use.

Alternately a separate class hierarchy that only required covariance in the
second argument is an option, but my vague recollection from the last time
that I looked into this is that while such a desguaring only uses
covariance in the second argument of the profunctor, you can prove that
contravariance in the first argument follows from the pile of laws. This
subject came up the last time someone thought to extend the Arrow
desguaring. You can probably find a thread on the mailing list from Ross
Paterson a few years ago.

This version has the benefit of fitting pretty close to the existing arrow
desugaring and not needing new language extensions.

On the other hand, refactoring the Arrow class in this (or any other) way
is somewhat of an invasive exercise. The profunctors package offers moral
equivalents to most of the Arrow subclasses, but no effort has been made to
match the existing Arrow hierarchy.

Given that little new code seems to be being written with Arrows in mind,
while some older code makes heavy use of it (hxt, etc.), refactoring the
arrow hierarchy is kind of a hard sell. It is by no means impossible, just
something that would require a fair bit of community wrangling and a lot of
work showing clear advantages to a new status quo at a time when its very
hard to get anybody to care about arrow notation at all.

-Edward

[1] http://www-kb.is.s.u-tokyo.ac.jp/~asada/papers/arrStrMnd.pdf
[2]
http://hackage.haskell.org/package/profunctors-5.2/docs/Data-Profunctor-Strong.html

On Fri, Dec 2, 2016 at 10:57 AM, Jan Bracker via ghc-devs <
ghc-devs@haskell.org> wrote:

> Simon, Richard,
>
> thank you for your answer! I don't have time to look into the GHC sources
> right now, but I will set aside some time after the holidays and take a
> close look at what the exact restrictions on proc-notation are and document
> them.
>
> Since you suggested a rewrite of GHC's handling of proc-syntax, are there
> any opinions on integrating generalized arrows (Joseph 2014) in the
> process? I think they would greatly improve arrows! I don't know if I have
> the time to attempt this, but if I find the time I would give it a try. Why
> wasn't this integrated while it was still actively developed?
>
> Best,
> Jan
>
> [Joseph 2014] https://www2.eecs.berkeley.edu/Pubs/TechRpts/2014/
> EECS-2014-130.pdf
>
>
>
> 2016-11-29 12:41 GMT+00:00 Simon Peyton Jones :
>
>> Jan,
>>
>>
>>
>> Type checking and desugaring for arrow syntax has received Absolutely No
>> Love for several years.  I do not understand how it works very well, and I
>> would not be at all surprised if it is broken in corner cases.
>>
>>
>>
>> It really needs someone to look at it carefully, document it better, and
>> perhaps refactor it – esp by using a different data type rather than
>> piggy-backing on HsExpr.
>>
>>
>>
>> In the light of that understanding, I think rebindable syntax will be
>> easier.
>>
>>
>>
>> I don’t know if you are up for that, but it’s a rather un-tended part of
>> GHC.
>>
>>
>>
>> Thanks
>>
>>
>>
>> Simon

Re: Allow top-level shadowing for imported names?

2016-10-04 Thread Edward Kmett
I for one would really like to see this go in. (I've commiserated with
Lennart in the past about the fact that the previous proposal just sort of
died.)

It makes additions of names to libraries far less brittle. You can add a
new export with a mere minor version bump, and many of the situations where
that causes breakage can be fixed by this simple rule change.

-Edward

On Mon, Oct 3, 2016 at 2:12 PM, Iavor Diatchki 
wrote:

> Hi,
>
> Lennart suggested that some time ago, here is the thread from the last
> time we discussed it:
>
> https://mail.haskell.org/pipermail/haskell-prime/2012-July/003702.html
>
> I think it is a good plan!
>
> -Iavor
>
>
>
> On Mon, Oct 3, 2016 at 4:46 AM, Richard Eisenberg 
> wrote:
>
>> By all means make the proposal -- I like this idea.
>>
>> > On Oct 3, 2016, at 4:29 AM, Herbert Valerio Riedel 
>> wrote:
>> >
>> > Hi *,
>> >
>> > I seem to recall this was already suggested in the past, but I can't
>> > seem to find it in the archives. For simplicity I'll restate the idea:
>> >
>> >
>> >foo :: Int -> Int -> (Int,Int)
>> >foo x y = (bar x, bar y)
>> >  where
>> >bar x = x+x
>> >
>> > results merely in a name-shadowing warning (for -Wall):
>> >
>> >foo.hs:4:9: warning: [-Wname-shadowing]
>> >This binding for ‘x’ shadows the existing binding
>> >  bound at foo.hs:2:5
>> >
>> >
>> > However,
>> >
>> >import Data.Monoid
>> >
>> >(<>) :: String -> String -> String
>> >(<>) = (++)
>> >
>> >main :: IO ()
>> >main = putStrLn ("Hi" <> "There")
>> >
>> > doesn't allow to shadow (<>), but rather complains about ambiguity:
>> >
>> >bar.hs:7:23: error:
>> >Ambiguous occurrence ‘<>’
>> >It could refer to either ‘Data.Monoid.<>’,
>> > imported from ‘Data.Monoid’ at
>> bar.hs:1:1-18
>> >  or ‘Main.<>’, defined at bar.hs:4:1
>> >
>> >
>> > This is of course in line with the Haskell Report, which says in
>> > https://www.haskell.org/onlinereport/haskell2010/haskellch5.
>> html#x11-1010005.3
>> >
>> > | The entities exported by a module may be brought into scope in another
>> > | module with an import declaration at the beginning of the module. The
>> > | import declaration names the module to be imported and optionally
>> > | specifies the entities to be imported. A single module may be imported
>> > | by more than one import declaration. Imported names serve as top level
>> > | declarations: they scope over the entire body of the module but may be
>> > | shadowed by *local non-top-level bindings.*
>> >
>> >
>> > However, why don't we allow this to be relaxed via a new language
>> > extensions, to allow top-level bindings to shadow imported names (and
>> > of course emit a warning)?
>> >
>> > Unless I'm missing something, this would help to keep existing and
>> > working code compiling if new versions of libraries start exporting new
>> > symbols (which happen to clash with local top-level defs), rather than
>> > resulting in a fatal name-clash; and have no major downsides.
>> >
>> > If this sounds like a good idea, I'll happily promote this into a proper
>> > proposal over at https://github.com/ghc-proposals/ghc-proposals; I
>> > mostly wanted to get early feedback here (and possibly find out if and
>> > where this was proposed before), before investing more time turning
>> > this into a fully fledged GHC proposal.
>> >
>> > Cheers,
>> >  HVR
>> > ___
>> > ghc-devs mailing list
>> > ghc-devs@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Is Safe Haskell intended to allow segfaults?

2016-08-12 Thread Edward Kmett
What about consuming Storable Vectors carefully, or simply working
parameterized over vector type, where Storable vectors are one of the
options?

-Edward

On Fri, Aug 12, 2016 at 12:58 PM, Ryan Newton <rrnew...@gmail.com> wrote:

> Yes, it is peek and poke that are dangerous.  It was Foreign.Storable that
> I wanted to mark as Unsafe.
>
> But we do sometimes run into examples where there's an A and a B, and if
> you import both, you can make A+B which blows up.  So preventing access to
> A+B may mean arbitrarily marking one or the other (or both) as Unsafe.
>
> What I was hoping for examples of are modules you have that are Safe and
> import Foreign.Storable.
>
>
>
>
> On Fri, Aug 12, 2016 at 9:49 AM, Edward Kmett <ekm...@gmail.com> wrote:
>
>> As for a sample list of modules, let's just start with your very first
>> example, Foreign.Ptr:
>>
>> In and of itself nothing in Foreign.Ptr is unsafe! It allows a bit of
>> arithmetic on a type you can't actually use with anything, and provides an
>> IO action mixed into an otherwise pure module that happens to create a
>> FunPtr slot from a haskell function. In fact this module is a textbook
>> example of an otherwise perfectly cromulent Trustworthy module today that
>> happens to have a single IO action in it.
>>
>> I can grab Ptr from it, use its Storable instance to make a default
>> signature for other safe code and still be perfectly safe.
>>
>> It gives no tools for manipulating the contents of the Ptr. It is no more
>> dangerous than an Int with a phantom type argument.
>>
>> You could randomly declare that this module is Unsafe because it combines
>> badly with APIs that would be safe if you could rely on any Ptr T actually
>> pointing to a T, and that users could then be granted the power to ferry
>> them around, but we don't trust a user to be able to do that today.
>>
>> It's the combinators that read/write to a Ptr are the dangerous bits, not
>> pure math.
>>
>> -Edward
>>
>>
>> On Wed, Aug 10, 2016 at 10:23 AM, Ryan Newton <rrnew...@gmail.com> wrote:
>>
>>> Hi Edward,
>>>
>>> On Tue, Aug 9, 2016 at 11:58 PM, Edward Kmett <ekm...@gmail.com> wrote:
>>>>
>>>> 1.) If you remove IO from being able to be compiled inside Safe code
>>>> _at all_ most packages I have that bother to expose Safe information will
>>>> have to stop bothering.
>>>>
>>>
>>> I definitely wouldn't argue for removing it entirely.  But it's good to
>>> know that there are instances where IO functions get mixed up in safe
>>> modules.  I'll try to systematically find all of these on hackage, but in
>>> the meantime do you have a sample list of modules?
>>>
>>> My modest starting proposal is marking certain Foreign.* modules as
>>> Unsafe rather than Trustworthy.  We'll find all the modules affected.  But,
>>> again, are there any modules you know of offhand that are affected?  They
>>> should fall into two categories:
>>>
>>>1. Safe modules that must become Trustworthy (if they import Foreign
>>>bits, but don't expose the ability to corrupt memory to the clients of
>>>their APIs).
>>>2. Safe modules that must become Unsafe or be split further into
>>>smaller modules.
>>>
>>> Obviously (2) is the biggest source of potential disruption.
>>>
>>> I wouldn't ask anyone to accept a patch on GHC until we'd explored these
>>> impacts pretty thoroughly.
>>>
>>> I'd have to cut up too many APIs into too many fine-grained pieces.
>>>>
>>>
>>> Yeah, the module-level business is pretty annoying.  "vector' removed
>>> ".Safe" modules and no one has gotten around to adding the ".Unsafe".
>>>
>>>
>>>> 2.) Assuming instead that you're talking about a stronger-than-Safe
>>>> additional language extension, say ReallySafe or SafeIO, it all comes down
>>>> to what the user is allowed to do in IO, doesn't it? What effects are users
>>>> granted access to? We don't have a very fine-grained system for IO-effect
>>>> management, and it seems pretty much any choice you pick for what to put in
>>>> the sandbox will be wrong for some users, so you'd need some sort of pragma
>>>> for each IO operation saying what bins it falls into and to track that
>>>> while type checking, etc.
>>>>
>>>
>>> Well, *maybe* it is a slippery slope that leads to a full effect
&g

Re: Is Safe Haskell intended to allow segfaults?

2016-08-12 Thread Edward Kmett
As for a sample list of modules, let's just start with your very first
example, Foreign.Ptr:

In and of itself nothing in Foreign.Ptr is unsafe! It allows a bit of
arithmetic on a type you can't actually use with anything, and provides an
IO action mixed into an otherwise pure module that happens to create a
FunPtr slot from a haskell function. In fact this module is a textbook
example of an otherwise perfectly cromulent Trustworthy module today that
happens to have a single IO action in it.

I can grab Ptr from it, use its Storable instance to make a default
signature for other safe code and still be perfectly safe.

It gives no tools for manipulating the contents of the Ptr. It is no more
dangerous than an Int with a phantom type argument.

You could randomly declare that this module is Unsafe because it combines
badly with APIs that would be safe if you could rely on any Ptr T actually
pointing to a T, and that users could then be granted the power to ferry
them around, but we don't trust a user to be able to do that today.

It's the combinators that read/write to a Ptr are the dangerous bits, not
pure math.

-Edward


On Wed, Aug 10, 2016 at 10:23 AM, Ryan Newton <rrnew...@gmail.com> wrote:

> Hi Edward,
>
> On Tue, Aug 9, 2016 at 11:58 PM, Edward Kmett <ekm...@gmail.com> wrote:
>>
>> 1.) If you remove IO from being able to be compiled inside Safe code _at
>> all_ most packages I have that bother to expose Safe information will have
>> to stop bothering.
>>
>
> I definitely wouldn't argue for removing it entirely.  But it's good to
> know that there are instances where IO functions get mixed up in safe
> modules.  I'll try to systematically find all of these on hackage, but in
> the meantime do you have a sample list of modules?
>
> My modest starting proposal is marking certain Foreign.* modules as Unsafe
> rather than Trustworthy.  We'll find all the modules affected.  But, again,
> are there any modules you know of offhand that are affected?  They should
> fall into two categories:
>
>1. Safe modules that must become Trustworthy (if they import Foreign
>bits, but don't expose the ability to corrupt memory to the clients of
>their APIs).
>2. Safe modules that must become Unsafe or be split further into
>smaller modules.
>
> Obviously (2) is the biggest source of potential disruption.
>
> I wouldn't ask anyone to accept a patch on GHC until we'd explored these
> impacts pretty thoroughly.
>
> I'd have to cut up too many APIs into too many fine-grained pieces.
>>
>
> Yeah, the module-level business is pretty annoying.  "vector' removed
> ".Safe" modules and no one has gotten around to adding the ".Unsafe".
>
>
>> 2.) Assuming instead that you're talking about a stronger-than-Safe
>> additional language extension, say ReallySafe or SafeIO, it all comes down
>> to what the user is allowed to do in IO, doesn't it? What effects are users
>> granted access to? We don't have a very fine-grained system for IO-effect
>> management, and it seems pretty much any choice you pick for what to put in
>> the sandbox will be wrong for some users, so you'd need some sort of pragma
>> for each IO operation saying what bins it falls into and to track that
>> while type checking, etc.
>>
>
> Well, *maybe* it is a slippery slope that leads to a full effect system.
> But I'd like to see these issues enumerated.  Does memory safety as a goal
> really involve so many different effects?  Do you think there will be 1, 3,
> 10, or 100 things beyond Foreign.Ptr to worry about?
>
> 3.) On the other hand, someone could _build_ an effect system in Haskell
>> that happens to sit on top of IO, holding effects in an HList, undischarged
>> nullary class constraint, etc.
>>
>
> Well, sure, I hope we will continue to aim for this as well.  This is
> effectively what we do with our "LVish" Par monad, where we use Safe
> Haskell to ensure users cannot break the effect system in -XSafe code.
>
> Best,
>  -Ryan
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: enumFromThenTo for Doubles

2016-08-11 Thread Edward Kmett
Good catch. Adding and subtracting over and over relying on massive
cancellation over and over is a recipe for floating point disaster!

That said, so is adding small things to a large thing over and over, you'll
accumulate the rounding error from the addition of small numbers to the
large base.

An even better fix would be then to track the base and the current
accumulated total delta from the base and do a final addition at the end.
Then you only ever add like sized step sizes together before adding them to
the base. This would stage the additions such that you get another matissa
sized window of possible accumulation.

Something like:

enumFromThen n m = go (n - m) n 0 where
  go !d !b !a = db `seq` db : go d b (a + d) where
db = d + b

which probably beats Kahan in practice, Kahan-Babuška-Neumaier should be
more stable still, and there are other techniques that go further into
accuracy at the cost of significant performance.

But we don't need a general number summation algorithm. All the numbers
except the base are the same, we have a final hammer available to us: just
do multiplication of the delta by the number of steps and add it to the
base.

That should be the most numerically stable thing possible, given that we
are forced to do at least the first massive cancellation between the from
and then steps by the API we have to meet, but I don't have benchmarks to
say which technique wins in practice.

-Edward

On Tue, Aug 9, 2016 at 11:22 PM, Andrew Farmer  wrote:

> Noticed this today:
>
> ghci> let xs = [0.0,0.1 .. 86400.0] in maximum xs
> 86400.005062
>
> enumFromThenTo is implemented by numericEnumFromThenTo:
>
> https://github.com/ghc/ghc/blob/a90085bd45239fffd65c01c24752a9
> bbcef346f1/libraries/base/GHC/Real.hs#L227
>
> Which probably accumulates error in numericEnumFromThen with the (m+m-n):
>
> numericEnumFromThen n m = n `seq` m `seq` (n : numericEnumFromThen m
> (m+m-n))
>
> Why not define numericEnumFromThen as:
>
> numericEnumFromThen n m = let d = m - n in d `seq` go d n
> where go delta x = x `seq` (x : go delta (x + delta))
>
> (or with BangPatterns)
>
> numericEnumFromThen n m = go (m - n) n
> where go !delta !x = x : go delta (x + delta)
>
> Seems like we'd save a lot of subtractions by using the worker function.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Edward Kmett
I see three major stories here:

1.) If you remove IO from being able to be compiled inside Safe code _at
all_ most packages I have that bother to expose Safe information will have
to stop bothering. I'd have to cut up too many APIs into too many
fine-grained pieces. This would considerably reduce the utility of Safe
Haskell to me. Many of them expose a few combinators here and there that
happen to live in IO and I can view offering Safe or Trustworthy to users
as a 'the pure stuff looks really pure' guarantee. For the most part it
'just works' and Trustworthy annotations can be put in when I know the
semantics of the hacks I'm using under the hood.

2.) Assuming instead that you're talking about a stronger-than-Safe
additional language extension, say ReallySafe or SafeIO, it all comes down
to what the user is allowed to do in IO, doesn't it? What effects are users
granted access to? We don't have a very fine-grained system for IO-effect
management, and it seems pretty much any choice you pick for what to put in
the sandbox will be wrong for some users, so you'd need some sort of pragma
for each IO operation saying what bins it falls into and to track that
while type checking, etc. At least then you could say what you are safe
with respect to. That all seems to be rather a big mess, roughly equivalent
to modeling an effect system for IO operations, and then retroactively
categorizing everything, putting a big burden on maintainers and requiring
a lot of community buy-in, sight unseen.

3.) On the other hand, someone could _build_ an effect system in Haskell
that happens to sit on top of IO, holding effects in an HList, undischarged
nullary class constraint, etc. then pull a couple of Trustworthy modules
around it for embedding the effects they want to permit and build this
today without any compiler support, they'd just have to make a final
application-specific Trustworthy wrapper to run whatever effects they want
to permit into their program. It is more invasive to the code in question,
but it requires zero community organizing and we've already got all the
compiler mojo we need. The downside is the Trustworthy wrappers at the
bottom of the heap and that it doesn't interoperate with basically anything
already written.

-Edward

On Tue, Aug 9, 2016 at 10:45 PM, Ryan Newton <rrnew...@gmail.com> wrote:

> I'm hearing that Safe Haskell is great for pure use cases (lambda bot).
> But that doesn't depend on being able to write arbitrary IO code inside the
> Safe bubble, does it?  In fact *all* of IO could be outside the safe
> boundary for this use case, could it not?  Are there any existing cases
> where it is important to be able to build up unsafe IO values inside -XSafe
> code?
>
> Edward, why does it seem like a losing proposition?  Are there further
> problems that come to mind?  ezyang mentioned the subprocess problem.  I
> don't have a strong opinion on that one.  But I tend to think the safe IO
> language *should* allow subprocess calls, and its a matter of configuring
> your OS to not allow ptrace in that situation.  This would be part of a set
> of requirements for how to compile and launch a complete "Safe Haskell"
> *program* in order to get a guarantee.
>
> My primary interest is actually not segfault-freedom, per-se, but being
> able to define a memory model for Safe Haskell (for which I'd suggest
> sequential consistency).  FFI undermines that, and peek/poke seems like it
> should cluster with FFI as an unsafe feature.  I'm not inclined to give a
> memory model to peek or FFI -- at that level you get what the architecture
> gives you -- but I do want a memory model for IORefs, IOVectors, etc.
>
> We're poking at the Stackage package set now to figure out what pressure
> point to push on to increase the percentage of Stackage that is Safe.  I'll
> be able to say more when we have more data on dependencies and problem
> points.  Across all of hackage, Safe Haskell has modest use: of the ~100K
> modules on Hackage, ~636 are marked Safe, ~874 trustworthy, and ~118
> Unsafe.  It should be easy to check if any of this Safe code is currently
> importing "Foreign.*" or using FFI.
>
> My general plea is that we not give the imperative partition of Haskell
> too much the short end of the stick [1]. There is oodles of code in IO (or
> MonadIO), and probably relatively little in "RIO".  To my knowledge, we
> don't have great ways to coin "RIO" newtypes without having to wrap and
> reexport rather a lot of IO functions.  Maybe if APIs like MVars or files
> were overloaded in a class then GND could do some of the work...
>
>   -Ryan
>
> [1] In safety guarantees, in optimizations, primops, whatever...  For
> instance, I find in microbenchmarks that IO code still runs 2X slower than
> pure code, even if no IO effects are performed.
>
>

Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Edward Kmett
I've always treated Safe Haskell as "Safe until you allow IO" -- in that
all 'evil' things get tainted by an IO type that you can't get rid of by
the usual means. So if you go to run pure Safe Haskell code in say,
lambdabot, which doesn't give the user a means to execute IO, it can't
segfault if all of the Trustworthy modules you depend upon actually are
trustworthy.

Trying to shore up segfault safety under Safe in IO seems like a losing
proposition.

-Edward

On Mon, Aug 8, 2016 at 1:27 PM, Ryan Newton  wrote:

> We're trying to spend some cycles pushing on Safe Haskell within the
> stackage packages.  (It's looking like a slog.)
>
> But we're running up against some basic questions regarding the core
> packages and Safe Haskell guarantees.  The manual currently says:
> 
>
>
> *Functions in the IO monad are still allowed and behave as usual. *
> As usual?  So it is ok to segfault GHC?  Elsewhere it says "in the safe
> language you can trust the types", and I'd always assumed that meant Safe
> Haskell is a type safe language, even in the IO fragment.
>
> Was there an explicit decision to allow segfaults and memory corruption?
> This can happen not just with FFI calls but with uses of Ptrs within
> Haskell, for example the following:
>
>
> ```
>
> {-# LANGUAGE Safe #-}
>
> module Main where
>
> import Foreign.Marshal.Alloc
>
> import Foreign.Storable
>
> import Foreign.Ptr
>
> import System.Random
>
>
> fn :: Ptr Int -> IO ()
>
> fn p = do
>
>   -- This is kosher:
>
>   poke p 3
>
>   print =<< peek p
>
>   -- This should crash the system:
>
>   ix <- randomIO
>
>   pokeElemOff p ix 0xcc
>
>
>
> main = alloca fn
>
> ```
>
>
>   -Ryan
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Deriving tweaking

2016-08-05 Thread Edward Kmett
Done and done! Retroactively. How is that for service? =)

-Edward

On Fri, Aug 5, 2016 at 2:08 PM, David Feuer  wrote:

> I know there's been some discussion about letting users select the
> deriving mechanism they want, but I'd like to propose a separate tweak to
> the defaults. Specifically, it's annoying to have to use three pragmas to
> let me write
>
> newtype Foo f a = Foo (f a) deriving (Functor, Foldable, Traversable)
> data Bar f a = Bar (f a) deriving (Functor, Foldable, Traversable)
>
> and more annoying still that I'll end up with Foldable and Functor
> instances for Foo that may be much worse than GND-derived ones.
>
> The tweaks I'm after:
>
> 1. Prefer GND to the built-in derivations for Functor and Foldable, and
> probably also Eq and Ord.
> 2. Make DeriveTraversable imply DeriveFunctor and DeriveFoldable.
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Can we offer ~ without GADTs or type families?

2016-08-05 Thread Edward Kmett
TypeOperators as a language extension doesn't require a whole lot on the
behalf of implementors today. They basically just have to add fixity
handling to types. This is a no-brainer for a compiler implementor. It is a
simple elaboration and some extra cases to deal with in their parser. The
typechecker changes are obvious.

Asking them to do all the things to support 'some typechecking details'
that aren't entirely trivial to support that same extension is an awful big
ask! OutsideIn(X) is a big paper to read, let alone implement, and the only
compiler to even try handling (~) today is GHC.

-Edward

On Fri, Aug 5, 2016 at 2:15 PM, Ryan Scott  wrote:

> Hi David,
>
> > Could we get a separate LANGUAGE pragma just for equality constraints?
>
> I think we should, and I don't think we'd even need to introduce a new
> pragma, since there's already a perfectly good one: -XTypeOperators!
> After all, there's nothing really that special about (~) other than
> some typechecking details. A fix to Trac #9194 [1] would give us this.
>
> Ryan S.
> -
> [1] https://ghc.haskell.org/trac/ghc/ticket/9194
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Request for feedback: deriving strategies syntax

2016-08-03 Thread Edward Kmett
It has the benefit that nothing lowercase would ever derive in that
position so it is a strict extension of the current syntax. So even it
builtin or whatever is a conditional keyword like qualified and as, I don't
see any issues with it.

'bespoke' does make me smile, though. =)

-Edward

On Sun, Jul 17, 2016 at 10:24 PM, Richard Eisenberg 
wrote:

> Of the three options from Ryan's first email in this thread, only the
> third is palatable to me (with the separate `deriving` clauses).
>
> I would like to mention that I don't see any real obstacles to something
> like
>
> > newtype ...
> >  deriving (Eq, default ToJSON, builtin Ord, newtype Monoid)
>
> That is, one `deriving` clause where each element is optionally prefixed
> with a keyword. On the ticket (#10598), it is suggested that parsing these
> would be hard. I agree that parsing these would be annoying, but I do not
> think that they are actually ambiguous. Avoiding a few hours of pain in the
> parser should not be our motivation for choosing a syntax we will all live
> with for years. For `default` and `newtype`, parsing is actually easy. If
> we want to keep the `builtin` pseudo-keyword, we could always parse as a
> type and then have some non-parser code examine the resulting AST and sort
> it out. (This is done in several other dark corners of the parser already.)
>
> Separately, I'm not enamored of the `builtin` keyword. The one idea I can
> suggest in this space (somewhat tongue-in-cheek, but feel free to take it
> seriously) is `bespoke` -- after all, each "builtin" instance must be
> generated by code written specifically for that class, which fits the
> English definition of bespoke nicely. "Which deriving mechanism do want?"
> "The bespoke one, please." And then GHC can boast that it has the classiest
> keyword of any programming language. :)
>
> Richard
>
> On Jul 16, 2016, at 10:02 PM, Ryan Scott  wrote:
>
> > I'm pursuing a fix to Trac #10598 [1], an issue in which GHC users do
> > not have fine-grained control over which strategy to use when deriving
> > an instance, especially when multiple extensions like
> > -XGeneralizedNewtypeDeriving and -XDeriveAnyClass are enabled
> > simultaneously. I have a working patch up at [2] which would fix the
> > issue, but there's still a lingering question of what the right syntax
> > is to use here. I want to make sure I get this right, so I'm
> > requesting input from the community.
> >
> > To condense the conversation in [1], there are three means by which
> > you can derive an instance in GHC today:
> >
> > 1. -XGeneralizedNewtypeDeriving
> > 2. -XDeriveAnyClass
> > 3. GHC's builtin algorithms (which are used for deriving Eq, Show,
> > Functor, Generic, Data, etc.)
> >
> > The problem is that it's sometimes hard to know which of the three
> > will kick in when you say `deriving C`. To resolve this ambiguity, I
> > want to introduce the -XDerivingStrategies extension, where a user can
> > explicitly request which of the above ways to derive an instance.
> >
> > Here are some of the previously proposed syntaxes for this feature,
> > with their perceived pros and cons:
> >
> > - Pragmas
> >  * Examples:
> >  - newtype T a = T a deriving ({-# BUILTIN #-} Eq, {-# GND #-}
> > Ord, {-# DAC #-} Read, Show)
> >  - deriving {-# BUILTIN #-} instance Functor T
> >  * Pros:
> >  - Backwards compatible
> >  - Requires no changes to Template Haskell
> >  * Cons:
> >  - Unlike other pragmas, these ones can affect the semantics of a
> program
> > - Type synonyms
> >  * Examples:
> >  - newtype T a = T a deriving (Builtin Eq, GND Ord, DAC Read, Show)
> >  - deriving instance Builtin (Functor T)
> >  * Pros:
> >  - Requires no Template Haskell or parser changes, just some
> > magic in the typechecker
> >  - Backwards compatible (back to GHC 7.6)
> >  * Cons:
> >  - Some developers objected to the idea of imbuing type synonyms
> > with magical properties
> > - Multiple deriving clauses, plus new keywords
> >  * Examples:
> >  - newtype T a = T a
> >  deriving Show
> >  deriving builtin instance (Eq, Foldable)
> >  deriving newtype instance Ord
> >  deriving anyclass instance Read
> >  - deriving builtin instance Functor T
> >  * Pros:
> >  - Doesn't suffer from the same semantic issues as the other
> suggestions
> >  - (Arguably) the most straightforward-looking syntax
> >  * Cons:
> >  - Requires breaking changes to Template Haskell
> >  - Changes the parser and syntax significantly
> >
> > Several GHC devs objected to the first two of the above suggestions in
> > [1], so I chose to implement the "Multiple deriving clauses, plus new
> > keywords" option in [2]. However, I'd appreciate further discussion on
> > the above options, which one you prefer, and if you have other
> > suggestions for syntax to use.
> >
> > Ryan S.
> > -
> > [1] 

Re: Re-exporting traverse_ from Data.Traversable

2016-07-25 Thread Edward Kmett
Yes there is.

For existing code if anybody has already explicitly hidden it from
Data.Foldable, so they can work with traverse_ from some specific container
type, they'd now get slapped with it on the backswing by Data.Traversable.

import Data.Foldable hiding (traverse_)
import SomeContainer
import Data.Traversable

main = something that used a monomorphic traverse_ from SomeContainer

This is sort of like how users get hammered with Control.Monad methods from
all of the Control.Monad.Foo modules today, where it can be remarkably hard
to hide all the attempts they make to shove the same fail, join, etc. down
your throat.

-Edward

On Mon, Jul 25, 2016 at 9:15 PM, Christopher Allen 
wrote:

> Any reason not to do it? I realize it needs Foldable, but even knowing
> that I still forget it's in Data.Foldable. Seems like a free UX win to
> me.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: How bad would it be for containers to depend on transformers?

2016-06-22 Thread Edward Kmett
If we're just talking about building one or two transformers then I'd say we 
should avoid incurring the dependency. The outcry would far far outweigh the 
code sharing advantage for one or two types. E.g. base duplicates State 
internally for mapAccumL for instance for this sort of reason.

Sent from my iPad

> On Jun 22, 2016, at 12:58 PM, David Feuer  wrote:
> 
> Currently, containers does not depend on transformers, so it has to duplicate 
> its functionality or just do without. Since transformers is also a GHC boot 
> package, I believe it should be feasible to make containers depend on it. To 
> what extent would that reduce 
> parallelizability of GHC builds or otherwise make people mad?
> 
> David
> ___
> Libraries mailing list
> librar...@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Moving ArgumentsDo forward

2016-06-01 Thread Edward Kmett
Just as a note: I noticed this was being discussed a couple of weeks ago as
a possible topic for haskell-prime, when they were discussing what was in
scope for the committee, so I'm not entirely sure its a dead topic.

-Edward

On Wed, Jun 1, 2016 at 11:09 AM, Bardur Arantsson 
wrote:

> On 06/01/2016 01:48 PM, Akio Takano wrote:
> > Hi,
> >
> > Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would
> > love to see in GHC. It's a small syntactic extension that allows do,
> > case, if and lambda blocks as function arguments, without parentheses.
> > However, its differential revision [1] has been abandoned, citing a
> > mixed response from the community. A message [2] on the ticket
> > summarizes a thread in haskell-cafe on this topic.
> >
> > I, for one, think adding this extension is worthwhile, because a
> > significant number of people support it. Also, given how some people
> > seem to feel ambivalent about this change, I believe actually allowing
> > people to try it makes it clearer whether it is a good idea.
> >
> > Thus I'm wondering: is there any chance that this gets merged? If so,
> > I'm willing to work on whatever is remaining to get the change merged.
> >
>
> What's changed since it was last discussed? I don't think the objections
> were centered in the implementation, so I don't see what "whatever is
> remaining to get the change merged" would be.
>
> AFAICT at best it's a *very* small improvement[1] and fractures Haskell
> syntax even more around extensions -- tooling etc. will need to
> understand even *more* syntax extensions[2].
>
> Regards,
>
> [1] If you grant that it is indeed an improvment, which I, personally,
> don't think it is.
>
> [2] I think most people agree that this is something that should perhaps
> be handled by something like
> https://github.com/haskell/haskell-ide-engine so that it would only need
> to be implemented once, but there's not even an alpha release yet, so
> that particular objection stands, AFAICT.
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Strictness/laziness warnings

2016-05-28 Thread Edward Kmett
How would you detect the argument only being forced some of the time?
Sounds like a lot of long-term cross-module book-keeping.

-Edward

On Sat, May 28, 2016 at 10:02 PM, David Feuer <david.fe...@gmail.com> wrote:

> I'm not suggesting these things are *wrong*, and I wouldn't want the
> warnings to be included in -Wall. They're just possible areas of concern.
> By "conditionally strict" I mean that the argument in question is only
> forced sometimes.
> On May 28, 2016 9:16 PM, "Edward Kmett" <ekm...@gmail.com> wrote:
>
>> I have code that'd trip at least 2&3 in use in production. #2 arises for
>> some tricks that Wren first introduced me to for loop invariant code
>> motion. #3 arises when you want to memoize a result but only produce it
>> lazily in case it isn't used. I don't quite understand what you mean by
>> "conditionally strict" in an argument though.
>>
>> -Edward
>>
>> On Sat, May 28, 2016 at 8:00 PM, David Feuer <david.fe...@gmail.com>
>> wrote:
>>
>>> There are certain patterns of strictness or laziness that signal the
>>> need for extra caution. I'm wondering whether it might be possible to offer
>>> warnings for different varieties of them, and pragmas suppressing the
>>> warnings at the relevant sites. Some function behaviors that suggest extra
>>> care:
>>>
>>> 1. Conditionally strict in an argument. In many cases, making it
>>> unconditionally strict will improve performance.
>>> 2. Strict in an argument that is or could be a function or a newtype
>>> wrapper around a function. This can be caused by  adding too much
>>> strictness defensively or to plug a leak.
>>> 3. Lazy in a primitive argument like an Int. This could lead to
>>> unnecessary boxing.
>>>
>>> Any of these could occur in correct, efficient code. But I'd love to be
>>> presented a list of warnings to check over, and a way to check items off
>>> the list with pragmas.
>>>
>>> ___
>>> ghc-devs mailing list
>>> ghc-devs@haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>
>>>
>>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Strictness/laziness warnings

2016-05-28 Thread Edward Kmett
I have code that'd trip at least 2&3 in use in production. #2 arises for
some tricks that Wren first introduced me to for loop invariant code
motion. #3 arises when you want to memoize a result but only produce it
lazily in case it isn't used. I don't quite understand what you mean by
"conditionally strict" in an argument though.

-Edward

On Sat, May 28, 2016 at 8:00 PM, David Feuer  wrote:

> There are certain patterns of strictness or laziness that signal the need
> for extra caution. I'm wondering whether it might be possible to offer
> warnings for different varieties of them, and pragmas suppressing the
> warnings at the relevant sites. Some function behaviors that suggest extra
> care:
>
> 1. Conditionally strict in an argument. In many cases, making it
> unconditionally strict will improve performance.
> 2. Strict in an argument that is or could be a function or a newtype
> wrapper around a function. This can be caused by  adding too much
> strictness defensively or to plug a leak.
> 3. Lazy in a primitive argument like an Int. This could lead to
> unnecessary boxing.
>
> Any of these could occur in correct, efficient code. But I'd love to be
> presented a list of warnings to check over, and a way to check items off
> the list with pragmas.
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Mentor for a JVM backend for GHC

2016-05-07 Thread Edward Kmett
By the time it has made it down to Cmm there are a lot of assumptions
about layout in memory -- everything is assumed to be a flat object
made out of 32-bit or 64-bit slots. These assumptions aren't really
suitable for the JVM.

-Edward

On Sat, May 7, 2016 at 11:32 AM, Thomas Jakway  wrote:
> This is a strange coincidence.  I'm definitely no expert GHC hacker but I
> started (highly preliminary) work on a JVM backend for GHC a few weeks ago.
> It's here: https://github.com/tjakway/ghcjvm/tree/jvm/compiler/jvmGen/Jvm
> (The memory runtime is here: https://github.com/tjakway/lljvm)
>
> I'm very new to this so pardon my ignorance, but I don't understand what the
> benefit is of intercepting STG code and translating that to bytecode vs.
> translating Cmm to bytecode (or Jasmin assembly, as I'd prefer)?  It seems
> like Cmm is designed for backends and the obvious choice.  Or have I got
> this really mixed up?
>
> I hope this isn't out of line considering my overall lack of experience but
> I think I can give some advice:
>
> read the JVM 7 spec cover-to-cover.
> I highly suggest outputting Jasmin assembly instead of raw bytecode.  The
> classfile format is complicated and you will have to essentially rewrite
> Jasmin in Haskell if you don't want to reuse it.  Jasmin is also the de
> facto standard assembler and much more thoroughly tested than any homegrown
> solution we might make.
> read the LLVM code generator.  This project is more like the LLVM backend
> than the native code generator.
> Don't go for speed.  The approach that I've begun is to emulate a C stack
> and memory system the RTS can run on top of
> (https://github.com/tjakway/lljvm/blob/master/src/main/java/lljvm/runtime/Memory.java).
> This will make getting something working much faster and also solves the
> problem of how to deal with memcpy/memset/memmove on the JVM.  This will of
> course be very slow (I think) and is not a permanent solution.  Can't do
> everything at once.  Any other approach will probably require rewriting the
> entire RTS from the beginning.
> I don't think Frege is especially useful to this project, though I'd love to
> be proven wrong.  Frege's compilation model is completely different from
> GHC's: they compile Haskell to Java and then send that to javac.  Porting
> GHC to the JVM is really more like writing a Cmm to JVM compiler.
>
>
> I've heard of the LambdaVM project but couldn't find the actual code
> anywhere.  The site where it was hosted appears to be offline.  I'd
> certainly like to look at it if anyone knows where to find it.
>
> Information on Jasmin:
> http://web.mit.edu/javadev/packages/jasmin/doc/
> http://web.mit.edu/javadev/packages/jasmin/doc/instructions.html
> http://web.mit.edu/javadev/packages/jasmin/doc/about.html
>
> Once you've tried manually dealing with constant pools you'll appreciate
> Jonathan Meyer's work!
>
> I forked davidar's extended version of Jasmin.  The differences versus the
> original Jasmin are detailed here.  Some nice additions:
>
> supports invokedynamic
> supports .annotation, .inner, .attribute, .deprecated directives
> better handling of the ldc_w instruction
> multi-line fields
> .debug directives
> signatures for local variables
> .bytecode directive to specify bytecode version
> (most importantly, I think): support for the StackMap attribute.  If we
> eventually want to use new JVM instructions like invokedynamic, we need
> stack map frames or the JVM will reject our bytecode.  JVM 7 has options to
> bypass this (but it's a hack), but they're deprecated and I believe not
> optional going forward.  Alternatively we can stick with older bytecode
> versions indefinitely and not use the new features.
>
> (Just to be clear, I forked it in case it was deleted.  I didn't write those
> features, the credit belongs to him).
>
> I think the biggest risk is taking too much on at once.  Any one of these
> subtasks, writing a bytecode assembler, porting the RTS, etc. could consume
> the whole summer if you're not careful.
>
> I'd love to help out with this project!
>
> Sincerely,
> Thomas Jakway
>
> ---
>
> Woops, after scrolling back through the emails it looks like someone sent
> out the LambdaVM source.  I'll have to take a look at that.
>
>
>
> On 05/02/2016 11:26 AM, Rahul Muttineni wrote:
>
> Hi GHC Developers,
>
> I've started working on a JVM backend for GHC [1] and I'd love to work on it
> as my Summer of Haskell project.
>
> Currently, the build system is setup using a mix of Shake (for the RTS
> build) and Stack (for the main compiler build) and I ensure that most
> commits build successfully. I have ported the core part of the scheduler and
> ported over the fundamental types (Capability, StgTSO, Task, StgClosure,
> etc.) taking advantage of OOP in the implementation when I could.
>
> Additionally, I performed a non-trivial refactor of the hs-java package
> adding support for inner classes and fields which was very cumbersome to do
> in the 

Re: Constrained Type Families?

2016-03-09 Thread Edward Kmett
Good point!

On Wed, Mar 9, 2016 at 11:48 AM, Ryan Ingram  wrote:

> I think it's more like the non-keyworded default definitions of class
> methods, for the same reasons; the default definition has to potentially be
> valid for all instances of the class​.
>
> It's the difference between
>
> class Applicative m => Monad m where
> return :: a -> m a
> return = pure  -- always valid, but can be overridden in instance
> declarations
>
> and
>
> class Fuctor f => Applicative f where
> (<*>) :: f (a -> b) -> f a -> f b
> default (<*>) :: Monad f => f (a -> b) -> f a -> f b
> (<*>) = ap -- only valid if matches the type signature above
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Constrained Type Families?

2016-03-09 Thread Edward Kmett
I'd pretty much just assumed that a class associated type with a default
definition was modeling the same thing as a default signature, just without
the 'default' keyword

-Edward

On Wed, Mar 9, 2016 at 7:39 AM, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> Notably if a class associated type has a more general kind, we currently
> can't give a default definition for it that has a tighter kind.
>
>
>
> This is the same situation as holds for default class methods.
>
>
>
> BUT for the latter we invented default method signatures
> –XdefaultSignatures (user manual Section 9.8.1.4
> <http://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html#class-declarations>),
> which can be more restrictive than the signature implied by the method
> signature of the class.
>
>
>
> Maybe we can do the same for default declarations for associated types?
>
>
>
> Would someone like to open a ticket and tell the story?
>
>
>
> Simon
>
>
>
> *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Richard
> Eisenberg
> *Sent:* 09 March 2016 01:32
> *To:* Edward Kmett <ekm...@gmail.com>
> *Cc:* ghc-devs <ghc-devs@haskell.org>
> *Subject:* Re: Constrained Type Families?
>
>
>
> I see no good reason for this restriction -- I think that we should just
> remove the restriction instead of cooking up a workaround. Have you brought
> this up before? Perhaps make a ticket.
>
>
>
> Richard
>
>
>
> On Mar 8, 2016, at 8:24 PM, Edward Kmett <ekm...@gmail.com> wrote:
>
>
>
> If and when that feature lands would it be possible to use it to bypass a
> current limitation in class associated types?
>
>
>
> Notably if a class associated type has a more general kind, we currently
> can't give a default definition for it that has a tighter kind.
>
>
>
> e.g. I have some classes which are technically polykinded but where 90% of
> the instances instantiate that kind as *. The status quo prevents me from
> putting in a type default that would only be valid when the kind argument
> is *.
>
>
>
> -Edward
>
>
>
> On Tue, Mar 8, 2016 at 8:21 PM, Richard Eisenberg <e...@cis.upenn.edu>
> wrote:
>
>
>
> On Mar 8, 2016, at 7:17 PM, Evan Austin <e.c.aus...@gmail.com> wrote:
>
> The wiki page for Phase I of Dependent Haskell describes an approach to
> constrained type families:
>
>
> https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Phase1#Typefamilyequationscanbeconstrained
>
>
>
> Did that land in GHC 8.0 and, if so, is the updated syntax documented
> somewhere?
>
>
>
> No, it didn't make it. The motivating test case seemed contrived and so we
> punted on this one.
>
>
>
> Do you have a use case that really needs this feature? That would help to
> motivate it for 8.2 or beyond.
>
>
>
> Thanks!
>
> Richard
>
>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> <https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c548849e42ffa4b50f01208d347ba9228%7c72f988bf86f141af91ab2d7cd011db47%7c1=QKme1PQXRrwAkxAODUaPscdFk7ovwwwxHAFhDxpBXb8%3d>
>
>
>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Constrained Type Families?

2016-03-08 Thread Edward Kmett
It has only been a low level irritant. Until Evan mentioned the link above,
I'd mostly just pushed it aside and learned to live with it.

This is probably the first time I've mentioned it outside of IRC.

-Edward

On Tue, Mar 8, 2016 at 8:31 PM, Richard Eisenberg <e...@cis.upenn.edu> wrote:

> I see no good reason for this restriction -- I think that we should just
> remove the restriction instead of cooking up a workaround. Have you brought
> this up before? Perhaps make a ticket.
>
> Richard
>
> On Mar 8, 2016, at 8:24 PM, Edward Kmett <ekm...@gmail.com> wrote:
>
> If and when that feature lands would it be possible to use it to bypass a
> current limitation in class associated types?
>
> Notably if a class associated type has a more general kind, we currently
> can't give a default definition for it that has a tighter kind.
>
> e.g. I have some classes which are technically polykinded but where 90% of
> the instances instantiate that kind as *. The status quo prevents me from
> putting in a type default that would only be valid when the kind argument
> is *.
>
> -Edward
>
> On Tue, Mar 8, 2016 at 8:21 PM, Richard Eisenberg <e...@cis.upenn.edu>
> wrote:
>
>>
>> On Mar 8, 2016, at 7:17 PM, Evan Austin <e.c.aus...@gmail.com> wrote:
>>
>> The wiki page for Phase I of Dependent Haskell describes an approach to
>> constrained type families:
>>
>> https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Phase1#Typefamilyequationscanbeconstrained
>>
>> Did that land in GHC 8.0 and, if so, is the updated syntax documented
>> somewhere?
>>
>>
>> No, it didn't make it. The motivating test case seemed contrived and so
>> we punted on this one.
>>
>> Do you have a use case that really needs this feature? That would help to
>> motivate it for 8.2 or beyond.
>>
>> Thanks!
>> Richard
>>
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Constrained Type Families?

2016-03-08 Thread Edward Kmett
An example would be something like:

class Foo (p :: k -> Type) where
  type Bar p :: k -> k
  type (k ~ Type) => Bar p = p

-Edward

On Tue, Mar 8, 2016 at 8:24 PM, Edward Kmett <ekm...@gmail.com> wrote:

> If and when that feature lands would it be possible to use it to bypass a
> current limitation in class associated types?
>
> Notably if a class associated type has a more general kind, we currently
> can't give a default definition for it that has a tighter kind.
>
> e.g. I have some classes which are technically polykinded but where 90% of
> the instances instantiate that kind as *. The status quo prevents me from
> putting in a type default that would only be valid when the kind argument
> is *.
>
> -Edward
>
> On Tue, Mar 8, 2016 at 8:21 PM, Richard Eisenberg <e...@cis.upenn.edu>
> wrote:
>
>>
>> On Mar 8, 2016, at 7:17 PM, Evan Austin <e.c.aus...@gmail.com> wrote:
>>
>> The wiki page for Phase I of Dependent Haskell describes an approach to
>> constrained type families:
>>
>> https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Phase1#Typefamilyequationscanbeconstrained
>>
>> Did that land in GHC 8.0 and, if so, is the updated syntax documented
>> somewhere?
>>
>>
>> No, it didn't make it. The motivating test case seemed contrived and so
>> we punted on this one.
>>
>> Do you have a use case that really needs this feature? That would help to
>> motivate it for 8.2 or beyond.
>>
>> Thanks!
>> Richard
>>
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Constrained Type Families?

2016-03-08 Thread Edward Kmett
If and when that feature lands would it be possible to use it to bypass a
current limitation in class associated types?

Notably if a class associated type has a more general kind, we currently
can't give a default definition for it that has a tighter kind.

e.g. I have some classes which are technically polykinded but where 90% of
the instances instantiate that kind as *. The status quo prevents me from
putting in a type default that would only be valid when the kind argument
is *.

-Edward

On Tue, Mar 8, 2016 at 8:21 PM, Richard Eisenberg  wrote:

>
> On Mar 8, 2016, at 7:17 PM, Evan Austin  wrote:
>
> The wiki page for Phase I of Dependent Haskell describes an approach to
> constrained type families:
>
> https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Phase1#Typefamilyequationscanbeconstrained
>
> Did that land in GHC 8.0 and, if so, is the updated syntax documented
> somewhere?
>
>
> No, it didn't make it. The motivating test case seemed contrived and so we
> punted on this one.
>
> Do you have a use case that really needs this feature? That would help to
> motivate it for 8.2 or beyond.
>
> Thanks!
> Richard
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: GADTs and functional dependencies?

2016-03-01 Thread Edward Kmett
https://ghc.haskell.org/trac/ghc/ticket/11534 is somewhat relevant to this
issue. Solving it would seem likely to fix this one as well.

-Edward

On Tue, Mar 1, 2016 at 1:47 PM, Iavor Diatchki 
wrote:

> Hello Conal,
>
> the implementation of fun-deps in GHC is quite limited, and they don't do
> what you'd expect with existential types (like in your example),
> type-signatures, or GADTs.   Basically, GHC only uses fun-deps to fill-in
> types for unification variables, but it won't use them to reason about
> quantified variables.
>
> Here is an example that shows the problem, just using type signatures:
>
> > class F a b | a -> b where
> >   f :: a -> b -> ()
> >
> > instance F Bool Char where
> >  f _ _ = ()
> >
> > test :: F Bool a => a -> Char
> > test a = a
>
> GHC rejects the declaration for `test` because there it needs to prove
> that `a ~ Char`.  Using the theory of fun-deps, the equality follows
> because from the fun-dep we know that:
>
> forall x y z. (F x y, F x z) => (y ~ z)
>
> Now, if we instantiate this axiom with `Bool`, `Char`, and `a`, we can
> prove that `Char ~ a` by combining the instance and the local assumption
> from the signature.
>
> Unfortunately, this is exactly the kind of reasoning GHC does not do.   I
> am not 100% sure on why not, but at present GHC will basically do all the
> work to ensure that the fun-dep axiom for each class is valid (that's all
> the checking that instances are consistent with their fun-deps), but then
> it won't use that invariant when solving equalities.
>
> I hope this helps!
> -Iavor
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
> On Tue, Mar 1, 2016 at 9:38 AM, Conal Elliott  wrote:
>
>> Do GADTs and functional dependencies get along? I'm wondering why the
>> following code doesn't type-check under GHC 7.10.3 and 8.1.20160224:
>>
>> > {-# OPTIONS_GHC -Wall #-}
>> > {-# LANGUAGE GADTs, KindSignatures, MultiParamTypeClasses,
>> FunctionalDependencies #-}
>> >
>> > module FundepGadt where
>> >
>> > class C a b | a -> b
>> >
>> > data G :: * -> * where
>> >   -- ...
>> >   GC :: C a b => G b -> G a
>> >
>> > instance Eq (G a) where
>> >   -- ...
>> >   GC b  == GC b' = b == b'
>>
>> Error message:
>>
>> FundepGadt.hs:14:25: error:
>> • Couldn't match type 'b1’ with 'b’
>>   'b1’ is a rigid type variable bound by
>> a pattern with constructor: GC :: forall a b. C a b => G b ->
>> G a,
>> in an equation for '==’
>> at FundepGadt.hs:14:12
>>   'b’ is a rigid type variable bound by
>> a pattern with constructor: GC :: forall a b. C a b => G b ->
>> G a,
>> in an equation for '==’
>> at FundepGadt.hs:14:3
>>   Expected type: G b
>> Actual type: G b1
>> • In the second argument of '(==)’, namely 'b'’
>>   In the expression: b == b'
>>   In an equation for '==’: (GC b) == (GC b') = b == b'
>> • Relevant bindings include
>> b' :: G b1 (bound at FundepGadt.hs:14:15)
>> b :: G b (bound at FundepGadt.hs:14:6)
>>
>> I think the functional dependency does ensure that "b == b" is
>> well-typed.
>>
>> In contrast, the following type-family version does type-check:
>>
>> > {-# OPTIONS_GHC -Wall #-}
>> > {-# LANGUAGE GADTs, KindSignatures, TypeFamilies #-}
>> >
>> > module TyfamGadt where
>> >
>> > class C a where
>> >   type B a
>> >
>> > data G :: * -> * where
>> >   -- ...
>> >   GC :: C a => G (B a) -> G a
>> >
>> > instance Eq (G a) where
>> >   -- ...
>> >   GC b  == GC b' = b == b'
>>
>> Thanks, - Conal
>>
>> ___
>> ghc-tickets mailing list
>> ghc-tick...@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-tickets
>>
>>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Potentially confusing syntax for injective type families

2016-02-14 Thread Edward Kmett
When this was first discussed a bunch of alternatives were tossed around,
mostly involving new keywords, or putting a conditional result keyword in
place. Here you can pick the name of the result type, so it doesn't pick
any naming conventions for you.

My understanding is that the current syntax was selected because it avoids
magic conditional keywords and fits into a gap in the current grammar.

All of the alternatives seemed worse.

-Edward

On Sun, Feb 14, 2016 at 5:56 AM, Matthew Pickering <
matthewtpicker...@gmail.com> wrote:

> I guess my point is that the most natural parsing of
>
> class Hcl a b where
>  type Ht a b = r | r -> a b
>
> is  (type Ht a b = r) (| r -> a b) rather than (type Ht a b) (= r | r -> a
> b).
>
> A concrete example, in the case of functional dependencies, the
> vertical bar is used to signal what we expect *additional* optional
> information. In this case, adding the injectivity annotation
> completely changes the meaning of what came before.
>
> I don't have a solution and I hate bike-shedding. I just made this
> message to make sure the fact had been considered before release.
>
> Matt
>
>
>
> On Sun, Feb 14, 2016 at 9:28 AM, Jan Stolarek 
> wrote:
> >> 2. Without the infectivity annotation, this declares an associate type
> >> synonym default. This isn't valid because Ht is not declared as an
> >> associated type before hand and r is not mentioned on the LHS.
> >>
> >> class Hcl a b where
> >> type Ht a b = r
> > Indeed, this is invalid and GHC rejects this, so I think we're OK here.
> In case of associated
> > types if you want to declare injectivity you need to provide the "| r ->
> " part. Otherwise
> > you're declaring a default. This is documented in the User's Guide for
> 8.0.
> >
> > Janek
> >
> > ---
> > Politechnika Łódzka
> > Lodz University of Technology
> >
> > Treść tej wiadomości zawiera informacje przeznaczone tylko dla adresata.
> > Jeżeli nie jesteście Państwo jej adresatem, bądź otrzymaliście ją przez
> pomyłkę
> > prosimy o powiadomienie o tym nadawcy oraz trwałe jej usunięcie.
> >
> > This email contains information intended solely for the use of the
> individual to whom it is addressed.
> > If you are not the intended recipient or if you have received this
> message in error,
> > please notify the sender and delete it from your system.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] New type of ($) operator in GHC 8.0 is problematic

2016-02-06 Thread Edward Kmett
On Fri, Feb 5, 2016 at 6:21 PM, Mike Izbicki  wrote:

> > We're in a bit of a bind in all this. We really need the fancy type for
> ($)
> > so that it can be used in all situations where it is used currently. The
> old
> > type for ($) was just a plain old lie. Now, at least, we're not lying.
> So,
> > do we 1) lie, 2) allow the language to grow, or 3) avoid certain growth
> > because it affects how easy the language is to learn? I don't really
> think
> > anyone is advocating for (3) exactly, but it's hard to have (2) and not
> make
> > things more complicated -- unless we have a beginners' mode or other
> > features in, say, GHCi that aid learning. As I've said, I'm in full
> favor of
> > adding these features.
>
> The old type for ($) is only a lie when the MagicHash extension is
> turned on.  Otherwise, it is not a lie.  I think the best solution is
> to pretty print the type depending on what language pragmas are in
> use.  In GHCI, this would be trivial.  The much harder case is haddock
> documentation.
>

Note: The old type of ($) has always been a lie, even without MagicHash, a
much stronger lie because the true type of ($) can't even be written in the
language today.

You can instantiate both the source and target types of ($) to polytypes,
not just monotypes.

This lets us use ($) in situations like

runST $ do ...

Having it infer a RankNType through its magical type inference rule there
doesn't require an extension on the behalf of the user, even if runST
required them at the definition site.

-Edward


> I think a good way around this would be an eventual patch to haddock
> that allows the user to select which extensions they want to use when
> browsing documentation.  There's a lot of usability issues that would
> need to be resolved with this still, but it reduces this technical
> discussion we're having down to a design discussion.  It also nicely
> lets the user specify the level of difficulty they want their prelude
> to be without causing incompatibilty with users who want a different
> level of prelude.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Reify and separating renamer+TH from type-checking

2016-01-13 Thread Edward Kmett
Worse, 'reify' is in many cases the very reason why folks are using
template-haskell in the first place to build instances or classes based on
properties of data types above the splice in the current module.

On Fri, Jan 8, 2016 at 2:40 PM, Edward Z. Yang  wrote:

> I implemented the refactoring to run the renamer and TH splices all
> first before doing any type-checking, but actually there's a problem:
> Template Haskell splices can call 'reify', which needs the type
> information in order to supply the information about the identifiers
> in question.  I can't think of any good way around this problem.
>
> Edward
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Kinds of type synonym arguments

2015-12-21 Thread Edward Kmett
I brought up the subject of allowing newtypes in kind # (or even in any
kind that ends in * or # after a chain of ->'s to get more powerful
Coercible instances) at ICFP this year and Simon seemed to think it'd be a
pretty straightforward modification to the typechecker.

I confess, he's likely waiting for me to actually sit down and give the
idea a nice writeup. ;)

This would be good for many things, especially when it comes to improving
the type safety of various custom c-- tricks.

-Edward

On Sun, Dec 20, 2015 at 2:14 PM, Ömer Sinan Ağacan 
wrote:

> I have another related question: What about allowing primitive types
> in newtypes?
>
> λ:4> newtype Blah1 = Blah1 Int
> λ:5> newtype Blah2 = Blah2 Int#
>
> :5:23: error:
> • Expecting a lifted type, but ‘Int#’ is unlifted
> • In the type ‘Int#’
>   In the definition of data constructor ‘Blah2’
>   In the newtype declaration for ‘Blah2’
>
> Ideally second definition should be OK, and kind of Blah2 should be #. Is
> this
> too hard to do?
>
> 2015-12-16 17:22 GMT-05:00 Richard Eisenberg :
> >
> > On Dec 16, 2015, at 2:06 PM, Ömer Sinan Ağacan 
> wrote:
> >>
> >> In any case, this is not that big deal. When I read the code I thought
> this
> >> should be a trivial change but apparently it's not.
> >
> > No, it's not. Your example (`f :: (Int#, b) -> b`) still has an unboxed
> thing in a boxed tuple. Boxed tuples simply can't (currently) hold unboxed
> things. And changing that is far from trivial. It's not the polymorphism
> that's the problem -- it's the unboxed thing in a boxed tuple.
> >
> > Richard
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Allow ambiguous types (with warning) by default

2015-12-05 Thread Edward Kmett
So you are saying you want users to write a ton of code that happens to
have signatures that can never be called and only catch it when they go to
try to actually use it in a concrete situation much later?

I don't really show how this would be a better default.

When and if users see the problem later they have to worry about if they
are doing something wrong at the definition site or the call site. With the
status quo it complains at the right time that you aren't going to sit
there flailing around trying to fix a call site that can never be fixed.

-Edward

On Sat, Dec 5, 2015 at 5:38 PM, David Feuer  wrote:

> The ambiguity check produces errors that are quite surprising to the
> uninitiated. When the check is suppressed, the errors at use sites are
> typically much easier to grasp. On the other hand, there's obviously a lot
> of value to catching mistakes as soon as possible. Would it be possible to
> turn that into a warning by default?
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Allow ambiguous types (with warning) by default

2015-12-05 Thread Edward Kmett
If you aren't the one writing the code that can't be called you may never
see the warning. It'll be tucked away in a cabal or stack build log
somewhere.

-Edward

On Sun, Dec 6, 2015 at 12:06 AM, David Feuer <david.fe...@gmail.com> wrote:

> No, I want it to *warn* by default. If I write
>
> foo :: something that will fail the ambiguity check
> bar = something that uses foo in a (necessarily) ambiguous way
>
> the current default leads me to do this:
>
> 1. Attempt to compile. Get an ambiguity error on foo whose exact cause
> is hard for me to see.
> 2. Enable AllowAmbiguousTypes and recompile. Get an error on bar whose
> exact cause is completely obvious, and that makes it perfectly clear
> what I need to do to fix foo.
> 3. Fix foo, and disable AllowAmbiguousTypes.
>
> I'd much rather go with
>
> 1. Attempt to compile. Get an ambiguity *warning* on foo whose exact
> cause is hard for me to see, but also an error on bar whose exact
> cause is completely obvious, and that makes it perfectly clear what I
> need to do to fix foo.
> 2. Fix foo.
>
> Simple example of how it is currently:
>
> > let foo :: Num a => F a; foo = undefined; bar :: Int; bar = foo
>
> :14:12:
> Couldn't match expected type ‘F a’ with actual type ‘F a0’
> NB: ‘F’ is a type function, and may not be injective
> The type variable ‘a0’ is ambiguous
> In the ambiguity check for the type signature for ‘foo’:
>   foo :: forall a. Num a => F a
> To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
> In the type signature for ‘foo’: foo :: Num a => F a
>
> Couldn't match what with what? Huh? Where did a0 come from?
>
> > :set -XAllowAmbiguousTypes
> > let foo :: Num a => F a; foo = undefined; bar :: Int; bar = foo
>
> :16:61:
> Couldn't match expected type ‘Int’ with actual type ‘F a0’
> The type variable ‘a0’ is ambiguous
> In the expression: foo
> In an equation for ‘bar’: bar = foo
>
> Aha! That's the problem! It doesn't know what a0 is! How can I tell it
> what a0 is? Oh! I can't, because foo doesn't give me a handle on it.
> Guess I have to fix foo.
>
> I'd really, really like to get *both* of those messages in one go,
> with the first one preferably explaining itself a bit better.
>
> On Sat, Dec 5, 2015 at 11:51 PM, Edward Kmett <ekm...@gmail.com> wrote:
> > So you are saying you want users to write a ton of code that happens to
> have
> > signatures that can never be called and only catch it when they go to
> try to
> > actually use it in a concrete situation much later?
> >
> > I don't really show how this would be a better default.
> >
> > When and if users see the problem later they have to worry about if they
> are
> > doing something wrong at the definition site or the call site. With the
> > status quo it complains at the right time that you aren't going to sit
> there
> > flailing around trying to fix a call site that can never be fixed.
> >
> > -Edward
> >
> > On Sat, Dec 5, 2015 at 5:38 PM, David Feuer <david.fe...@gmail.com>
> wrote:
> >>
> >> The ambiguity check produces errors that are quite surprising to the
> >> uninitiated. When the check is suppressed, the errors at use sites are
> >> typically much easier to grasp. On the other hand, there's obviously a
> lot
> >> of value to catching mistakes as soon as possible. Would it be possible
> to
> >> turn that into a warning by default?
> >>
> >>
> >> ___
> >> ghc-devs mailing list
> >> ghc-devs@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >>
> >
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Pre-Proposal: Introspective Template Haskell

2015-11-11 Thread Edward Kmett
In practice I find that almost every piece of template-haskell code I've
written gets broken by something every other release of GHC, so it hasn't
exactly been a shining beacon of backwards compatibility thus far.

Invariably it is always missing _something_ that I need, and anything that
ties it to a more canonical form like this would be a very good thing.

I'd strongly support this move.

A sample just from my current working directory:

haskell> grep -r MIN_VERSION_template_haskell */src

bifunctors/src/Data/Bifunctor/TH/Internal.hs:#if
MIN_VERSION_template_haskell(2,10,0)

bifunctors/src/Data/Bifunctor/TH/Internal.hs:#if
MIN_VERSION_template_haskell(2,7,0)

bifunctors/src/Data/Bifunctor/TH/Internal.hs:#if
MIN_VERSION_template_haskell(2,10,0)

bifunctors/src/Data/Bifunctor/TH/Internal.hs:#if
MIN_VERSION_template_haskell(2,8,0)

bifunctors/src/Data/Bifunctor/TH/Internal.hs:#if
MIN_VERSION_template_haskell(2,8,0)

bifunctors/src/Data/Bifunctor/TH/Internal.hs:#if
MIN_VERSION_template_haskell(2,8,0)

bifunctors/src/Data/Bifunctor/TH.hs:#ifndef MIN_VERSION_template_haskell

bifunctors/src/Data/Bifunctor/TH.hs:#if __GLASGOW_HASKELL__ < 710 &&
MIN_VERSION_template_haskell(2,8,0)

bifunctors/src/Data/Bifunctor/TH.hs:#if MIN_VERSION_template_haskell(2,7,0)

bifunctors/src/Data/Bifunctor/TH.hs:#if MIN_VERSION_template_haskell(2,7,0)

bifunctors/src/Data/Bifunctor/TH.hs:#if MIN_VERSION_template_haskell(2,7,0)

bifunctors/src/Data/Bifunctor/TH.hs:#if MIN_VERSION_template_haskell(2,7,0)

bifunctors/src/Data/Bifunctor/TH.hs:#if MIN_VERSION_template_haskell(2,7,0)

bifunctors/src/Data/Bifunctor/TH.hs:# if __GLASGOW_HASKELL__ >= 710 ||
!(MIN_VERSION_template_haskell(2,8,0))

bifunctors/src/Data/Bifunctor/TH.hs:#if MIN_VERSION_template_haskell(2,7,0)

free/src/Control/Monad/Free/TH.hs:#if MIN_VERSION_template_haskell(2,10,0)

lens/src/Control/Lens/Internal/FieldTH.hs:#if
MIN_VERSION_template_haskell(2,8,0)

lens/src/Control/Lens/Internal/TH.hs:#ifndef MIN_VERSION_template_haskell

lens/src/Control/Lens/Internal/TH.hs:#define
MIN_VERSION_template_haskell(x,y,z) (defined(__GLASGOW_HASKELL__) &&
__GLASGOW_HASKELL__ >= 706)

lens/src/Control/Lens/Internal/TH.hs:#if MIN_VERSION_template_haskell(2,9,0)

lens/src/Control/Lens/Plated.hs:#if !(MIN_VERSION_template_haskell(2,8,0))

lens/src/Control/Lens/TH.hs:#ifndef MIN_VERSION_template_haskell

lens/src/Control/Lens/TH.hs:#define MIN_VERSION_template_haskell(x,y,z)
(defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706)

lens/src/Control/Lens/TH.hs:#if !(MIN_VERSION_template_haskell(2,7,0))

lens/src/Control/Lens/TH.hs:#if MIN_VERSION_template_haskell(2,10,0)

lens/src/Control/Lens/TH.hs:#if !(MIN_VERSION_template_haskell(2,7,0))

lens/src/Language/Haskell/TH/Lens.hs:#ifndef MIN_VERSION_template_haskell

lens/src/Language/Haskell/TH/Lens.hs:#define
MIN_VERSION_template_haskell(x,y,z) 1

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,9,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,9,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,9,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,9,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
!MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,9,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
!MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
!MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,8,0)

lens/src/Language/Haskell/TH/Lens.hs:#if MIN_VERSION_template_haskell(2,9,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
MIN_VERSION_template_haskell(2,10,0)

lens/src/Language/Haskell/TH/Lens.hs:#if
MIN_VERSION_template_haskell(2,10,0)


Re: Pre-Proposal: Introspective Template Haskell

2015-11-11 Thread Edward Kmett
That would be a sufficient "horrible backdoor" for me. :)

-Edward

> On Nov 11, 2015, at 3:03 PM, Richard Eisenberg <e...@cis.upenn.edu> wrote:
> 
> 
>> On Nov 11, 2015, at 2:25 PM, Edward Kmett <ekm...@gmail.com> wrote:
>> 
>> As a data point, in a couple of packages I wind up forced into using 
>> mkNameG_v and mkNameG_tc in order to avoid incurring a dependency on a 
>> stage2 compiler today. Removing them would force me to drop support for 
>> stage1-only platforms offered by some linux distributions. 
>> 
>> If you're going to drop support for it, please consider offering me some 
>> horrible back door to get at the functionality that I can't currently 
>> replace by other means.
> 
> I've had to use these functions, too, mostly because TH didn't export the 
> functionality I needed. But this wouldn't be problematic in the new scenario: 
> just depend on the ghc package instead of template-haskell. Then you can do 
> whatever you like. :)
> 
>> -Edward
> 
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Pre-Proposal: Introspective Template Haskell

2015-11-11 Thread Edward Kmett
On Wed, Nov 11, 2015 at 12:50 PM, Richard Eisenberg 
wrote:

>
> This is a very good point. We would want to bless some API that would
> remain stable. Then, clients that go around that API get what they deserve.
> A starting point for the stable API would be today's template-haskell (less
> some unsafe features, like exposing NameG).
>

As a data point, in a couple of packages I wind up forced into using
mkNameG_v and mkNameG_tc in order to avoid incurring a dependency on a
stage2 compiler today. Removing them would force me to drop support for
stage1-only platforms offered by some linux distributions.

If you're going to drop support for it, please consider offering me some
horrible back door to get at the functionality that I can't currently
replace by other means.

-Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: too many lines too long

2015-11-10 Thread Edward Kmett
Heck, I've been able to use 132 columns since my VT-220 days. ;)

-Edward

On Mon, Nov 9, 2015 at 5:45 PM, Simon Peyton Jones 
wrote:

> In my view 80 chars is too short.  It was justified in the days of
> 80-column CRTs, but that just isn't a restriction any more.   I routinely
> edit in a much wider window.
>
> Clearly there's a judgement call here.  But I'd prefer 120 cols say.
>
> Simon
>
> -Original Message-
> From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Richard
> Eisenberg
> Sent: 09 November 2015 21:03
> To: ghc-devs Devs 
> Subject: too many lines too long
>
> Hi devs,
>
> We seem to be uncommitted to the ideal of 80-character lines. Almost every
> patch on Phab I look through has a bunch of "line too long" lint errors. No
> one seems to do much about these. And Phab's very very loud indication of a
> lint error makes reviewing the code harder.
>
> I like the ideal of 80-character lines. I aim for this ideal in my
> patches, falling short sometimes, of course. But I think the current
> setting of requiring everyone to "explain" away their overlong lines during
> `arc diff` and then trying hard to ignore the lint errors during code
> review is wrong. And it makes us all inured to more serious lint errors.
>
> How about this: after `arc diff` is run, it will count the number of
> overlong lines before and after the patch. If there are more after, have
> the last thing `arc diff` outputs be a stern telling-off of the dev, along
> the lines of
>
> > Before your patch, 15 of the edited lines were over 80 characters.
> > Now, a whopping 28 of them are. Can't you do better? Please?
>
> Would this be ignored more or followed more? Who knows. But it would sure
> be less annoying. :)
>
> What do others think?
>
> Thanks,
> Richard
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
>
> https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7cebcdeaa0675a490898dc08d2e94927cc%7c72f988bf86f141af91ab2d7cd011db47%7c1=6IXQEBFIJnDRWCSKmNxdVsWQm2bqPVPn133kblshukU%3d
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Unlifted data types

2015-10-28 Thread Edward Kmett
On Wed, Oct 28, 2015 at 9:19 AM, Richard Eisenberg <e...@cis.upenn.edu>
wrote:

> I don't have terribly much to add, but I do want to counter one point:
>
> On Oct 28, 2015, at 5:48 AM, Edward Kmett <ekm...@gmail.com> wrote:
> >  There are situations where we are truly polymorphic in lifting, e.g.
> (==) from Eq and compare from Ord don't care if the arguments of type 'a'
> are lifted or not.
>
> But these do, I think. In running code, if (==) is operating over a lazy
> type, it has to check if the pointer points to a thunk. If (==) is
> operating over a strict one, it can skip the check. This is not a big
> difference, but it *is* a difference.
>

Yes, but this is the job of the particular instance. Remember the instance
gets to know the type it is working at, and its corresponding levity.

class Eq (l :: Levity) (t :: Type l) where
  (==) :: a -> a -> Bool

instance Eq @Unlifted (SmallMutableArray s a) where
  (==) = sameSmallMutableArray

instance Eq @Lifted [] where
  (==) = ...

Your objection arises for things like

instance Eq @l (Foo @l)

Where the same code has to execute with different levities, but if I can't
even case or seq on a value with polymorphic levity, and can't construct
such a value but merely pass it around then such code is still sound. It
isn't safe to write functions that return values of polymorphic levity. I
can however hand them back as (# a #). This is how we handle indexing into
a array today.

If we had a Maybe that was levity polymorphic in its argument

Maybe :: forall (l :: Levity). Type l -> Lifted

instance Eq @l a => Eq @Lifted (Maybe @l a) where
  Just a == Just b = a == b
  _ == _ = False

is still okay under these rules, it never case analyzes a value of
polymorphic levity, never seq's it. Neither of those things is legal
because you can't 'enter' the closure.

If it was levity polymorphic in the result type

Maybe :: forall (i :: Levity) (j :: Levity). Type i -> Type j

then your objection comes true.

I can't naively write:

instance Eq @i a => Eq j (Maybe @i @j a) where
  Just a == Just b = a == b
  _ == _ = False

without compiling the same code twice, because of the act of case analysis.

If we don't have real 'strict data types' in Lifted this situation never
arises though.

Even if we do I can write separate:

instance Eq @i a => Eq Lifted (Maybe @i Lifted a)
instance Eq @i a => Eq Unlifted (Maybe @i Unlifted a)

instances, unless we can do better by writing a class constraint on the
levity that we can use in a clever way here.

I'm mostly concerned with the middle case where we don't overload data
types on their levity, and try to recover the ability to talk about strict
data types by other more explicit means, but rather permit them to accept
arguments of different levities. There none of the code I care about
actually needs to act differently based on levity.

Anything that results in a function space there has to care about levity,
but until a type occurs on the right hand side of an (->) or I go to seq a
value of that type or case analyze it, I don't need to care about if its
lifted or unlifted.

With Dan's (!S) then things get more complicated in ways I don't fully
understand the ramifications of yet, as you might be able to lift some of
those restrictions.

A little more thinking about this has led here: The distinction isn't
> really forall vs. pi. That is, in the cases where the levity matters, we
> don't really need to pi-quantify. Instead, it's exactly like type classes.
>

In many ways pi comes down to doing typeclass like things, you're tracking
information from the type system. The vehicle we have for doing that today
is typeclasses. I've been thinking about anything that i have that actually
needs the "pi" there as a form of "constraint" passing all along, with the
constraint being whatever introspection you need to allow on the type to
carry on.

Imagine, for a moment, that we have an alternate universe where strict is
> the default, and we have
>
> > data Lazy a = Thunk (() -> a) | WHNF a
>
> The WHNF is a bit of a lie, because this representation would mean that
> the contents of a WHNF are fully evaluated. But let's not get hung up on
> that point.
>
> Then, we have
>
> > type family BaseType a where
> >   BaseType (Lazy a) = a
> >   BaseType a = a
> >
> > class Forceable a where
> >   force :: a -> BaseType a
> >
> > instance Forceable a where
> >   force = id
> >
> > instance Forceable (Lazy a) where
> >  force (Thunk f) = f ()
> >  force (WHNF a) = a
>
> Things that need to behave differently depending on strictness just take a
> dictionary of the Forceable class. Equivalently, they make a runtime
> decision of whether to force or not. So we don't need an exponential number
> of maps. We need a m

Re: Temporarily pinning a thread to a capability

2015-10-28 Thread Edward Kmett
If the number of capabilities is increased or decreased while everything I
have here is running I'm going to have to blow up the world anyways.

Basically I'll need to rely on an invariant that setNumCapabilities is
called before you spin up these Par-like computations.

-Edward

On Wed, Oct 28, 2015 at 4:28 PM, Ryan Yates <fryguy...@gmail.com> wrote:

> A thread with TSO_LOCKED can be migrated if the number of capabilities
> decreases.
>
> Ryan
>
> On Tue, Oct 27, 2015 at 11:35 PM, Edward Kmett <ekm...@gmail.com> wrote:
>
>> Would anything go wrong with a thread id if I pinned it to a capability
>> after the fact?
>>
>> I could in theory do so just by setting
>>
>> tso->flags |= TSO_LOCKED
>>
>> and then disabling this later by restoring the TSO flags.
>>
>> I can't think of anything but I figured folks here might be able to think
>> of invariants I don't know about.
>>
>> Usage scenario:
>>
>> I have a number of things where I can't afford a map from a ThreadId# or
>> even its internal id to a per-thread value for bounded wait-free
>> structures.
>>
>> On the other hand, I can afford one entry per capability and to make a
>> handful of primitives that can't be preempted, letting me use normal
>> writes, not even a CAS, to update the capability-local variable in a
>> primitive (indexing into an array of size based on the number of
>> capabilities). This lets me bound the amount of "helpers" to consider by
>> the capability count rather than the potentially much larger and much more
>> variable number of live threads.
>>
>> However, I may need to access this stuff in "pure" code that wasn't
>> written with my needs in mind, so I need to at least temporarily pin the
>> current thread to a fixed capability for the duration when that happens.
>>
>> This isn't perfect, it won't react to a growing number of capabilities
>> nicely in the future, but it does handle a lot of things I can't do now at
>> all without downgrading to lock-free and starving a lot of computations, so
>> I'm hoping the answer is "it all works". =)
>>
>> -Edward
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Unlifted data types

2015-10-28 Thread Edward Kmett
On Wed, Oct 28, 2015 at 5:05 AM, Simon Peyton Jones 
wrote:

> I'm out of bandwidth at the moment, but let me just remark that this is
> swampy territory. It's easy to mess up.
>
> A particular challenge is polymorphism:
>
>   map :: forall a b. (a->b) -> [a] -> [b]
>   map f (x:xs) = (f x) : (map f xs)
>
> In the compiled code for map, is a thunk built for (f x), or is it
> evaluated eagerly.  Well, if you can instantiate the 'b' with !Int, say,
> then it should be evaluated eagerly. But if you instantiate with Int, then
> build a thunk.   So, we really need two compiled versions of 'map'.  Or
> perhaps four if we take 'b' into account.  In general an exponential number.
>

That's one reason that GHC doesn't let you instantiate a polymorphic type
> variable with an unlifted type, even if it is boxed.
>

This is one of the things we'd like to be able to fix. Right now I have a
small explosion of code going on that is being duplicated over and over to
parameterize over different unlifted types.

In the discussions about levity/lifting so far Dan and I have been trying
to tease apart what cases can be handled "forall" style rather than "pi"
style to borrow the split from Richard's presentation, just to get at a
sense of what really could be talked about without needing different
calling conventions, despite lifting. There are situations where we are
truly polymorphic in lifting, e.g. (==) from Eq and compare from Ord don't
care if the arguments of type 'a' are lifted or not.

Until you go to write a function application that returns a value of that
type. If all you do is rearrange them then that machinery can be parametric
in the choice. `map` on the other hand, cares about the selection because
of the `f x` application.

(Similarly, `min` and `max` from Ord do care about the convention on hand.)

One could see a world wherein you could parameterize such an instance on
levity explicitly, but it is pretty exhausting to think about.


> Another big issue is that *any* mixture of subtyping and (Haskell-style)
> parametric polymorphism gets very complicated very fast.  Especially when
> you add higher kinds.  (Then you need variance annotations, and before long
> you want variance polymorphism.)  I'm extremely dubious about adding
> subtyping to Haskell.  That's one reason Scala is so complicated.
>

I was actually quite surprised to see a subtyping relationship rear its
head in:

https://ghc.haskell.org/trac/ghc/attachment/wiki/ImpredicativePolymorphism/Impredicative-2015/impredicativity.pdf

But re-imagining GHC is good too.  Swampy territory it may be, but it's
> also important, and there really *ought* to be a more seamless of combining
> strictness and laziness.


I'm somewhat dubious of most approaches that try to mix strictness and
laziness under one umbrella. That is why trying to tease out the small
handful of cases where we are truly parametric in levity seems interesting.
Finding out some situations existed where we really don't care if a type is
lifted or not was eye opening to me personally, at least.

-Edward


> |  -Original Message-
> |  From: Dan Doel [mailto:dan.d...@gmail.com]
> |  Sent: 27 October 2015 23:42
> |  To: Richard Eisenberg
> |  Cc: Simon Peyton Jones; ghc-devs
> |  Subject: Re: Unlifted data types
> |
> |  Hello,
> |
> |  I've added a section with my notes on the minimal semantics required to
> |  address what Haskell lacks with respect to strict types.
> |
> |  Ed Kmett pointed me to some stuff that I think may fix all the problems
> with
> |  the !T sort of solution. It builds on the new constraint being
> considered
> |  for handling impredicativity. The quick sketch goes like this. Given the
> |  declaration:
> |
> |  data Nat = Z | S !Nat
> |
> |  then:
> |
> |  Nat :: *
> |  !Nat :: Unlifted
> |  S :: Nat -> Nat
> |
> |  But we also have:
> |
> |  !Nat <~ Nat
> |
> |  and the witness of this is just an identity function, because all
> values of
> |  type !Nat are legitimate values of type Nat. Then we can
> |  have:
> |
> |  case n of
> |S m -> ...
> |Z -> ...
> |
> |  where m has type !Nat, but we can still call `S m` and the like, because
> |  !Nat <~ Nat. If we do use `S m`, the S call will do some unnecessary
> |  evaluation of m, but this can (hopefully) be fixed with an optimization
> |  based on knowing that m has type !Nat, which we are weakening to Nat.
> |
> |  Thoughts?
> |
> |  -- Dan
> |
> |
> |  On Thu, Oct 8, 2015 at 8:36 AM, Richard Eisenberg 
> wrote:
> |  >
> |  > On Oct 8, 2015, at 6:02 AM, Simon Peyton Jones  >
> |  wrote:
> |  >
> |  >> What's the wiki page?
> |  >
> |  > https://ghc.haskell.org/trac/ghc/wiki/UnliftedDataTypes
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs 

Re: Unlifted data types

2015-10-27 Thread Edward Kmett
The idea of treating !S as a subtype of S and then relying on the potential
for new impredicativity machinery to let us just talk about how !S <= S
makes me really happy.

data Nat = Z | S !Nat

Pattern matching on S could give back the tighter type !Nat rather than Nat
for the argument, and if we ever have to show that to a user, the
'approximation' machinery would show it to users as Nat, concealing this
implementation detail. Similarly matching with an as-pattern as part of a
pattern that evaluates could do the same.

The constructor is a bit messier. It should really give back S :: Nat ->
Nat as what the constructor should behave as rather than S :: !Nat -> Nat,
because this will match existing behavior. Then the exposed constructor
would force the argument before storing it away, just like we do today and
we could recover via a sort of peephole optimization the elimination of the
jump into the closure to evaluate when it is fed something known to be of
type !Nat by some kind of "case/(!)-coercion" rule in the optimizer.

I'm partial to those parts of the idea and think it works pretty well.

I'm not sure how well it mixes with all the other discussions on levity
polymorphism though. Notably: Trying to get to having !Nat live in an
Unlifted kind, while Nat has a different kind seems likely to cause all
sorts of headaches. =/

-Edward

On Tue, Oct 27, 2015 at 7:42 PM, Dan Doel  wrote:

> Hello,
>
> I've added a section with my notes on the minimal semantics required
> to address what Haskell lacks with respect to strict types.
>
> Ed Kmett pointed me to some stuff that I think may fix all the
> problems with the !T sort of solution. It builds on the new constraint
> being considered for handling impredicativity. The quick sketch goes
> like this. Given the declaration:
>
> data Nat = Z | S !Nat
>
> then:
>
> Nat :: *
> !Nat :: Unlifted
> S :: Nat -> Nat
>
> But we also have:
>
> !Nat <~ Nat
>
> and the witness of this is just an identity function, because all
> values of type !Nat are legitimate values of type Nat. Then we can
> have:
>
> case n of
>   S m -> ...
>   Z -> ...
>
> where m has type !Nat, but we can still call `S m` and the like,
> because !Nat <~ Nat. If we do use `S m`, the S call will do some
> unnecessary evaluation of m, but this can (hopefully) be fixed with an
> optimization based on knowing that m has type !Nat, which we are
> weakening to Nat.
>
> Thoughts?
>
> -- Dan
>
>
> On Thu, Oct 8, 2015 at 8:36 AM, Richard Eisenberg 
> wrote:
> >
> > On Oct 8, 2015, at 6:02 AM, Simon Peyton Jones 
> wrote:
> >
> >> What's the wiki page?
> >
> > https://ghc.haskell.org/trac/ghc/wiki/UnliftedDataTypes
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Temporarily pinning a thread to a capability

2015-10-27 Thread Edward Kmett
Would anything go wrong with a thread id if I pinned it to a capability
after the fact?

I could in theory do so just by setting

tso->flags |= TSO_LOCKED

and then disabling this later by restoring the TSO flags.

I can't think of anything but I figured folks here might be able to think
of invariants I don't know about.

Usage scenario:

I have a number of things where I can't afford a map from a ThreadId# or
even its internal id to a per-thread value for bounded wait-free
structures.

On the other hand, I can afford one entry per capability and to make a
handful of primitives that can't be preempted, letting me use normal
writes, not even a CAS, to update the capability-local variable in a
primitive (indexing into an array of size based on the number of
capabilities). This lets me bound the amount of "helpers" to consider by
the capability count rather than the potentially much larger and much more
variable number of live threads.

However, I may need to access this stuff in "pure" code that wasn't written
with my needs in mind, so I need to at least temporarily pin the current
thread to a fixed capability for the duration when that happens.

This isn't perfect, it won't react to a growing number of capabilities
nicely in the future, but it does handle a lot of things I can't do now at
all without downgrading to lock-free and starving a lot of computations, so
I'm hoping the answer is "it all works". =)

-Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Taking a step back

2015-10-20 Thread Edward Kmett
Johan,

Thank you so much for all of your contributions to the community.

I confess, there are days when I find myself lost in maintenance hell that
I feel a desire to throw in the towel as well. (If Eric Mertens and others
hadn't picked up so much of the slack on my own projects I'm afraid I
likely would have reached the point of gravitational collapse long ago.)

I'm terribly sorry to hear that recent attempts to mitigate the impact of
changes, the three release policy which as inspired by comments you made,
haven't been enough to assuage your fears and discontent about the current
direction things are heading.

We are all poorer for the loss of your guidance.

-Edward

On Tue, Oct 20, 2015 at 9:59 AM, Johan Tibell 
wrote:

> Friends,
>
> I'm taking a step back from day-to-day library work.
>
> There are two main reasons I use Haskell: on one hand I find writing
> Haskell educational and fun. On the other I hope to make it a viable
> alternative to existing mainstream languages. With recent changes to our
> core libraries, and the general direction these are moving in, I believe
> we're moving away from becoming a viable alternative to those mainstream
> languages.
>
> This has some practical implications for how I spend my Haskell hacking
> time. Much of what I do is maintaining and working on libraries that are
> needed for real world usage, but that aren't that interesting to work on.
> I've lost the motivation to work on these.
>
> I've decided to take a step back from the core maintenance work on cabal,
> network, containers, and a few others* starting now. I've already found
> replacement maintainers for these.
>
> I still plan to hack on random side projects, including GHC, and to
> continue coming to Haskell events and conference, just with a shorter bug
> backlog to worry about. :)
>
> -- Johan Tibell
>
> * For now I will still hack on unordered-containers and ekg, as there are
> some things I'd like to experiment with there.
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: MonadFail decisions

2015-10-16 Thread Edward Kmett
Not a bad idea. I think Herbert was talking about calling it -Wcompat or
something.

On Fri, Oct 16, 2015 at 1:06 PM, Howard B. Golden <howard_b_gol...@yahoo.com
> wrote:

> On Friday, October 16, 2015 9:22 AM, Edward Kmett wrote:
>
>
> > It sounds like we'll need to delay the warnings themselves until around
> 8.4.
>
> I propose an optional generic flag -fearly-warning (pun slightly intended)
> to get _all_ warnings of planned changes.
>
> Howard
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: MonadFail decisions

2015-10-16 Thread Edward Kmett
The current intention is to go ahead with MonadFail.

It sounds like we'll need to delay the warnings themselves until around 8.4.

We can add them, but not turn them on by default in the short term. This
has the knock-on effect of delaying the whole plan a release or two, but
otherwise the plan is very actionable.

A lot of the opposition comes from fear that we 'might do anything at any
time'. If we're up front about what is coming and give sufficient notice
and the ability for folks to maintain a reasonably wide backwards
compatibility window without needing to dip into CPP or suppress warnings
them most of those fears go away.

-Edward

On Fri, Oct 16, 2015 at 12:09 PM, David Luposchainsky <
dluposchain...@googlemail.com> wrote:

> On 13.10.2015 16:29, Simon Peyton Jones wrote:
> > Also, David, did our conversation at HX help you get un-stuck?
>
> Hi Simon,
>
> yes, it was definitely a good pointer. On the other hand, I found the
> Haskell
> Exchange to be quite a frustrating event with respect to current events:
> there
> was a load of very loud, but in my opinion very wrong, categorical
> opposition to
> breaking changes in general.
> I spent quite a bit of time worrying about MonadFail in the past, but
> right now
> I'd like to wait for a "tentative yes" from the CLC before I keep going,
> because
> I'm really not sure the mob is going to make me throw away my patch.
> Granted, a
> lot of the discussion is about MRP, but many of the points brought up
> there are
> equally valid against the MFP.
>
> David
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: MonadFail decisions

2015-10-16 Thread Edward Kmett
Hi David,

I took the time to update the MonadFail wiki page to include both the
timeline currently under consideration, lengthening the timeline to finish
in 8.8 to comply with the "3 release policy" and to ensure that folks
always have a notification of pending breaking changes.

I included a couple of personal comments about the desugaring in 1.3 where
we could do better. The improvements in 1.3 could be made any time over the
8.0 and 8.2 releases before we start expecting people to cut over in 8.4
without impact.

As for the "mob", please keep in mind that the vast majority of feedback
about the MonadFail proposal has been positive and draw heart from that.
Many of the folks who were against the Foldable/Traversable generalizations
(e.g. Lennart) are heavily in favor of MFP.

-Edward






On Fri, Oct 16, 2015 at 12:09 PM, David Luposchainsky <
dluposchain...@googlemail.com> wrote:

> On 13.10.2015 16:29, Simon Peyton Jones wrote:
> > Also, David, did our conversation at HX help you get un-stuck?
>
> Hi Simon,
>
> yes, it was definitely a good pointer. On the other hand, I found the
> Haskell
> Exchange to be quite a frustrating event with respect to current events:
> there
> was a load of very loud, but in my opinion very wrong, categorical
> opposition to
> breaking changes in general.
> I spent quite a bit of time worrying about MonadFail in the past, but
> right now
> I'd like to wait for a "tentative yes" from the CLC before I keep going,
> because
> I'm really not sure the mob is going to make me throw away my patch.
> Granted, a
> lot of the discussion is about MRP, but many of the points brought up
> there are
> equally valid against the MFP.
>
> David
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: MonadFail decisions

2015-10-13 Thread Edward Kmett
On Tue, Oct 13, 2015 at 10:29 AM, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> Dear Edward and Core Libraries Committee
>
>
>
> Can you tell us what plan you want to execute for MonadFail?
> Specifically, in https://wiki.haskell.org/MonadFail_Proposal
>
> · Is the specification in 1.3 what you have agreed?
>
The main concern I have with section 1.3 is the statement about view
pattern desugaring. It really should just borrow the failability of the
pattern part. The view pattern component adds nothing.

Getting better introspection on pattern synonyms to avoid them becoming a
huge source of MonadFail constraints would be good as well.

We can in theory incorporate improvements on this front gradually however.

> · Is the transition strategy in 1.7 exactly what you want?
>
> The "3 release policy" informs the design here a bit. Notably it puts off
warnings for this for a while, as we can't warn about it in 8.0 (or really
even 8.2) which means that at least in 8.0 this is almost entirely a
library change. Under that policy we can't do the warnings until 8.4 and
cut-over til 8.6.

For 8.0 the change to 1.7 basically comes down to "don't turn on the
warnings by default yet".

We can’t implement 8.0 without being sure of the specification!  The
> current Phab is
>
> https://phabricator.haskell.org/D1248
>
>
>
> Also, David, did our conversation at HX help you get un-stuck?
>
>
-Edward


>
>
> Thanks
>
>
>
> Simon
>
>
>
> *From:* haskell-core-librar...@googlegroups.com [mailto:
> haskell-core-librar...@googlegroups.com] *On Behalf Of *Edward Kmett
> *Sent:* 13 October 2015 01:43
> *To:* core-libraries-commit...@haskell.org
> *Subject:* [core libraries] Prelude: 3 Release Policy
>
>
>
> Recently there has been a bunch of chatter about ways to mitigate the
> amount of CPP pushed on users by changes to the Prelude.
>
>
>
> In particular the discussion has been around the idea of trying to ensure
> that it is possible to write code in _some_ way without CPP that can run
> backwards for 3 releases of GHC, preferably in a -Wall safe manner. The
> approach they may have to use may not be the idiomatic way, but in general
> it should exist.
>
>
>
> Gershom ran around at the Haskell Exchange sounding folks out about this
> idea, and it seems to codify a reasonable tension between the "change
> nothing" and "change everything" camps. The feedback thus far seems to be
> noises of "grumbling acceptance" rather than the current state of outright
> panic that we might do anything at any time.
>
>
>
> I'm personally considering this a very high priority for all changes to
> Prelude going forward.
>
>
>
> The 3 years forms a backward-facing window, not a guarantee against future
> change, but we should of course try to let folks know what is coming with a
> decent time horizon so folks can look forward as well. That is a separate
> concern, though.
>
>
>
> I'm not ready to give the "3 release policy" outright veto power over new
> functionality, but at least if we have two plans that can in the end yield
> the same end state, we should definitely err on the side of the plan that
> falls within these guidelines, and be very well ready to explain to a
> rather irate community when we violate this rubric. It shouldn't be done
> lightly, if at all, if we can help it!
>
>
>
> All in all it is a fairly weak guarantee, but it does have some impact on
> current items under consideration.
>
>
>
> Off the top of my head:
>
>
>
> * A number of new members for Floating were passed by proposal back before
> 7.10 went out the door, but haven't found their way into base yet: expm1,
> log1p, etc. are absolutely required for decent precision numerics. When the
> proposal passed we ultimately decided _not_ to include default definitions
> for these to force authors to implement them explicitly. Under the
> guidelines here, the plan would likely have to include default definitions
> for these to start when introducing them in 8.0. Then in 8.4 we could in
> theory remove the defaults and remain in compliance with the letter of the
> law here or introduce an ad hoc warning about lack of implementation, and
> remove the defaults in 8.6, depending on how gradual an introduction we
> wanted to give. We wouldn't be able to do the warnings in 8.2, however, and
> remain within the letter of the law, and we wouldn't be able to introduce
> them without defaults without violating the no-warnings guideline.
>
>
>
> * MonadFail reform proposal wouldn't be able to start issuing warnings
> about missing instances until 8.4 even if we put in Mona

Re: Deriving Contravariant and Profunctor

2015-09-11 Thread Edward Kmett
They'd all act the same assuming any or all of the instances existed, but
GHC can't backtrack and figure out which way to get there, it'll only look
at the instance head.

-Edward

On Fri, Sep 11, 2015 at 2:22 PM, David Feuer <david.fe...@gmail.com> wrote:

> Oh, I see... you get horrible overlap problems there. Blech! I guess
> they'll all act the same (modulo optimized <$ and such), but GHC can't
> know that and will see them as forever incoherent.
>
> On Fri, Sep 11, 2015 at 1:52 PM, Edward Kmett <ekm...@gmail.com> wrote:
> > Actually it is trickier than you'd think.
> >
> > With "Functor" you can pretend that contravariance doesn't exist.
> >
> > With both profunctor and contravariant it is necessarily part of the
> puzzle.
> >
> > data Compose f g a = Compose (f (g a))
> >
> > * are both f and g contravariant leading to a functor?
> > * is f contravariant and g covariant leading to a contravariant functor?
> > * is f covariant and g contravariant leading to a contravariant functor?
> >
> > data Wat p f a b = Wat (p (f a) b)
> >
> > is p a Profunctor or a Bifunctor? is f Contravariant or a Functor?
> >
> > We investigated adding TH code-generation for the contravariant package,
> and
> > ultimately rejected it on these grounds.
> >
> > https://github.com/ekmett/contravariant/issues/17
> >
> > -Edward
> >
> >
> >
> > On Fri, Sep 11, 2015 at 12:49 PM, David Feuer <david.fe...@gmail.com>
> wrote:
> >>
> >> Would it be possible to add mechanisms to derive Contravariant and
> >> Profunctor instances? As with Functor, each algebraic datatype can
> >> only have one sensible instance of each of these.
> >>
> >> David Feuer
> >> ___
> >> ghc-devs mailing list
> >> ghc-devs@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >
> >
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Unlifted data types

2015-09-09 Thread Edward Kmett
I think ultimately the two views of levity that we've been talking diverge
along the same lines as the pi vs forall discussion from your Levity
polymorphism talk.

I've been focused entirely on situations where forall suffices, and no
distinction is needed in how you compile for both levities.

Maybe could be polymorphic using a mere forall in the levity of the boxed
argument it carries as it doesn't care what it is, it never forces it,
pattern matching on it just gives it back when you pattern match on it.

Eq or Ord could just as easily work over anything boxed. The particular Eq
_instance_ needs to care about the levity.

Most of the combinators for working with Maybe do need to care about that
levity however.

e.g. consider fmap in Functor, the particular instances would care. Because
you ultimately wind up using fmap to build 'f a' values and those need to
know how the let binding should work. There seems to be a pi at work there.
Correct operational behavior would depend on the levity.

But if we look at what inference should probably grab for the levity of
Functor:

you'd get:

class Functor (l : Levity) (l' : Levity') (f :: GC l -> GC l') where
   fmap :: forall a b. (a :: GC l) (b :: GC l). (a -> b) -> f a -> f b

Baed on the notion that given current practices, f would cause us to pick a
common kind for a and b, and the results of 'f'. Depending on how and if we
decided to default to * unless annotated in various situations would drive
this closer and closer to the existing Functor by default.

These are indeed distinct functors with distinct operational behavior, and
we could implement each of them by supplying separate instances, as the
levity would take part in the instance resolution like any other kind
argument.

Whether we could expect an average Haskeller to be willing to do so is an
entirely different matter.

-Edward


On Wed, Sep 9, 2015 at 12:44 PM, Dan Doel  wrote:

> On Wed, Sep 9, 2015 at 9:03 AM, Richard Eisenberg 
> wrote:
> > No functions (excepting `error` and friends) are truly levity
> polymorphic.
>
> I was talking with Ed Kmett about this yesterday, and he pointed out
> that this isn't true. There are a significant array of levity
> polymorphic functions having to do with reference types. They simply
> shuffle around pointers with the right calling convention, and don't
> really care what levity their arguments are, because they're just
> operating uniformly either way. So if we had:
>
> MVar# :: forall (l :: Levity). * -> TYPE (Boxed l) -> TYPE (Boxed
> Unlifted)
>
> then:
>
> takeMVar :: forall s (l :: Levity) (a :: TYPE (Boxed l)). MVar# s
> l a -> State# s -> (# State# s, a #)
> putMVar :: forall s (l :: Levity) (a :: Type (Boxed l)). MVar# s l
> a -> a -> State# s -> State# s
>
> are genuinely parametric in l. And the same is true for MutVar#,
> Array#, MutableArray#, etc.
>
> I think data type constructors are actually parametric, too (ignoring
> data with ! in them for the moment; the underlying constructors of
> those). Using a constructor just puts the pointers for the fields in
> the type, and matching on a constructor gives them back. They don't
> need to care whether their fields are lifted or not, they just
> preserve whatever the case is.
>
> But this:
>
> > We use levity polymorphism in the types to get GHC to use its existing
> type inference to infer strictness. By the time type inference is done, we
> must ensure that no levity polymorphism remains, because the code generator
> won't be able to deal with it.
>
> Is not parametric polymorphism; it is ad-hoc polymorphism. It even has
> the defaulting step from type classes. Except the ad-hoc has been
> given the same notation as the genuinely parametric, so you can no
> longer identify the latter. (I'm not sure I'm a great fan of the
> ad-hoc part anyway, to be honest.)
>
> -- Dan
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: ArrayArrays

2015-09-08 Thread Edward Kmett
Once you start to include all the other primitive types there is a bit more
of an explosion. MVar#, TVar#, MutVar#, Small variants, etc. can all be
modified to carry unlifted content.

Being able to be parametric over that choice would permit a number of
things in user land to do the same thing with an open-ended set of design
possibilities that are rather hard to contemplate in advance. e.g. being
able to abstract over them could let you just use a normal (,) to carry
around unlifted parametric data types or being able to talk about [MVar# s
a] drastically reducing the number of one off data types we need to invent.

If you can talk about the machinery mentioned above then you can have
typeclasses parameterized on an argument that could be either unlifted or
lifted.

I'm not willing to fight too hard for it, but it feels more like the
"right" solution than retaining a cut-and-paste copy of the same code and
bifurcating further on each argument you want to consider such a degree of
freedom.

As such it seems like a pretty big win for a comparatively minor change to
the levity polymorphism machinery.

-Edward

On Tue, Sep 8, 2015 at 3:40 AM, Simon Marlow <marlo...@gmail.com> wrote:

> This would be very cool, however it's questionable whether it's worth it.
>
> Without any unlifted kind, we need
>  - ArrayArray#
>  - a set of new/read/write primops for every element type,
>either built-in or made from unsafeCoerce#
>
> With the unlifted kind, we would need
>  - ArrayArray#
>  - one set of new/read/write primops
>
> With levity polymorphism, we would need
>  - none of this, Array# can be used
>
> So having an unlifted kind already kills a lot of the duplication,
> polymorphism only kills a bit more.
>
> Cheers
> Simon
>
> On 08/09/2015 00:14, Edward Kmett wrote:
>
>> Assume we had the ability to talk about Levity in a new way and instead
>> of just:
>>
>> data Levity = Lifted | Unlifted
>>
>> type * = TYPE 'Lifted
>> type # = TYPE 'Unlifted
>>
>> we replace had a more nuanced notion of TYPE parameterized on another
>> data type:
>>
>> data Levity = Lifted | Unlifted
>> data Param = Composite | Simple Levity
>>
>> and we parameterized TYPE with a Param rather than Levity.
>>
>> Existing strange representations can continue to live in TYPE 'Composite
>>
>> (# Int# , Double #) :: TYPE 'Composite
>>
>> and we don't support parametricity in there, just like, currently we
>> don't allow parametricity in #.
>>
>> We can include the undefined example from Richard's talk:
>>
>> undefined :: forall (v :: Param). v
>>
>> and ultimately lift it into his pi type when it is available just as
>> before.
>>
>> But we could let consider TYPE ('Simple 'Unlifted) as a form of
>> 'parametric #' covering unlifted things we're willing to allow
>> polymorphism over because they are just pointers to something in the
>> heap, that just happens to not be able to be _|_ or a thunk.
>>
>> In this setting, recalling that above, I modified Richard's TYPE to take
>> a Param instead of Levity, we can define a type alias for things that
>> live as a simple pointer to a heap allocated object:
>>
>> type GC (l :: Levity) = TYPE ('Simple l)
>> type * = GC 'Lifted
>>
>> and then we can look at existing primitives generalized:
>>
>> Array# :: forall (l :: Levity) (a :: GC l). a -> GC 'Unlifted
>> MutableArray# :: forall (l :: Levity) (a :: GC l). * -> a -> GC 'Unlifted
>> SmallArray# :: forall (l :: Levity) (a :: GC l). a -> GC 'Unlifted
>> SmallMutableArray# :: forall (l :: Levity) (a :: GC l). * -> a -> GC
>> 'Unlifted
>> MutVar# :: forall (l :: Levity) (a :: GC l). * -> a -> GC 'Unlifted
>> MVar# :: forall (l :: Levity) (a :: GC l). * -> a -> GC 'Unlifted
>>
>> Weak#, StablePtr#, StableName#, etc. all can take similar modifications.
>>
>> Recall that an ArrayArray# was just an Array# hacked up to be able to
>> hold onto the subset of # that is collectable.
>>
>> Almost all of the operations on these data types can work on the more
>> general kind of argument.
>>
>> newArray# :: forall (s :: *) (l :: Levity) (a :: GC l). Int# -> a ->
>> State# s -> (# State# s, MutableArray# s a #)
>>
>> writeArray# :: forall (s :: *) (l :: Levity) (a :: GC l). MutableArray#
>> s a -> Int# -> a -> State# s -> State# s
>>
>> readArray# :: forall (s :: *) (l :: Levity) (a :: GC l). MutableArray# s
>> a -> Int# -> State# s -> (# State# s, a #)
>>
>> etc.
>>
>> Only a couple of our existin

Re: ArrayArrays

2015-09-07 Thread Edward Kmett
Assume we had the ability to talk about Levity in a new way and instead of
just:

data Levity = Lifted | Unlifted

type * = TYPE 'Lifted
type # = TYPE 'Unlifted

we replace had a more nuanced notion of TYPE parameterized on another data
type:

data Levity = Lifted | Unlifted
data Param = Composite | Simple Levity

and we parameterized TYPE with a Param rather than Levity.

Existing strange representations can continue to live in TYPE 'Composite

(# Int# , Double #) :: TYPE 'Composite

and we don't support parametricity in there, just like, currently we don't
allow parametricity in #.

We can include the undefined example from Richard's talk:

undefined :: forall (v :: Param). v

and ultimately lift it into his pi type when it is available just as before.

But we could let consider TYPE ('Simple 'Unlifted) as a form of 'parametric
#' covering unlifted things we're willing to allow polymorphism over
because they are just pointers to something in the heap, that just happens
to not be able to be _|_ or a thunk.

In this setting, recalling that above, I modified Richard's TYPE to take a
Param instead of Levity, we can define a type alias for things that live as
a simple pointer to a heap allocated object:

type GC (l :: Levity) = TYPE ('Simple l)
type * = GC 'Lifted

and then we can look at existing primitives generalized:

Array# :: forall (l :: Levity) (a :: GC l). a -> GC 'Unlifted
MutableArray# :: forall (l :: Levity) (a :: GC l). * -> a -> GC 'Unlifted
SmallArray# :: forall (l :: Levity) (a :: GC l). a -> GC 'Unlifted
SmallMutableArray# :: forall (l :: Levity) (a :: GC l). * -> a -> GC
'Unlifted
MutVar# :: forall (l :: Levity) (a :: GC l). * -> a -> GC 'Unlifted
MVar# :: forall (l :: Levity) (a :: GC l). * -> a -> GC 'Unlifted

Weak#, StablePtr#, StableName#, etc. all can take similar modifications.

Recall that an ArrayArray# was just an Array# hacked up to be able to hold
onto the subset of # that is collectable.

Almost all of the operations on these data types can work on the more
general kind of argument.

newArray# :: forall (s :: *) (l :: Levity) (a :: GC l). Int# -> a -> State#
s -> (# State# s, MutableArray# s a #)

writeArray# :: forall (s :: *) (l :: Levity) (a :: GC l). MutableArray# s a
-> Int# -> a -> State# s -> State# s

readArray# :: forall (s :: *) (l :: Levity) (a :: GC l). MutableArray# s a
-> Int# -> State# s -> (# State# s, a #)

etc.

Only a couple of our existing primitives _can't_ generalize this way. The
one that leaps to mind is atomicModifyMutVar, which would need to stay
constrained to only work on arguments in *, because of the way it operates.

With that we can still talk about

MutableArray# s Int

but now we can also talk about:

MutableArray# s (MutableArray# s Int)

without the layer of indirection through a box in * and without an
explosion of primops. The same newFoo, readFoo, writeFoo machinery works
for both kinds.

The struct machinery doesn't get to take advantage of this, but it would
let us clean house elsewhere in Prim and drastically improve the range of
applicability of the existing primitives with nothing more than a small
change to the levity machinery.

I'm not attached to any of the names above, I coined them just to give us a
concrete thing to talk about.

Here I'm only proposing we extend machinery in GHC.Prim this way, but an
interesting 'now that the barn door is open' question is to consider that
our existing Haskell data types often admit a similar form of parametricity
and nothing in principle prevents this from working for Maybe or [] and
once you permit inference to fire across all of GC l then it seems to me
that you'd start to get those same capabilities there as well when
LevityPolymorphism was turned on.

-Edward

On Mon, Sep 7, 2015 at 5:56 PM, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> This could make the menagerie of ways to pack
> {Small}{Mutable}Array{Array}# references into a
> {Small}{Mutable}Array{Array}#' actually typecheck soundly, reducing the
> need for folks to descend into the use of the more evil structure
> primitives we're talking about, and letting us keep a few more principles
> around us.
>
>
>
> I’m lost. Can you give some concrete examples that illustrate how levity
> polymorphism will help us?
>
>
> Simon
>
>
>
> *From:* Edward Kmett [mailto:ekm...@gmail.com]
> *Sent:* 07 September 2015 21:17
> *To:* Simon Peyton Jones
> *Cc:* Ryan Newton; Johan Tibell; Simon Marlow; Manuel M T Chakravarty;
> Chao-Hong Chen; ghc-devs; Ryan Scott; Ryan Yates
> *Subject:* Re: ArrayArrays
>
>
>
> I had a brief discussion with Richard during the Haskell Symposium about
> how we might be able to let parametricity help a bit in reducing the space
> of necessarily primops to a slightly more manageable level.
>
>
>
> Notably, it'd be interesting to explore the ability to al

Re: ArrayArrays

2015-09-07 Thread Edward Kmett
I volunteered to write something up with the caveat that it would take me a
while after the conference ended to get time to do so.

I'll see what I can do.

-Edward

On Mon, Sep 7, 2015 at 9:59 AM, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> It was fun to meet and discuss this.
>
>
>
> Did someone volunteer to write a wiki page that describes the proposed
> design?  And, I earnestly hope, also describes the menagerie of currently
> available array types and primops so that users can have some chance of
> picking the right one?!
>
>
>
> Thanks
>
>
>
> Simon
>
>
>
> *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Ryan
> Newton
> *Sent:* 31 August 2015 23:11
> *To:* Edward Kmett; Johan Tibell
> *Cc:* Simon Marlow; Manuel M T Chakravarty; Chao-Hong Chen; ghc-devs;
> Ryan Scott; Ryan Yates
> *Subject:* Re: ArrayArrays
>
>
>
> Dear Edward, Ryan Yates, and other interested parties --
>
>
>
> So when should we meet up about this?
>
>
>
> May I propose the Tues afternoon break for everyone at ICFP who is
> interested in this topic?  We can meet out in the coffee area and
> congregate around Edward Kmett, who is tall and should be easy to find ;-).
>
>
>
> I think Ryan is going to show us how to use his new primops for combined
> array + other fields in one heap object?
>
>
>
> On Sat, Aug 29, 2015 at 9:24 PM Edward Kmett <ekm...@gmail.com> wrote:
>
> Without a custom primitive it doesn't help much there, you have to store
> the indirection to the mask.
>
>
>
> With a custom primitive it should cut the on heap root-to-leaf path of
> everything in the HAMT in half. A shorter HashMap was actually one of the
> motivating factors for me doing this. It is rather astoundingly difficult
> to beat the performance of HashMap, so I had to start cheating pretty
> badly. ;)
>
>
>
> -Edward
>
>
>
> On Sat, Aug 29, 2015 at 5:45 PM, Johan Tibell <johan.tib...@gmail.com>
> wrote:
>
> I'd also be interested to chat at ICFP to see if I can use this for my
> HAMT implementation.
>
>
>
> On Sat, Aug 29, 2015 at 3:07 PM, Edward Kmett <ekm...@gmail.com> wrote:
>
> Sounds good to me. Right now I'm just hacking up composable accessors for
> "typed slots" in a fairly lens-like fashion, and treating the set of slots
> I define and the 'new' function I build for the data type as its API, and
> build atop that. This could eventually graduate to template-haskell, but
> I'm not entirely satisfied with the solution I have. I currently
> distinguish between what I'm calling "slots" (things that point directly to
> another SmallMutableArrayArray# sans wrapper) and "fields" which point
> directly to the usual Haskell data types because unifying the two notions
> meant that I couldn't lift some coercions out "far enough" to make them
> vanish.
>
>
>
> I'll be happy to run through my current working set of issues in person
> and -- as things get nailed down further -- in a longer lived medium than
> in personal conversations. ;)
>
>
>
> -Edward
>
>
>
> On Sat, Aug 29, 2015 at 7:59 AM, Ryan Newton <rrnew...@gmail.com> wrote:
>
> I'd also love to meet up at ICFP and discuss this.  I think the array
> primops plus a TH layer that lets (ab)use them many times without too much
> marginal cost sounds great.  And I'd like to learn how we could be either
> early users of, or help with, this infrastructure.
>
>
>
> CC'ing in Ryan Scot and Omer Agacan who may also be interested in dropping
> in on such discussions @ICFP, and Chao-Hong Chen, a Ph.D. student who is
> currently working on concurrent data structures in Haskell, but will not be
> at ICFP.
>
>
>
>
>
> On Fri, Aug 28, 2015 at 7:47 PM, Ryan Yates <fryguy...@gmail.com> wrote:
>
> I completely agree.  I would love to spend some time during ICFP and
> friends talking about what it could look like.  My small array for STM
> changes for the RTS can be seen here [1].  It is on a branch somewhere
> between 7.8 and 7.10 and includes irrelevant STM bits and some
> confusing naming choices (sorry), but should cover all the details
> needed to implement it for a non-STM context.  The biggest surprise
> for me was following small array too closely and having a word/byte
> offset miss-match [2].
>
> [1]:
> https://github.com/fryguybob/ghc/compare/ghc-htm-bloom...fryguybob:ghc-htm-mut
> [2]: https://ghc.haskell.org/trac/ghc/ticket/10413
>
> Ryan
>
>
> On Fri, Aug 28, 2015 at 10:09 PM, Edward Kmett <ekm...@gmail.com> wrote:
> > I'd love to have that last 10%, but its a lot of work to get there an

Re: ArrayArrays

2015-09-07 Thread Edward Kmett
I had a brief discussion with Richard during the Haskell Symposium about
how we might be able to let parametricity help a bit in reducing the space
of necessarily primops to a slightly more manageable level.

Notably, it'd be interesting to explore the ability to allow parametricity
over the portion of # that is just a gcptr.

We could do this if the levity polymorphism machinery was tweaked a bit.
You could envision the ability to abstract over things in both * and the
subset of # that are represented by a gcptr, then modifying the existing
array primitives to be parametric in that choice of levity for their
argument so long as it was of a "heap object" levity.

This could make the menagerie of ways to pack {Small}{Mutable}Array{Array}#
references into a {Small}{Mutable}Array{Array}#' actually typecheck
soundly, reducing the need for folks to descend into the use of the more
evil structure primitives we're talking about, and letting us keep a few
more principles around us.

Then in the cases like `atomicModifyMutVar#` where it needs to actually be
in * rather than just a gcptr, due to the constructed field selectors it
introduces on the heap then we could keep the existing less polymorphic
type.

-Edward

On Mon, Sep 7, 2015 at 9:59 AM, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> It was fun to meet and discuss this.
>
>
>
> Did someone volunteer to write a wiki page that describes the proposed
> design?  And, I earnestly hope, also describes the menagerie of currently
> available array types and primops so that users can have some chance of
> picking the right one?!
>
>
>
> Thanks
>
>
>
> Simon
>
>
>
> *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Ryan
> Newton
> *Sent:* 31 August 2015 23:11
> *To:* Edward Kmett; Johan Tibell
> *Cc:* Simon Marlow; Manuel M T Chakravarty; Chao-Hong Chen; ghc-devs;
> Ryan Scott; Ryan Yates
> *Subject:* Re: ArrayArrays
>
>
>
> Dear Edward, Ryan Yates, and other interested parties --
>
>
>
> So when should we meet up about this?
>
>
>
> May I propose the Tues afternoon break for everyone at ICFP who is
> interested in this topic?  We can meet out in the coffee area and
> congregate around Edward Kmett, who is tall and should be easy to find ;-).
>
>
>
> I think Ryan is going to show us how to use his new primops for combined
> array + other fields in one heap object?
>
>
>
> On Sat, Aug 29, 2015 at 9:24 PM Edward Kmett <ekm...@gmail.com> wrote:
>
> Without a custom primitive it doesn't help much there, you have to store
> the indirection to the mask.
>
>
>
> With a custom primitive it should cut the on heap root-to-leaf path of
> everything in the HAMT in half. A shorter HashMap was actually one of the
> motivating factors for me doing this. It is rather astoundingly difficult
> to beat the performance of HashMap, so I had to start cheating pretty
> badly. ;)
>
>
>
> -Edward
>
>
>
> On Sat, Aug 29, 2015 at 5:45 PM, Johan Tibell <johan.tib...@gmail.com>
> wrote:
>
> I'd also be interested to chat at ICFP to see if I can use this for my
> HAMT implementation.
>
>
>
> On Sat, Aug 29, 2015 at 3:07 PM, Edward Kmett <ekm...@gmail.com> wrote:
>
> Sounds good to me. Right now I'm just hacking up composable accessors for
> "typed slots" in a fairly lens-like fashion, and treating the set of slots
> I define and the 'new' function I build for the data type as its API, and
> build atop that. This could eventually graduate to template-haskell, but
> I'm not entirely satisfied with the solution I have. I currently
> distinguish between what I'm calling "slots" (things that point directly to
> another SmallMutableArrayArray# sans wrapper) and "fields" which point
> directly to the usual Haskell data types because unifying the two notions
> meant that I couldn't lift some coercions out "far enough" to make them
> vanish.
>
>
>
> I'll be happy to run through my current working set of issues in person
> and -- as things get nailed down further -- in a longer lived medium than
> in personal conversations. ;)
>
>
>
> -Edward
>
>
>
> On Sat, Aug 29, 2015 at 7:59 AM, Ryan Newton <rrnew...@gmail.com> wrote:
>
> I'd also love to meet up at ICFP and discuss this.  I think the array
> primops plus a TH layer that lets (ab)use them many times without too much
> marginal cost sounds great.  And I'd like to learn how we could be either
> early users of, or help with, this infrastructure.
>
>
>
> CC'ing in Ryan Scot and Omer Agacan who may also be interested in dropping
> in on such discussions @ICFP, and Chao-Hong Chen, a Ph.D. student who is
> currently 

Re: ArrayArrays

2015-09-07 Thread Edward Kmett
Indeed. I can CAS today with appropriately coerced primitives.

-Edward

On Mon, Sep 7, 2015 at 4:27 PM, Ryan Newton <rrnew...@gmail.com> wrote:

> Ah, incidentally that introduces an interesting difference between
> atomicModify and CAS.  CAS should be able to work on mutable locations in
> that subset of # that are represented by a gcptr, whereas Edward pointed
> out that atomicModify cannot.
>
> (Indeed, to use lock-free algorithms with these new unboxed mutable
> structures we'll need CAS on the slots.)
>
> On Mon, Sep 7, 2015 at 4:16 PM, Edward Kmett <ekm...@gmail.com> wrote:
>
>> I had a brief discussion with Richard during the Haskell Symposium about
>> how we might be able to let parametricity help a bit in reducing the space
>> of necessarily primops to a slightly more manageable level.
>>
>> Notably, it'd be interesting to explore the ability to allow
>> parametricity over the portion of # that is just a gcptr.
>>
>> We could do this if the levity polymorphism machinery was tweaked a bit.
>> You could envision the ability to abstract over things in both * and the
>> subset of # that are represented by a gcptr, then modifying the existing
>> array primitives to be parametric in that choice of levity for their
>> argument so long as it was of a "heap object" levity.
>>
>> This could make the menagerie of ways to pack
>> {Small}{Mutable}Array{Array}# references into a
>> {Small}{Mutable}Array{Array}#' actually typecheck soundly, reducing the
>> need for folks to descend into the use of the more evil structure
>> primitives we're talking about, and letting us keep a few more principles
>> around us.
>>
>> Then in the cases like `atomicModifyMutVar#` where it needs to actually
>> be in * rather than just a gcptr, due to the constructed field selectors it
>> introduces on the heap then we could keep the existing less polymorphic
>> type.
>>
>> -Edward
>>
>> On Mon, Sep 7, 2015 at 9:59 AM, Simon Peyton Jones <simo...@microsoft.com
>> > wrote:
>>
>>> It was fun to meet and discuss this.
>>>
>>>
>>>
>>> Did someone volunteer to write a wiki page that describes the proposed
>>> design?  And, I earnestly hope, also describes the menagerie of currently
>>> available array types and primops so that users can have some chance of
>>> picking the right one?!
>>>
>>>
>>>
>>> Thanks
>>>
>>>
>>>
>>> Simon
>>>
>>>
>>>
>>> *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Ryan
>>> Newton
>>> *Sent:* 31 August 2015 23:11
>>> *To:* Edward Kmett; Johan Tibell
>>> *Cc:* Simon Marlow; Manuel M T Chakravarty; Chao-Hong Chen; ghc-devs;
>>> Ryan Scott; Ryan Yates
>>> *Subject:* Re: ArrayArrays
>>>
>>>
>>>
>>> Dear Edward, Ryan Yates, and other interested parties --
>>>
>>>
>>>
>>> So when should we meet up about this?
>>>
>>>
>>>
>>> May I propose the Tues afternoon break for everyone at ICFP who is
>>> interested in this topic?  We can meet out in the coffee area and
>>> congregate around Edward Kmett, who is tall and should be easy to find ;-).
>>>
>>>
>>>
>>> I think Ryan is going to show us how to use his new primops for combined
>>> array + other fields in one heap object?
>>>
>>>
>>>
>>> On Sat, Aug 29, 2015 at 9:24 PM Edward Kmett <ekm...@gmail.com> wrote:
>>>
>>> Without a custom primitive it doesn't help much there, you have to store
>>> the indirection to the mask.
>>>
>>>
>>>
>>> With a custom primitive it should cut the on heap root-to-leaf path of
>>> everything in the HAMT in half. A shorter HashMap was actually one of the
>>> motivating factors for me doing this. It is rather astoundingly difficult
>>> to beat the performance of HashMap, so I had to start cheating pretty
>>> badly. ;)
>>>
>>>
>>>
>>> -Edward
>>>
>>>
>>>
>>> On Sat, Aug 29, 2015 at 5:45 PM, Johan Tibell <johan.tib...@gmail.com>
>>> wrote:
>>>
>>> I'd also be interested to chat at ICFP to see if I can use this for my
>>> HAMT implementation.
>>>
>>>
>>>
>>> On Sat, Aug 29, 2015 at 3:07 PM, Edward Kmett <ekm...@gmail.com> wrote:
>>>
>>> Sounds good to me. Right now I'm just hackin

Re: ArrayArrays

2015-08-28 Thread Edward Kmett
I'd love to have that last 10%, but its a lot of work to get there and more
importantly I don't know quite what it should look like.

On the other hand, I do have a pretty good idea of how the primitives above
could be banged out and tested in a long evening, well in time for 7.12.
And as noted earlier, those remain useful even if a nicer typed version
with an extra level of indirection to the sizes is built up after.

The rest sounds like a good graduate student project for someone who has
graduate students lying around. Maybe somebody at Indiana University who
has an interest in type theory and parallelism can find us one. =)

-Edward

On Fri, Aug 28, 2015 at 8:48 PM, Ryan Yates fryguy...@gmail.com wrote:

 I think from my perspective, the motivation for getting the type
 checker involved is primarily bringing this to the level where users
 could be expected to build these structures.  it is reasonable to
 think that there are people who want to use STM (a context with
 mutation already) to implement a straight forward data structure that
 avoids extra indirection penalty.  There should be some places where
 knowing that things are field accesses rather then array indexing
 could be helpful, but I think GHC is good right now about handling
 constant offsets.  In my code I don't do any bounds checking as I know
 I will only be accessing my arrays with constant indexes.  I make
 wrappers for each field access and leave all the unsafe stuff in
 there.  When things go wrong though, the compiler is no help.  Maybe
 template Haskell that generates the appropriate wrappers is the right
 direction to go.
 There is another benefit for me when working with these as arrays in
 that it is quite simple and direct (given the hoops already jumped
 through) to play with alignment.  I can ensure two pointers are never
 on the same cache-line by just spacing things out in the array.

 On Fri, Aug 28, 2015 at 7:33 PM, Edward Kmett ekm...@gmail.com wrote:
  They just segfault at this level. ;)
 
  Sent from my iPhone
 
  On Aug 28, 2015, at 7:25 PM, Ryan Newton rrnew...@gmail.com wrote:
 
  You presumably also save a bounds check on reads by hard-coding the
 sizes?
 
  On Fri, Aug 28, 2015 at 3:39 PM, Edward Kmett ekm...@gmail.com wrote:
 
  Also there are 4 different things here, basically depending on two
  independent questions:
 
  a.) if you want to shove the sizes into the info table, and
  b.) if you want cardmarking.
 
  Versions with/without cardmarking for different sizes can be done pretty
  easily, but as noted, the infotable variants are pretty invasive.
 
  -Edward
 
  On Fri, Aug 28, 2015 at 6:36 PM, Edward Kmett ekm...@gmail.com wrote:
 
  Well, on the plus side you'd save 16 bytes per object, which adds up if
  they were small enough and there are enough of them. You get a bit
 better
  locality of reference in terms of what fits in the first cache line of
 them.
 
  -Edward
 
  On Fri, Aug 28, 2015 at 6:14 PM, Ryan Newton rrnew...@gmail.com
 wrote:
 
  Yes. And for the short term I can imagine places we will settle with
  arrays even if it means tracking lengths unnecessarily and
 unsafeCoercing
  pointers whose types don't actually match their siblings.
 
  Is there anything to recommend the hacks mentioned for fixed sized
 array
  objects *other* than using them to fake structs? (Much to
 derecommend, as
  you mentioned!)
 
  On Fri, Aug 28, 2015 at 3:07 PM Edward Kmett ekm...@gmail.com
 wrote:
 
  I think both are useful, but the one you suggest requires a lot more
  plumbing and doesn't subsume all of the usecases of the other.
 
  -Edward
 
  On Fri, Aug 28, 2015 at 5:51 PM, Ryan Newton rrnew...@gmail.com
  wrote:
 
  So that primitive is an array like thing (Same pointed type,
 unbounded
  length) with extra payload.
 
  I can see how we can do without structs if we have arrays,
 especially
  with the extra payload at front. But wouldn't the general solution
 for
  structs be one that that allows new user data type defs for # types?
 
 
 
  On Fri, Aug 28, 2015 at 4:43 PM Edward Kmett ekm...@gmail.com
 wrote:
 
  Some form of MutableStruct# with a known number of words and a
 known
  number of pointers is basically what Ryan Yates was suggesting
 above, but
  where the word counts were stored in the objects themselves.
 
  Given that it'd have a couple of words for those counts it'd likely
  want to be something we build in addition to MutVar# rather than a
  replacement.
 
  On the other hand, if we had to fix those numbers and build info
  tables that knew them, and typechecker support, for instance, it'd
 get
  rather invasive.
 
  Also, a number of things that we can do with the 'sized' versions
  above, like working with evil unsized c-style arrays directly
 inline at the
  end of the structure cease to be possible, so it isn't even a pure
 win if we
  did the engineering effort.
 
  I think 90% of the needs I have are covered just by adding the one
  primitive. The last 10% gets pretty

Re: ArrayArrays

2015-08-28 Thread Edward Kmett
I posted a summary article on what this lets you do to

https://www.fpcomplete.com/user/edwardk/unlifted-structures

I can see about making a more proposal/feature-oriented summary for the
Haskell Wiki. It may have to wait until after ICFP though.

-Edward

On Fri, Aug 28, 2015 at 5:42 AM, Simon Peyton Jones simo...@microsoft.com
wrote:

 At the very least I'll take this email and turn it into a short article.

 Yes, please do make it into a wiki page on the GHC Trac, and maybe make a
 ticket for it.


 Thanks



 Simon



 *From:* Edward Kmett [mailto:ekm...@gmail.com]
 *Sent:* 27 August 2015 16:54
 *To:* Simon Peyton Jones
 *Cc:* Manuel M T Chakravarty; Simon Marlow; ghc-devs
 *Subject:* Re: ArrayArrays



 An ArrayArray# is just an Array# with a modified invariant. It points
 directly to other unlifted ArrayArray#'s or ByteArray#'s.



 While those live in #, they are garbage collected objects, so this all
 lives on the heap.



 They were added to make some of the DPH stuff fast when it has to deal
 with nested arrays.



 I'm currently abusing them as a placeholder for a better thing.



 The Problem

 -



 Consider the scenario where you write a classic doubly-linked list in
 Haskell.



 data DLL = DLL (IORef (Maybe DLL) (IORef (Maybe DLL)



 Chasing from one DLL to the next requires following 3 pointers on the heap.



 DLL ~ IORef (Maybe DLL) ~ MutVar# RealWorld (Maybe DLL) ~ Maybe DLL ~
 DLL



 That is 3 levels of indirection.



 We can trim one by simply unpacking the IORef with -funbox-strict-fields
 or UNPACK



 We can trim another by adding a 'Nil' constructor for DLL and worsening
 our representation.



 data DLL = DLL !(IORef DLL) !(IORef DLL) | Nil



 but now we're still stuck with a level of indirection



 DLL ~ MutVar# RealWorld DLL ~ DLL



 This means that every operation we perform on this structure will be about
 half of the speed of an implementation in most other languages assuming
 we're memory bound on loading things into cache!



 Making Progress

 --



 I have been working on a number of data structures where the indirection
 of going from something in * out to an object in # which contains the real
 pointer to my target and coming back effectively doubles my runtime.



 We go out to the MutVar# because we are allowed to put the MutVar# onto
 the mutable list when we dirty it. There is a well defined write-barrier.



 I could change out the representation to use



 data DLL = DLL (MutableArray# RealWorld DLL) | Nil



 I can just store two pointers in the MutableArray# every time, but this
 doesn't help _much_ directly. It has reduced the amount of distinct
 addresses in memory I touch on a walk of the DLL from 3 per object to 2.



 I still have to go out to the heap from my DLL and get to the array object
 and then chase it to the next DLL and chase that to the next array. I do
 get my two pointers together in memory though. I'm paying for a card
 marking table as well, which I don't particularly need with just two
 pointers, but we can shed that with the SmallMutableArray# machinery
 added back in 7.10, which is just the old array code a a new data type,
 which can speed things up a bit when you don't have very big arrays:



 data DLL = DLL (SmallMutableArray# RealWorld DLL) | Nil



 But what if I wanted my object itself to live in # and have two mutable
 fields and be able to share the sme write barrier?



 An ArrayArray# points directly to other unlifted array types. What if we
 have one # - * wrapper on the outside to deal with the impedence mismatch
 between the imperative world and Haskell, and then just let the
 ArrayArray#'s hold other arrayarrays.



 data DLL = DLL (MutableArrayArray# RealWorld)



 now I need to make up a new Nil, which I can just make be a special
 MutableArrayArray# I allocate on program startup. I can even abuse pattern
 synonyms. Alternately I can exploit the internals further to make this
 cheaper.



 Then I can use the readMutableArrayArray# and writeMutableArrayArray#
 calls to directly access the preceding and next entry in the linked list.



 So now we have one DLL wrapper which just 'bootstraps me' into a strict
 world, and everything there lives in #.



 next :: DLL - IO DLL

 next (DLL m) = IO $ \s - case readMutableArrayArray# s of

(# s', n #) - (# s', DLL n #)



 It turns out GHC is quite happy to optimize all of that code to keep
 things unboxed. The 'DLL' wrappers get removed pretty easily when they are
 known strict and you chain operations of this sort!



 Cleaning it Up

 --



 Now I have one outermost indirection pointing to an array that points
 directly to other arrays.



 I'm stuck paying for a card marking table per object, but I can fix that
 by duplicating the code for MutableArrayArray# and using a
 SmallMutableArray#. I can hack up primops that let me store a mixture of
 SmallMutableArray# fields and normal ones in the data structure

Re: ArrayArrays

2015-08-28 Thread Edward Kmett
They just segfault at this level. ;)

Sent from my iPhone

 On Aug 28, 2015, at 7:25 PM, Ryan Newton rrnew...@gmail.com wrote:
 
 You presumably also save a bounds check on reads by hard-coding the sizes?
 
 On Fri, Aug 28, 2015 at 3:39 PM, Edward Kmett ekm...@gmail.com wrote:
 Also there are 4 different things here, basically depending on two 
 independent questions: 
 
 a.) if you want to shove the sizes into the info table, and 
 b.) if you want cardmarking.
 
 Versions with/without cardmarking for different sizes can be done pretty 
 easily, but as noted, the infotable variants are pretty invasive.
 
 -Edward
 
 On Fri, Aug 28, 2015 at 6:36 PM, Edward Kmett ekm...@gmail.com wrote:
 Well, on the plus side you'd save 16 bytes per object, which adds up if 
 they were small enough and there are enough of them. You get a bit better 
 locality of reference in terms of what fits in the first cache line of them.
 
 -Edward
 
 On Fri, Aug 28, 2015 at 6:14 PM, Ryan Newton rrnew...@gmail.com wrote:
 Yes. And for the short term I can imagine places we will settle with 
 arrays even if it means tracking lengths unnecessarily and unsafeCoercing 
 pointers whose types don't actually match their siblings. 
 
 Is there anything to recommend the hacks mentioned for fixed sized array 
 objects *other* than using them to fake structs? (Much to derecommend, as 
 you mentioned!)
 
 On Fri, Aug 28, 2015 at 3:07 PM Edward Kmett ekm...@gmail.com wrote:
 I think both are useful, but the one you suggest requires a lot more 
 plumbing and doesn't subsume all of the usecases of the other.
 
 -Edward
 
 On Fri, Aug 28, 2015 at 5:51 PM, Ryan Newton rrnew...@gmail.com wrote:
 So that primitive is an array like thing (Same pointed type, unbounded 
 length) with extra payload. 
 
 I can see how we can do without structs if we have arrays, especially 
 with the extra payload at front. But wouldn't the general solution for 
 structs be one that that allows new user data type defs for # types?
 
 
 
 On Fri, Aug 28, 2015 at 4:43 PM Edward Kmett ekm...@gmail.com wrote:
 Some form of MutableStruct# with a known number of words and a known 
 number of pointers is basically what Ryan Yates was suggesting above, 
 but where the word counts were stored in the objects themselves.
 
 Given that it'd have a couple of words for those counts it'd likely 
 want to be something we build in addition to MutVar# rather than a 
 replacement.
 
 On the other hand, if we had to fix those numbers and build info tables 
 that knew them, and typechecker support, for instance, it'd get rather 
 invasive.
 
 Also, a number of things that we can do with the 'sized' versions 
 above, like working with evil unsized c-style arrays directly inline at 
 the end of the structure cease to be possible, so it isn't even a pure 
 win if we did the engineering effort.
 
 I think 90% of the needs I have are covered just by adding the one 
 primitive. The last 10% gets pretty invasive.
 
 -Edward
 
 On Fri, Aug 28, 2015 at 5:30 PM, Ryan Newton rrnew...@gmail.com 
 wrote:
 I like the possibility of a general solution for mutable structs (like 
 Ed said), and I'm trying to fully understand why it's hard. 
 
 So, we can't unpack MutVar into constructors because of object 
 identity problems. But what about directly supporting an extensible 
 set of unlifted MutStruct# objects, generalizing (and even replacing) 
 MutVar#? That may be too much work, but is it problematic otherwise?
 
 Needless to say, this is also critical if we ever want best in class 
 lockfree mutable structures, just like their Stm and sequential 
 counterparts. 
 
 On Fri, Aug 28, 2015 at 4:43 AM Simon Peyton Jones 
 simo...@microsoft.com wrote:
 At the very least I'll take this email and turn it into a short 
 article.
 Yes, please do make it into a wiki page on the GHC Trac, and maybe 
 make a ticket for it.
 
 
 Thanks
 
  
 
 Simon
 
  
 
 From: Edward Kmett [mailto:ekm...@gmail.com] 
 Sent: 27 August 2015 16:54
 To: Simon Peyton Jones
 Cc: Manuel M T Chakravarty; Simon Marlow; ghc-devs
 Subject: Re: ArrayArrays
 
  
 
 An ArrayArray# is just an Array# with a modified invariant. It points 
 directly to other unlifted ArrayArray#'s or ByteArray#'s.
  
 While those live in #, they are garbage collected objects, so this 
 all lives on the heap.
  
 They were added to make some of the DPH stuff fast when it has to 
 deal with nested arrays.
  
 I'm currently abusing them as a placeholder for a better thing.
  
 The Problem
 -
  
 Consider the scenario where you write a classic doubly-linked list in 
 Haskell.
  
 data DLL = DLL (IORef (Maybe DLL) (IORef (Maybe DLL)
  
 Chasing from one DLL to the next requires following 3 pointers on the 
 heap.
  
 DLL ~ IORef (Maybe DLL) ~ MutVar# RealWorld (Maybe DLL) ~ Maybe 
 DLL ~ DLL
  
 That is 3 levels of indirection.
  
 We can trim one by simply unpacking the IORef with 
 -funbox-strict-fields or UNPACK
  
 We can trim another by adding a 'Nil

Re: ArrayArrays

2015-08-28 Thread Edward Kmett
I think both are useful, but the one you suggest requires a lot more
plumbing and doesn't subsume all of the usecases of the other.

-Edward

On Fri, Aug 28, 2015 at 5:51 PM, Ryan Newton rrnew...@gmail.com wrote:

 So that primitive is an array like thing (Same pointed type, unbounded
 length) with extra payload.

 I can see how we can do without structs if we have arrays, especially with
 the extra payload at front. But wouldn't the general solution for structs
 be one that that allows new user data type defs for # types?



 On Fri, Aug 28, 2015 at 4:43 PM Edward Kmett ekm...@gmail.com wrote:

 Some form of MutableStruct# with a known number of words and a known
 number of pointers is basically what Ryan Yates was suggesting above, but
 where the word counts were stored in the objects themselves.

 Given that it'd have a couple of words for those counts it'd likely want
 to be something we build in addition to MutVar# rather than a replacement.

 On the other hand, if we had to fix those numbers and build info tables
 that knew them, and typechecker support, for instance, it'd get rather
 invasive.

 Also, a number of things that we can do with the 'sized' versions above,
 like working with evil unsized c-style arrays directly inline at the end of
 the structure cease to be possible, so it isn't even a pure win if we did
 the engineering effort.

 I think 90% of the needs I have are covered just by adding the one
 primitive. The last 10% gets pretty invasive.

 -Edward

 On Fri, Aug 28, 2015 at 5:30 PM, Ryan Newton rrnew...@gmail.com wrote:

 I like the possibility of a general solution for mutable structs (like
 Ed said), and I'm trying to fully understand why it's hard.

 So, we can't unpack MutVar into constructors because of object identity
 problems. But what about directly supporting an extensible set of unlifted
 MutStruct# objects, generalizing (and even replacing) MutVar#? That may be
 too much work, but is it problematic otherwise?

 Needless to say, this is also critical if we ever want best in class
 lockfree mutable structures, just like their Stm and sequential
 counterparts.

 On Fri, Aug 28, 2015 at 4:43 AM Simon Peyton Jones 
 simo...@microsoft.com wrote:

 At the very least I'll take this email and turn it into a short article.

 Yes, please do make it into a wiki page on the GHC Trac, and maybe make
 a ticket for it.


 Thanks



 Simon



 *From:* Edward Kmett [mailto:ekm...@gmail.com]
 *Sent:* 27 August 2015 16:54
 *To:* Simon Peyton Jones
 *Cc:* Manuel M T Chakravarty; Simon Marlow; ghc-devs
 *Subject:* Re: ArrayArrays



 An ArrayArray# is just an Array# with a modified invariant. It points
 directly to other unlifted ArrayArray#'s or ByteArray#'s.



 While those live in #, they are garbage collected objects, so this all
 lives on the heap.



 They were added to make some of the DPH stuff fast when it has to deal
 with nested arrays.



 I'm currently abusing them as a placeholder for a better thing.



 The Problem

 -



 Consider the scenario where you write a classic doubly-linked list in
 Haskell.



 data DLL = DLL (IORef (Maybe DLL) (IORef (Maybe DLL)



 Chasing from one DLL to the next requires following 3 pointers on the
 heap.



 DLL ~ IORef (Maybe DLL) ~ MutVar# RealWorld (Maybe DLL) ~ Maybe DLL
 ~ DLL



 That is 3 levels of indirection.



 We can trim one by simply unpacking the IORef with
 -funbox-strict-fields or UNPACK



 We can trim another by adding a 'Nil' constructor for DLL and worsening
 our representation.



 data DLL = DLL !(IORef DLL) !(IORef DLL) | Nil



 but now we're still stuck with a level of indirection



 DLL ~ MutVar# RealWorld DLL ~ DLL



 This means that every operation we perform on this structure will be
 about half of the speed of an implementation in most other languages
 assuming we're memory bound on loading things into cache!



 Making Progress

 --



 I have been working on a number of data structures where the
 indirection of going from something in * out to an object in # which
 contains the real pointer to my target and coming back effectively doubles
 my runtime.



 We go out to the MutVar# because we are allowed to put the MutVar# onto
 the mutable list when we dirty it. There is a well defined write-barrier.



 I could change out the representation to use



 data DLL = DLL (MutableArray# RealWorld DLL) | Nil



 I can just store two pointers in the MutableArray# every time, but this
 doesn't help _much_ directly. It has reduced the amount of distinct
 addresses in memory I touch on a walk of the DLL from 3 per object to 2.



 I still have to go out to the heap from my DLL and get to the array
 object and then chase it to the next DLL and chase that to the next array.
 I do get my two pointers together in memory though. I'm paying for a card
 marking table as well, which I don't particularly need with just two
 pointers, but we can shed that with the SmallMutableArray# machinery

Re: ArrayArrays

2015-08-28 Thread Edward Kmett
Some form of MutableStruct# with a known number of words and a known number
of pointers is basically what Ryan Yates was suggesting above, but where
the word counts were stored in the objects themselves.

Given that it'd have a couple of words for those counts it'd likely want to
be something we build in addition to MutVar# rather than a replacement.

On the other hand, if we had to fix those numbers and build info tables
that knew them, and typechecker support, for instance, it'd get rather
invasive.

Also, a number of things that we can do with the 'sized' versions above,
like working with evil unsized c-style arrays directly inline at the end of
the structure cease to be possible, so it isn't even a pure win if we did
the engineering effort.

I think 90% of the needs I have are covered just by adding the one
primitive. The last 10% gets pretty invasive.

-Edward

On Fri, Aug 28, 2015 at 5:30 PM, Ryan Newton rrnew...@gmail.com wrote:

 I like the possibility of a general solution for mutable structs (like Ed
 said), and I'm trying to fully understand why it's hard.

 So, we can't unpack MutVar into constructors because of object identity
 problems. But what about directly supporting an extensible set of unlifted
 MutStruct# objects, generalizing (and even replacing) MutVar#? That may be
 too much work, but is it problematic otherwise?

 Needless to say, this is also critical if we ever want best in class
 lockfree mutable structures, just like their Stm and sequential
 counterparts.

 On Fri, Aug 28, 2015 at 4:43 AM Simon Peyton Jones simo...@microsoft.com
 wrote:

 At the very least I'll take this email and turn it into a short article.

 Yes, please do make it into a wiki page on the GHC Trac, and maybe make a
 ticket for it.


 Thanks



 Simon



 *From:* Edward Kmett [mailto:ekm...@gmail.com]
 *Sent:* 27 August 2015 16:54
 *To:* Simon Peyton Jones
 *Cc:* Manuel M T Chakravarty; Simon Marlow; ghc-devs
 *Subject:* Re: ArrayArrays



 An ArrayArray# is just an Array# with a modified invariant. It points
 directly to other unlifted ArrayArray#'s or ByteArray#'s.



 While those live in #, they are garbage collected objects, so this all
 lives on the heap.



 They were added to make some of the DPH stuff fast when it has to deal
 with nested arrays.



 I'm currently abusing them as a placeholder for a better thing.



 The Problem

 -



 Consider the scenario where you write a classic doubly-linked list in
 Haskell.



 data DLL = DLL (IORef (Maybe DLL) (IORef (Maybe DLL)



 Chasing from one DLL to the next requires following 3 pointers on the
 heap.



 DLL ~ IORef (Maybe DLL) ~ MutVar# RealWorld (Maybe DLL) ~ Maybe DLL ~
 DLL



 That is 3 levels of indirection.



 We can trim one by simply unpacking the IORef with -funbox-strict-fields
 or UNPACK



 We can trim another by adding a 'Nil' constructor for DLL and worsening
 our representation.



 data DLL = DLL !(IORef DLL) !(IORef DLL) | Nil



 but now we're still stuck with a level of indirection



 DLL ~ MutVar# RealWorld DLL ~ DLL



 This means that every operation we perform on this structure will be
 about half of the speed of an implementation in most other languages
 assuming we're memory bound on loading things into cache!



 Making Progress

 --



 I have been working on a number of data structures where the indirection
 of going from something in * out to an object in # which contains the real
 pointer to my target and coming back effectively doubles my runtime.



 We go out to the MutVar# because we are allowed to put the MutVar# onto
 the mutable list when we dirty it. There is a well defined write-barrier.



 I could change out the representation to use



 data DLL = DLL (MutableArray# RealWorld DLL) | Nil



 I can just store two pointers in the MutableArray# every time, but this
 doesn't help _much_ directly. It has reduced the amount of distinct
 addresses in memory I touch on a walk of the DLL from 3 per object to 2.



 I still have to go out to the heap from my DLL and get to the array
 object and then chase it to the next DLL and chase that to the next array.
 I do get my two pointers together in memory though. I'm paying for a card
 marking table as well, which I don't particularly need with just two
 pointers, but we can shed that with the SmallMutableArray# machinery
 added back in 7.10, which is just the old array code a a new data type,
 which can speed things up a bit when you don't have very big arrays:



 data DLL = DLL (SmallMutableArray# RealWorld DLL) | Nil



 But what if I wanted my object itself to live in # and have two mutable
 fields and be able to share the sme write barrier?



 An ArrayArray# points directly to other unlifted array types. What if we
 have one # - * wrapper on the outside to deal with the impedence mismatch
 between the imperative world and Haskell, and then just let the
 ArrayArray#'s hold other arrayarrays.



 data DLL = DLL (MutableArrayArray

Re: ArrayArrays

2015-08-27 Thread Edward Kmett
 objects, one
that could put itself on the mutable list when any of those pointers
changed then I could shed this last factor of two in all circumstances.

Prototype
-

Over the last few days I've put together a small prototype implementation
with a few non-trivial imperative data structures for things like Tarjan's
link-cut trees, the list labeling problem and order-maintenance.

https://github.com/ekmett/structs

Notable bits:

Data.Struct.Internal.LinkCut
https://github.com/ekmett/structs/blob/9ff2818f888aff4789b7a41077a674a10d15e6ee/src/Data/Struct/Internal/LinkCut.hs
provides an implementation of link-cut trees in this style.

Data.Struct.Internal
https://github.com/ekmett/structs/blob/9ff2818f888aff4789b7a41077a674a10d15e6ee/src/Data/Struct/Internal.hs
provides the rather horrifying guts that make it go fast.

Once compiled with -O or -O2, if you look at the core, almost all the
references to the LinkCut or Object data constructor get optimized away,
and we're left with beautiful strict code directly mutating out underlying
representation.

At the very least I'll take this email and turn it into a short article.

-Edward

On Thu, Aug 27, 2015 at 9:00 AM, Simon Peyton Jones simo...@microsoft.com
wrote:

 Just to say that I have no idea what is going on in this thread.  What is
 ArrayArray?  What is the issue in general?  Is there a ticket? Is there a
 wiki page?



 If it’s important, an ab-initio wiki page + ticket would be a good thing.



 Simon



 *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Edward
 Kmett
 *Sent:* 21 August 2015 05:25
 *To:* Manuel M T Chakravarty
 *Cc:* Simon Marlow; ghc-devs
 *Subject:* Re: ArrayArrays



 When (ab)using them for this purpose, SmallArrayArray's would be very
 handy as well.



 Consider right now if I have something like an order-maintenance structure
 I have:



 data Upper s = Upper {-# UNPACK #-} !(MutableByteArray s) {-# UNPACK #-}
 !(MutVar s (Upper s)) {-# UNPACK #-} !(MutVar s (Upper s))



 data Lower s = Lower {-# UNPACK #-} !(MutVar s (Upper s)) {-# UNPACK #-}
 !(MutableByteArray s) {-# UNPACK #-} !(MutVar s (Lower s)) {-# UNPACK #-}
 !(MutVar s (Lower s))



 The former contains, logically, a mutable integer and two pointers, one
 for forward and one for backwards. The latter is basically the same thing
 with a mutable reference up pointing at the structure above.



 On the heap this is an object that points to a structure for the
 bytearray, and points to another structure for each mutvar which each point
 to the other 'Upper' structure. So there is a level of indirection smeared
 over everything.



 So this is a pair of doubly linked lists with an upward link from the
 structure below to the structure above.



 Converted into ArrayArray#s I'd get



 data Upper s = Upper (MutableArrayArray# s)



 w/ the first slot being a pointer to a MutableByteArray#, and the next 2
 slots pointing to the previous and next previous objects, represented just
 as their MutableArrayArray#s. I can use sameMutableArrayArray# on these for
 object identity, which lets me check for the ends of the lists by tying
 things back on themselves.



 and below that



 data Lower s = Lower (MutableArrayArray# s)



 is similar, with an extra MutableArrayArray slot pointing up to an upper
 structure.



 I can then write a handful of combinators for getting out the slots in
 question, while it has gained a level of indirection between the wrapper to
 put it in * and the MutableArrayArray# s in #, that one can be basically
 erased by ghc.



 Unlike before I don't have several separate objects on the heap for each
 thing. I only have 2 now. The MutableArrayArray# for the object itself, and
 the MutableByteArray# that it references to carry around the mutable int.



 The only pain points are



 1.) the aforementioned limitation that currently prevents me from stuffing
 normal boxed data through a SmallArray or Array into an ArrayArray leaving
 me in a little ghetto disconnected from the rest of Haskell,



 and



 2.) the lack of SmallArrayArray's, which could let us avoid the card
 marking overhead. These objects are all small, 3-4 pointers wide. Card
 marking doesn't help.



 Alternately I could just try to do really evil things and convert the
 whole mess to SmallArrays and then figure out how to unsafeCoerce my way to
 glory, stuffing the #'d references to the other arrays directly into the
 SmallArray as slots, removing the limitation  we see here by aping the
 MutableArrayArray# s API, but that gets really really dangerous!



 I'm pretty much willing to sacrifice almost anything on the altar of speed
 here, but I'd like to be able to let the GC move them and collect them
 which rules out simpler Ptr and Addr based solutions.



 -Edward



 On Thu, Aug 20, 2015 at 9:01 PM, Manuel M T Chakravarty 
 c...@cse.unsw.edu.au wrote:

 That’s an interesting idea.

 Manuel

  Edward Kmett ekm...@gmail.com:

 
  Would it be possible to add

Re: ArrayArrays

2015-08-27 Thread Edward Kmett
On Thu, Aug 27, 2015 at 1:24 PM, Edward Z. Yang ezy...@mit.edu wrote:

 It seems to me that we should take a page from OCaml's playbook
 and add support for native mutable fields in objects, because
 this is essentially what a mix of words and pointers is.


That actually doesn't work as well as one might hope.

We currently treat data constructor closures as so much tissue paper around
a present. We tear them open, rip out all their contents, scatter them
throughout our code and then we build a whole new data constructor closure
when we're done, or we just leave them suspended in closures awaiting
someone to demand we finally make a new data constructor.

Half the time we don't even give back the data constructor closure and push
it into update g frames and we just give back the items on the stack.

With the machinery I mentioned above I get a world where every time I
access an object I can know it is evaluated for real, so this means I'm not
stuck 'entering an unknown closure', and getting it to give me back a slab
of memory that we know is a real data constructor that i can bang away on
mutable entries in.

In a world where things in * could hold mutable pointers we have to care a
lot more about object identity in deeply uncomfortable ways.

With what I've implemented I only care about object identity between things
in # that are gcptrs. The garbage collector may move them around, but it
doesn't put in thunks anywhere.

-Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: ArrayArrays

2015-08-21 Thread Edward Kmett
On Fri, Aug 21, 2015 at 9:49 AM, Ryan Yates fryguy...@gmail.com wrote:

 Hi Edward,

 I've been working on removing indirection in STM and I added a heap
 object like SmallArray, but with a mix of words and pointers (as well
 as a header with metadata for STM).  It appears to work well now, but
 it is missing the type information.  All the pointers have the same
 type which works fine for your Upper.  In my case I use it to
 represent a red-black tree node [1].


This would be perfect for my purposes.


 Also all the structures I make are fixed size and it would be nice if
 the compiler could treat that fix size like a constant in code
 generation.


To make the fixed sized thing work without an extra couple of size
parameters in the arguments, you'd want to be able to build an info table
for each generated size. That sounds messy.


 I don't know what the right design is or what would be
 needed, but it seems simple enough to give the right typing
 information to something like this and basically get a mutable struct.
 I'm talking about this work at HIW and really hope to find someone
 interested in extending this expressiveness to let us write something
 that looks clear in Haskell, but gives the heap representation that we
 really need for performance.


I'll be there. Let's talk.


 From the RTS perspective I think there are any obstacles.


FWIW- I was able to get some code put together that let me scribble
unlifted SmallMutableArray#s directly into other SmallMutableArray#s, which
nicely just works as long as you fix up all the fields that are supposed
to be arrays before you ever dare use them.

writeSmallMutableArraySmallArray# :: SmallMutableArray# s Any - Int# -
SmallMutableArray# s Any - State# s - State# s
writeSmallMutableArraySmallArray# m i a s = unsafeCoerce# writeSmallArray#
m i a s
{-# INLINE writeSmallMutableArraySmallArray# #-}

readSmallMutableArraySmallArray# :: SmallMutableArray# s Any - Int# -
State# s - (# State# s, SmallMutableArray# s Any #)
readSmallMutableArraySmallArray# m i s = unsafeCoerce# readSmallArray# m i s
{-# INLINE readSmallMutableArraySmallArray# #-}

With some support for typed 'Field's I can write code now that looks like:
order :: PrimMonad m = Upper (PrimState m) - Int - Order (PrimState m)
- Order (PrimState m) - m (Order (PrimState m))
order p a l r = st $ do
  this - primitive $ \s - case unsafeCoerce# newSmallArray# 4# a s of
(# s', b #) - (# s', Order b #)
  set parent this p
  set next this l
  set prev this r
  return this

and in there basically build my own little strict, mutable, universe and
with some careful monitoring of the core make sure that the little Order
wrappers as the fringes get removed.

Here I'm using one of the slots as a pointer to a boxed Int for testing,
rather than as a pointer to a MutableByteArray that holds the Int.

-Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


ArrayArrays

2015-08-20 Thread Edward Kmett
Would it be possible to add unsafe primops to add Array# and SmallArray#
entries to an ArrayArray#? The fact that the ArrayArray# entries are all
directly unlifted avoiding a level of indirection for the containing
structure is amazing, but I can only currently use it if my leaf level data
can be 100% unboxed and distributed among ByteArray#s. It'd be nice to be
able to have the ability to put SmallArray# a stuff down at the leaves to
hold lifted contents.

I accept fully that if I name the wrong type when I go to access one of the
fields it'll lie to me, but I suppose it'd do that if i tried to use one of
the members that held a nested ArrayArray# as a ByteArray# anyways, so it
isn't like there is a safety story preventing this.

I've been hunting for ways to try to kill the indirection problems I get
with Haskell and mutable structures, and I could shoehorn a number of them
into ArrayArrays if this worked.

Right now I'm stuck paying for 2 or 3 levels of unnecessary indirection
compared to c/java and this could reduce that pain to just 1 level of
unnecessary indirection.

-Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: ArrayArrays

2015-08-20 Thread Edward Kmett
When (ab)using them for this purpose, SmallArrayArray's would be very handy
as well.

Consider right now if I have something like an order-maintenance structure
I have:

data Upper s = Upper {-# UNPACK #-} !(MutableByteArray s) {-# UNPACK #-}
!(MutVar s (Upper s)) {-# UNPACK #-} !(MutVar s (Upper s))

data Lower s = Lower {-# UNPACK #-} !(MutVar s (Upper s)) {-# UNPACK #-}
!(MutableByteArray s) {-# UNPACK #-} !(MutVar s (Lower s)) {-# UNPACK #-}
!(MutVar s (Lower s))

The former contains, logically, a mutable integer and two pointers, one for
forward and one for backwards. The latter is basically the same thing with
a mutable reference up pointing at the structure above.

On the heap this is an object that points to a structure for the bytearray,
and points to another structure for each mutvar which each point to the
other 'Upper' structure. So there is a level of indirection smeared over
everything.

So this is a pair of doubly linked lists with an upward link from the
structure below to the structure above.

Converted into ArrayArray#s I'd get

data Upper s = Upper (MutableArrayArray# s)

w/ the first slot being a pointer to a MutableByteArray#, and the next 2
slots pointing to the previous and next previous objects, represented just
as their MutableArrayArray#s. I can use sameMutableArrayArray# on these for
object identity, which lets me check for the ends of the lists by tying
things back on themselves.

and below that

data Lower s = Lower (MutableArrayArray# s)

is similar, with an extra MutableArrayArray slot pointing up to an upper
structure.

I can then write a handful of combinators for getting out the slots in
question, while it has gained a level of indirection between the wrapper to
put it in * and the MutableArrayArray# s in #, that one can be basically
erased by ghc.

Unlike before I don't have several separate objects on the heap for each
thing. I only have 2 now. The MutableArrayArray# for the object itself, and
the MutableByteArray# that it references to carry around the mutable int.

The only pain points are

1.) the aforementioned limitation that currently prevents me from stuffing
normal boxed data through a SmallArray or Array into an ArrayArray leaving
me in a little ghetto disconnected from the rest of Haskell,

and

2.) the lack of SmallArrayArray's, which could let us avoid the card
marking overhead. These objects are all small, 3-4 pointers wide. Card
marking doesn't help.

Alternately I could just try to do really evil things and convert the whole
mess to SmallArrays and then figure out how to unsafeCoerce my way to
glory, stuffing the #'d references to the other arrays directly into the
SmallArray as slots, removing the limitation  we see here by aping the
MutableArrayArray# s API, but that gets really really dangerous!

I'm pretty much willing to sacrifice almost anything on the altar of speed
here, but I'd like to be able to let the GC move them and collect them
which rules out simpler Ptr and Addr based solutions.

-Edward

On Thu, Aug 20, 2015 at 9:01 PM, Manuel M T Chakravarty 
c...@cse.unsw.edu.au wrote:

 That’s an interesting idea.

 Manuel

  Edward Kmett ekm...@gmail.com:
 
  Would it be possible to add unsafe primops to add Array# and SmallArray#
 entries to an ArrayArray#? The fact that the ArrayArray# entries are all
 directly unlifted avoiding a level of indirection for the containing
 structure is amazing, but I can only currently use it if my leaf level data
 can be 100% unboxed and distributed among ByteArray#s. It'd be nice to be
 able to have the ability to put SmallArray# a stuff down at the leaves to
 hold lifted contents.
 
  I accept fully that if I name the wrong type when I go to access one of
 the fields it'll lie to me, but I suppose it'd do that if i tried to use
 one of the members that held a nested ArrayArray# as a ByteArray# anyways,
 so it isn't like there is a safety story preventing this.
 
  I've been hunting for ways to try to kill the indirection problems I get
 with Haskell and mutable structures, and I could shoehorn a number of them
 into ArrayArrays if this worked.
 
  Right now I'm stuck paying for 2 or 3 levels of unnecessary indirection
 compared to c/java and this could reduce that pain to just 1 level of
 unnecessary indirection.
 
  -Edward
  ___
  ghc-devs mailing list
  ghc-devs@haskell.org
  http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Abstract FilePath Proposal

2015-06-28 Thread Edward Kmett
Worse there are situations where you absolutely _have_ to be able to use
\\?\ encoding of a path on Windows to read, modify or delete files with
impossible names that were created by other means.

e.g. Filenames like AUX, that had traditional roles under DOS cause weird
interactions, or that were created with impossibly long names -- which
can happen in the wild when you move directories around, etc.

I'm weakly in favor of the proposal precisely because it is the first
version of this concept that I've seen that DOESN'T try to get too clever
with regards to adding all sorts of normalization and this proposal seems
to be the simplest move that would enable us to do something correctly in
the future, regardless of what that correct thing winds up being.

-Edward

On Sun, Jun 28, 2015 at 8:09 AM, David Turner dct25-56...@mythic-beasts.com
 wrote:

 Hi,

 I think it'd be more robust to handle normalisation when converting from
 String/Text to FilePath (and combining things with (/) and so on) rather
 than in the underlying representation.

 It's absolutely crucial that you can ask the OS for a filename (which it
 gives you as a sequence of bytes) and then pass that exact same sequence of
 bytes back to the OS without any normalisation or other useful alterations
 having taken place.

 You can do some deeply weird stuff in Windows by starting an absolute path
 with \\?\, including apparently using '.' and '..' as the name of a
 filesystem component:

 Because it turns off automatic expansion of the path string, the \\?\
 prefix also allows the use of .. and . in the path names, which can be
 useful if you are attempting to perform operations on a file with these
 otherwise reserved relative path specifiers as part of the fully qualified
 path.


 (from
 https://msdn.microsoft.com/en-us/library/windows/desktop/aa365247(v=vs.85).aspx
 )

 I don't fancy shaking all the corner cases out of this. An explicit
 'normalise' function seems ok, but baking normalisation into the type
 itself seems bad.

 Cheers,

 David


 On 28 June 2015 at 11:03, Boespflug, Mathieu m...@tweag.io wrote:

 Hi Neil,

 why does the proposal *not* include normalization?

 There are four advantages that I see to making FilePath a datatype:

 1. it makes it possible to implement the correct semantics for some
 systems (including POSIX),
 2. it allows for information hiding, which in turn helps modularity,
 3. the type is distinct from any other type, hence static checks are
 stronger,
 4. it becomes possible to quotient values over some arbitrary set of
 identities that makes sense. i.e. in the case of FilePath, arguably
 foo/bar//baz *is* foo/bar/baz *is* foo//bar/baz for all intents
 and purposes, so it is not useful to distinguish these three ways of
 writing down the same path (and in fact in practice distinguishing
 them leads to subtle bugs). That is, the Eq instance compares
 FilePath's modulo a few laws.

 Do you propose to forego (4)? If so why so?

 If we're going through a deprecation process, could we do so once, by
 getting the notion of path equality we want right the first time?
 Contrary to type indexing FilePath, it seems to me that the design
 space for path identities is much smaller. Essentially, exactly the
 ones here:
 https://hackage.haskell.org/package/filepath-1.1.0.2/docs/System-FilePath-Posix.html#v:normalise
 .

 Best,

 Mathieu


 On 27 June 2015 at 12:12, Neil Mitchell ndmitch...@gmail.com wrote:
  Hi Niklas,
 
  The function writeFile takes a FilePath. We could fork base or tell
 everyone
  to use writeFile2, but in practice everyone will keep using writeFile,
 and
  this String for FilePath. This approach is the only thing we could
 figure
  that made sense.
 
  Henning: we do not propose normalisation on initialisation. For ASCII
  strings fromFilePath . toFilePath will be id. It might also be for
 unicode
  on some/all platforms. Of course, you can write your own FilePath
 creator
  that does normalisation on construction.
 
  Thanks, Neil
 
 
  On Saturday, 27 June 2015, Niklas Larsson metanik...@gmail.com wrote:
 
  Hi!
 
  Instead of trying to minimally patch the existing API and still
 breaking
  loads of code, why not make a new API that doesn't have to compromise
 and
  depreciate the old one?
 
  Niklas
  
  Från: Herbert Valerio Riedel
  Skickat: ‎2015-‎06-‎26 18:09
  Till: librar...@haskell.org; ghc-devs@haskell.org
  Ämne: Abstract FilePath Proposal
 
  -BEGIN PGP SIGNED MESSAGE-
  Hash: SHA1
 
  Hello *,
 
  What?
  =
 
  We (see From:  CC: headers) propose, plain and simple, to turn the
  currently defined type-synonym
 
type FilePath = String
 
  into an abstract/opaque data type instead.
 
  Why/How/When?
  =
 
  For details (including motivation and a suggested transition scheme)
  please consult
 
https://ghc.haskell.org/trac/ghc/wiki/Proposal/AbstractFilePath
 
 
 
  Suggested discussion period: 4 weeks
  -BEGIN PGP 

Re: Handling overflow and division by zero

2015-06-28 Thread Edward Kmett
You should be able to reduce the bit-twiddling a great deal IIRC in the
word case.

SW a + SW b
  | c - a + b, c = min a b = SW c
  | otherwise = throw Overflow

There is a similar trick that escapes me at the moment for the signed case.


On Sun, Jun 28, 2015 at 6:15 PM, Nikita Karetnikov nik...@karetnikov.org
wrote:

 Haskell is often marketed as a safe (or safer) language, but there's
 an issue that makes it less safe as it could be.  I'm talking about
 arithmetic overflows and division by zero.  The safeint package tries
 to address this, but it only supports the Int type because (as I
 understand it) there are no useful primitives for other common types
 defined in Data.Int and Data.Word.

 I've tried adding Int64 support to safeint just to see how it would work
 without primops.  Here's a snippet (I haven't tested this code well, so
 it may be wrong, sorry about that):

 shiftRUnsigned :: Word64 - Int - Word64
 shiftRUnsigned = shiftR

 --
 http://git.haskell.org/ghc.git/blob/HEAD:/compiler/codeGen/StgCmmPrim.hs#l930
 plusSI64 :: SafeInt64 - SafeInt64 - SafeInt64
 plusSI64 (SI64 a) (SI64 b) = if c == 0 then SI64 r else overflowError
   where
 r = a + b
 c = (fromIntegral $ (complement (a `xor` b)) .. (a `xor` r))
 `shiftRUnsigned`
 ((finiteBitSize a) - 1)

 --
 http://git.haskell.org/ghc.git/blob/HEAD:/compiler/codeGen/StgCmmPrim.hs#l966
 minusSI64 :: SafeInt64 - SafeInt64 - SafeInt64
 minusSI64 (SI64 a) (SI64 b) = if c == 0 then SI64 r else overflowError
   where
 r = a - b
 c = (fromIntegral $ (a `xor` b) .. (a `xor` r))
 `shiftRUnsigned`
 ((finiteBitSize a) - 1)

 -- https://stackoverflow.com/a/1815371
 timesSI64 :: SafeInt64 - SafeInt64 - SafeInt64
 timesSI64 (SI64 a) (SI64 b) =
   let x = a * b
   in if a /= 0  x `div` a /= b
  then overflowError
  else SI64 x

 I may be wrong, but my understanding is that new primops could reduce
 overhead here.  If so, would a patch adding them be accepted?  Are
 there any caveats?

 In the safeint package, would it be reasonable to return an Either
 value instead of throwing an exception?  Or would it be too much?

 I haven't created a wiki page or ticket because I don't know much, so
 I want to get some feedback before doing so.  That would be my first
 patch to GHC (if ever), so maybe I'm not the best candidate, but I've
 been thinking about it for too long to ignore. :\
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


  1   2   >