From wolfgang-it at jeltsch.info Thu Jul 6 20:45:32 2017 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Thu, 06 Jul 2017 23:45:32 +0300 Subject: Heterogeneous equality into base? Message-ID: <1499373932.2497.139.camel@jeltsch.info> Hi! The module Data.Type.Equality in the base package contains the type (:~:) for homogeneous equality. However, a type for heterogeneous equality would be very useful as well. I would define such a type as follows: > {-# LANGUAGE GADTs, PolyKinds, TypeOperators #-} >  > data (a :: k) :~~: (b :: l) where >  >     Refl :: a :~~: a Is there already such a type in the base package? If not, does it make sense to file a feature request (or would such a proposal be likely to not being accepted for some reason)? All the best, Wolfgang From david.feuer at gmail.com Thu Jul 6 20:55:31 2017 From: david.feuer at gmail.com (David Feuer) Date: Thu, 6 Jul 2017 16:55:31 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <1499373932.2497.139.camel@jeltsch.info> References: <1499373932.2497.139.camel@jeltsch.info> Message-ID: That seems generally reasonable to me. It'll need the usual discussion process here and then it can be added to `base`. However, I think it should not be added to `Data.Type.Equality`, but rather to a new module, perhaps `Data.Type.Equality.Heterogeneous`. That module will then be able to offer the full complement of basic functions (sym, trans, ...) without stepping on the pre-existing names. I imagine you'll also want one or two extra casting operations, and conversions between `:~:` and `:~~:`. Also, you have called the constructor of this type HRefl in the past, which strikes me as better than Refl. David On Thu, Jul 6, 2017 at 4:45 PM, Wolfgang Jeltsch wrote: > Hi! > > The module Data.Type.Equality in the base package contains the type > (:~:) for homogeneous equality. However, a type for heterogeneous > equality would be very useful as well. I would define such a type as > follows: > >> {-# LANGUAGE GADTs, PolyKinds, TypeOperators #-} >> >> data (a :: k) :~~: (b :: l) where >> >> Refl :: a :~~: a > > Is there already such a type in the base package? If not, does it make > sense to file a feature request (or would such a proposal be likely to > not being accepted for some reason)? > > All the best, > Wolfgang > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From emertens at gmail.com Thu Jul 6 20:59:54 2017 From: emertens at gmail.com (Eric Mertens) Date: Thu, 06 Jul 2017 20:59:54 +0000 Subject: Heterogeneous equality into base? In-Reply-To: References: <1499373932.2497.139.camel@jeltsch.info> Message-ID: This seems like the kind of thing that first should be fleshed out in its own package. Is there some reason that this module would need to be in base? On Thu, Jul 6, 2017 at 1:56 PM David Feuer wrote: > That seems generally reasonable to me. It'll need the usual discussion > process here and then it can be added to `base`. However, I think it > should not be added to `Data.Type.Equality`, but rather to a new > module, perhaps `Data.Type.Equality.Heterogeneous`. That module will > then be able to offer the full complement of basic functions (sym, > trans, ...) without stepping on the pre-existing names. I imagine > you'll also want one or two extra casting operations, and conversions > between `:~:` and `:~~:`. Also, you have called the constructor of > this type HRefl in the past, which strikes me as better than Refl. > > David > > On Thu, Jul 6, 2017 at 4:45 PM, Wolfgang Jeltsch > wrote: > > Hi! > > > > The module Data.Type.Equality in the base package contains the type > > (:~:) for homogeneous equality. However, a type for heterogeneous > > equality would be very useful as well. I would define such a type as > > follows: > > > >> {-# LANGUAGE GADTs, PolyKinds, TypeOperators #-} > >> > >> data (a :: k) :~~: (b :: l) where > >> > >> Refl :: a :~~: a > > > > Is there already such a type in the base package? If not, does it make > > sense to file a feature request (or would such a proposal be likely to > > not being accepted for some reason)? > > > > All the best, > > Wolfgang > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dave at zednenem.com Thu Jul 6 21:15:36 2017 From: dave at zednenem.com (David Menendez) Date: Thu, 6 Jul 2017 17:15:36 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <1499373932.2497.139.camel@jeltsch.info> References: <1499373932.2497.139.camel@jeltsch.info> Message-ID: Do you have any code examples that use heterogeneous equality? In the past, GHC has been less flexible with kind variables than with type variables, so I’m not sure what this would enable. On Thu, Jul 6, 2017 at 4:45 PM, Wolfgang Jeltsch wrote: > Hi! > > The module Data.Type.Equality in the base package contains the type > (:~:) for homogeneous equality. However, a type for heterogeneous > equality would be very useful as well. I would define such a type as > follows: > >> {-# LANGUAGE GADTs, PolyKinds, TypeOperators #-} >> >> data (a :: k) :~~: (b :: l) where >> >> Refl :: a :~~: a > > Is there already such a type in the base package? If not, does it make > sense to file a feature request (or would such a proposal be likely to > not being accepted for some reason)? > > All the best, > Wolfgang > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -- Dave Menendez From wolfgang-it at jeltsch.info Thu Jul 6 21:47:50 2017 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Fri, 07 Jul 2017 00:47:50 +0300 Subject: Heterogeneous equality into base? In-Reply-To: References: <1499373932.2497.139.camel@jeltsch.info> Message-ID: <1499377670.2497.152.camel@jeltsch.info> Hi! From https://wiki.haskell.org/Library_submissions, I understood that the discussion should take place on the GHC Trac and will be moved to the Libraries Mailing List only in serious cases. Is this the case?(Interestingly, the link on the aforementioned page contains a bogus URL. However, I do not know for sure the correct URL to fix this.) I also think that creating a new module Data.Type.Equality.Heterogeneous is the way to go. I would call the constructor of (:~~:) Refl, not HRefl. If you need to distinguish between the Refl of (:~:) and the Refl of (:~~:), you can qualify the name using the module system. I think it is generally better to use the module system for qualifying names than putting the qualification into the identifiers like in “HRefl”. The module system is made to express qualification. On the other hand, qualification in identifiers is typically done with single letters to save space, which is not very descriptive and quickly results in ambiguities (for example, “m” means “monoid” in “mappend”, but “monad” in “mplus”). I will try to come up with an initial implementation of this new Data.Type.Equality.Heterogeneous module. All the best, Wolfgang Am Donnerstag, den 06.07.2017, 16:55 -0400 schrieb David Feuer: > That seems generally reasonable to me. It'll need the usual discussion > process here and then it can be added to `base`. However, I think it > should not be added to `Data.Type.Equality`, but rather to a new > module, perhaps `Data.Type.Equality.Heterogeneous`. That module will > then be able to offer the full complement of basic functions (sym, > trans, ...) without stepping on the pre-existing names. I imagine > you'll also want one or two extra casting operations, and conversions > between `:~:` and `:~~:`. Also, you have called the constructor of > this type HRefl in the past, which strikes me as better than Refl. > > David > > On Thu, Jul 6, 2017 at 4:45 PM, Wolfgang Jeltsch > wrote: > > > > Hi! > > > > The module Data.Type.Equality in the base package contains the type > > (:~:) for homogeneous equality. However, a type for heterogeneous > > equality would be very useful as well. I would define such a type as > > follows: > > > > > > > > {-# LANGUAGE GADTs, PolyKinds, TypeOperators #-} > > > > > > data (a :: k) :~~: (b :: l) where > > > > > >     Refl :: a :~~: a > > > > Is there already such a type in the base package? If not, does it > > make sense to file a feature request (or would such a proposal be > > likely to not being accepted for some reason)? > > > > All the best, > > Wolfgang From wolfgang-it at jeltsch.info Thu Jul 6 22:10:37 2017 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Fri, 07 Jul 2017 01:10:37 +0300 Subject: Heterogeneous equality into base? In-Reply-To: References: <1499373932.2497.139.camel@jeltsch.info> Message-ID: <1499379037.2497.163.camel@jeltsch.info> Hi! Yes, I have some code that uses this heterogeneous equality type apparently successfully. I will try to explain the idea behind this code a bit. There is a kind-polymorphic class Q that contains an associated type synonym family that maps instances of Q to types of kind *. This type synonym family shall be injective, and there should be actual witness of this injectivity. This is achieved by requiring every instantiation of Q to provide a heterogeneous equality proof of some kind. The equality must be heterogeneous, because Q is kind-polymorphic. Here is some code that illustrates the idea in more detail: > {-# LANGUAGE GADTs, >              PolyKinds, >              TypeFamilies, >              TypeOperators, >              UndecidableInstances, >              UndecidableSuperClasses #-} >  > import GHC.Exts (Constraint) >  > -- * Heterogeneous equality >  > data (a :: l) :~~: (b :: k) where >  >     Refl :: a :~~: a >  > transLike :: a :~~: c -> b :~~: c -> a :~~: b > transLike Refl Refl = Refl >  > -- * Interface >  > type family C a :: k -> Constraint >  > class C (F q) q => Q q where >  >     type F q :: * >  >     eq :: (Q q', F q ~ F q') => q :~~: q' >  > -- * Implementation for []/Bool >  > class ListQ q where >  >     listEq :: q :~~: [] >  > instance ListQ [] where >  >     listEq = Refl >  > type instance C Bool = ListQ >  > instance Q [] where >  >     type F [] = Bool >  >     eq = transLike listEq listEq The central thing is the eq method, whose complete type is as follows:     forall q q' . (Q q, Q q', F q ~ F q') => q :~~: q' All the best, Wolfgang Am Donnerstag, den 06.07.2017, 17:15 -0400 schrieb David Menendez: > Do you have any code examples that use heterogeneous equality? In the > past, GHC has been less flexible with kind variables than with type > variables, so I’m not sure what this would enable. > > On Thu, Jul 6, 2017 at 4:45 PM, Wolfgang Jeltsch > wrote: > > > > Hi! > > > > The module Data.Type.Equality in the base package contains the type > > (:~:) for homogeneous equality. However, a type for heterogeneous > > equality would be very useful as well. I would define such a type as > > follows: > > > > > > > > {-# LANGUAGE GADTs, PolyKinds, TypeOperators #-} > > > > > > data (a :: k) :~~: (b :: l) where > > > > > >     Refl :: a :~~: a > > Is there already such a type in the base package? If not, does it > > make > > sense to file a feature request (or would such a proposal be likely > > to > > not being accepted for some reason)? > > > > All the best, > > Wolfgang > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > From rae at cs.brynmawr.edu Fri Jul 7 01:57:56 2017 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Thu, 6 Jul 2017 21:57:56 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <1499379037.2497.163.camel@jeltsch.info> References: <1499373932.2497.139.camel@jeltsch.info> <1499379037.2497.163.camel@jeltsch.info> Message-ID: <7C199CCC-3027-4451-919C-105219778A79@cs.brynmawr.edu> Hi Ben, This discussion of heterogeneous equality in base may be of interest to you. Did you have to use a similar definition to get the new Typeable stuff working? I would imagine so. If you indeed did, that would provide a good argument for exporting this definition from base. Separately from seeking Ben's input, I am in favor of this addition. If (:~:) is in base, (:~~:) should be, too. Thanks, Richard > On Jul 6, 2017, at 6:10 PM, Wolfgang Jeltsch wrote: > > Hi! > > Yes, I have some code that uses this heterogeneous equality type > apparently successfully. I will try to explain the idea behind this code > a bit. > > There is a kind-polymorphic class Q that contains an associated type > synonym family that maps instances of Q to types of kind *. This type > synonym family shall be injective, and there should be actual witness of > this injectivity. This is achieved by requiring every instantiation of Q > to provide a heterogeneous equality proof of some kind. The equality > must be heterogeneous, because Q is kind-polymorphic. > > Here is some code that illustrates the idea in more detail: > >> {-# LANGUAGE GADTs, >> PolyKinds, >> TypeFamilies, >> TypeOperators, >> UndecidableInstances, >> UndecidableSuperClasses #-} >> >> import GHC.Exts (Constraint) >> >> -- * Heterogeneous equality >> >> data (a :: l) :~~: (b :: k) where >> >> Refl :: a :~~: a >> >> transLike :: a :~~: c -> b :~~: c -> a :~~: b >> transLike Refl Refl = Refl >> >> -- * Interface >> >> type family C a :: k -> Constraint >> >> class C (F q) q => Q q where >> >> type F q :: * >> >> eq :: (Q q', F q ~ F q') => q :~~: q' >> >> -- * Implementation for []/Bool >> >> class ListQ q where >> >> listEq :: q :~~: [] >> >> instance ListQ [] where >> >> listEq = Refl >> >> type instance C Bool = ListQ >> >> instance Q [] where >> >> type F [] = Bool >> >> eq = transLike listEq listEq > > The central thing is the eq method, whose complete type is as follows: > > forall q q' . (Q q, Q q', F q ~ F q') => q :~~: q' > > All the best, > Wolfgang > > Am Donnerstag, den 06.07.2017, 17:15 -0400 schrieb David Menendez: >> Do you have any code examples that use heterogeneous equality? In the >> past, GHC has been less flexible with kind variables than with type >> variables, so I’m not sure what this would enable. >> >> On Thu, Jul 6, 2017 at 4:45 PM, Wolfgang Jeltsch >> wrote: >>> >>> Hi! >>> >>> The module Data.Type.Equality in the base package contains the type >>> (:~:) for homogeneous equality. However, a type for heterogeneous >>> equality would be very useful as well. I would define such a type as >>> follows: >>> >>>> >>>> {-# LANGUAGE GADTs, PolyKinds, TypeOperators #-} >>>> >>>> data (a :: k) :~~: (b :: l) where >>>> >>>> Refl :: a :~~: a >>> Is there already such a type in the base package? If not, does it >>> make >>> sense to file a feature request (or would such a proposal be likely >>> to >>> not being accepted for some reason)? >>> >>> All the best, >>> Wolfgang >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From julm+haskell at autogeree.net Fri Jul 7 04:03:41 2017 From: julm+haskell at autogeree.net (Julien Moutinho) Date: Fri, 7 Jul 2017 06:03:41 +0200 Subject: Heterogeneous equality into base? In-Reply-To: <1499377670.2497.152.camel@jeltsch.info> Message-ID: <20170707040341.GA12877@localhost> Hi libraries@, My 2 cents inlined below :) ~~julm Le jeu. 06 juil. 2017 à 17:15:36 -0400, David Menendez a écrit : > Do you have any code examples that use heterogeneous equality? In the > past, GHC has been less flexible with kind variables than with type > variables, so I’m not sure what this would enable. I have been using (:~~:) to return two proofs when two type-indexed runtime representations of types are equal: one proof for the equality of kinds, and another proof for the equality of types. For instance, this can be seen in eqVarKi, eqConstKi, and eqTypeKi in https://hackage.haskell.org/package/symantic-6.3.0.20170703/ It's also done here: https://ghc.haskell.org/trac/ghc/wiki/Typeable#Step4:Decomposingarbitrarytypes Le ven. 07 juil. 2017 à 00:47:50 +0300, Wolfgang Jeltsch a écrit : > I also think that creating a new module Data.Type.Equality.Heterogeneous > is the way to go. I would call the constructor of (:~~:) Refl, not > HRefl. If you need to distinguish between the Refl of (:~:) and the Refl > of (:~~:), you can qualify the name using the module system. > > I think it is generally better to use the module system for qualifying > names than putting the qualification into the identifiers like in > “HRefl”. The module system is made to express qualification. On the > other hand, qualification in identifiers is typically done with single > letters to save space, which is not very descriptive and quickly results > in ambiguities (for example, “m” means “monoid” in “mappend”, but > “monad” in “mplus”). By myself I came up with the name KRefl, but changed it to HRefl to reduce cognitive efforts, when I discovered Richard's thesis which is introducing it. http://cs.brynmawr.edu/~rae/papers/2016/thesis/eisenberg-thesis.pdf I'm using both Refl and HRefl in the same package, so I prefer to name the latter HRefl instead of H.Refl, to keep a flat namespace which allows open imports and re-exports in parent modules. This also makes grep-ing/web-searching easier, and Haddock generated docs more readable (because there the module paths are hidden). https://www.reddit.com/r/haskell/comments/6j2t1o/on_naming_things_library_design/ This said, some of these concerns may not apply to base. Cheers :] -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 992 bytes Desc: Digital signature URL: From ryan.gl.scott at gmail.com Fri Jul 7 15:15:52 2017 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Fri, 7 Jul 2017 08:15:52 -0700 Subject: Heterogeneous equality into base? Message-ID: Sorry for only just discovering this thread now. A lot of this discussion is in fact moot, since (:~~:) already is in base! Specifically, it's landing in Data.Type.Equality [1] in the next version of base (bundled with GHC 8.2). Moreover, it's constructor is named HRefl, so your wish has been granted ;) As for why it's being introduced in base, it ended up being useful for the new Type-indexed Typeable that's also landing in GHC 8.2. In particular, the eqTypeRep function [2] must return heterogeneous equality (:~~:), not homogeneous equality (:~:), since it's possible that you'll compare two TypeReps with different kinds. Ryan S. ----- [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311 -------------- next part -------------- An HTML attachment was scrubbed... URL: From wolfgang-it at jeltsch.info Sat Jul 8 23:56:02 2017 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Sun, 09 Jul 2017 02:56:02 +0300 Subject: Heterogeneous equality into base? In-Reply-To: References: Message-ID: <1499558162.2497.231.camel@jeltsch.info> Hi! Unfortunately, my wish has not been granted, as I wanted the data constructor of (:~~:) to be named Refl and (:~~:) to be defined in a separate module. I see that there are no heterogeneous versions of sym, trans, and so on in base at the moment. If they will be available at some time, how will they be called? Will they be named hsym, htrans, and so on? This would be awful, in my opinion. In Haskell, we have the module system for qualification. I very well understand the issues Julien Moutinho pointed out. For example, you cannot have a module that just reexports all the functions from Data.Sequence and Data.Map, because you would get name clashes. However, I think that the solution to these kinds of problems is to fix the module system. An idea would be to allow for exporting qualified names. Then a module could import Data.Sequence and Data.Map qualified as Seq and Map, respectively, and export Seq.empty, Map.empty, and so on.  If we try to work around those issues with the module system by putting qualification into the actual identifiers in the form of single letters (like in mappend, HRef, and so on), we will be stuck with this workaround forever, even if the module system will be changed at some time, because identifiers in core libraries are typically not changed. Just imagine, we would have followed this practice for the containers package. We would have identifiers like “smap”, “munion”, “imintersection”, and so on. All the best, Wolfgang Am Freitag, den 07.07.2017, 08:15 -0700 schrieb Ryan Scott: > Sorry for only just discovering this thread now. A lot of this > discussion is in fact moot, since (:~~:) already is in base! > Specifically, it's landing in Data.Type.Equality [1] in the next > version of base (bundled with GHC 8.2). Moreover, it's constructor is > named HRefl, so your wish has been granted ;) > > As for why it's being introduced in base, it ended up being useful for > the new Type-indexed Typeable that's also landing in GHC 8.2. In > particular, the eqTypeRep function [2] must return heterogeneous > equality (:~~:), not homogeneous equality (:~:), since it's possible > that you'll compare two TypeReps with different kinds. > > Ryan S. > ----- > [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 > [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311> From andrew.thaddeus at gmail.com Sun Jul 9 01:25:58 2017 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Sat, 8 Jul 2017 21:25:58 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <1499558162.2497.231.camel@jeltsch.info> References: <1499558162.2497.231.camel@jeltsch.info> Message-ID: <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> Just wanted to weigh in with my two cents. I also prefer to use the module system for the most part rather than prefixing function names with something that indicates the data type they operate on. However, when it comes to types, I would much rather they have different names. I like that the data constructor of :~~: is HRefl. However, for the functions sym, trans, etc., I would rather have a Data.Type.Equality.Hetero that exports all of these without any kind of prefixes on them. Then there's the question of where we export :~~: from. It could be exported only from the Hetero module, or it could be exported from both. Sent from my iPhone > On Jul 8, 2017, at 7:56 PM, Wolfgang Jeltsch wrote: > > Hi! > > Unfortunately, my wish has not been granted, as I wanted the data > constructor of (:~~:) to be named Refl and (:~~:) to be defined in a > separate module. I see that there are no heterogeneous versions of sym, > trans, and so on in base at the moment. If they will be available at > some time, how will they be called? Will they be named hsym, htrans, and > so on? This would be awful, in my opinion. > > In Haskell, we have the module system for qualification. I very well > understand the issues Julien Moutinho pointed out. For example, you > cannot have a module that just reexports all the functions from > Data.Sequence and Data.Map, because you would get name clashes. > > However, I think that the solution to these kinds of problems is to fix > the module system. An idea would be to allow for exporting qualified > names. Then a module could import Data.Sequence and Data.Map qualified > as Seq and Map, respectively, and export Seq.empty, Map.empty, and so > on. > > If we try to work around those issues with the module system by putting > qualification into the actual identifiers in the form of single letters > (like in mappend, HRef, and so on), we will be stuck with this > workaround forever, even if the module system will be changed at some > time, because identifiers in core libraries are typically not changed. > Just imagine, we would have followed this practice for the containers > package. We would have identifiers like “smap”, “munion”, > “imintersection”, and so on. > > All the best, > Wolfgang > > Am Freitag, den 07.07.2017, 08:15 -0700 schrieb Ryan Scott: >> Sorry for only just discovering this thread now. A lot of this >> discussion is in fact moot, since (:~~:) already is in base! >> Specifically, it's landing in Data.Type.Equality [1] in the next >> version of base (bundled with GHC 8.2). Moreover, it's constructor is >> named HRefl, so your wish has been granted ;) >> >> As for why it's being introduced in base, it ended up being useful for >> the new Type-indexed Typeable that's also landing in GHC 8.2. In >> particular, the eqTypeRep function [2] must return heterogeneous >> equality (:~~:), not homogeneous equality (:~:), since it's possible >> that you'll compare two TypeReps with different kinds. >> >> Ryan S. >> ----- >> [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 >> [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311> > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From david.feuer at gmail.com Sun Jul 9 01:37:49 2017 From: david.feuer at gmail.com (David Feuer) Date: Sat, 8 Jul 2017 21:37:49 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> Message-ID: FWIW, I agree with Andrew Martin on this one. On Jul 8, 2017 9:26 PM, "Andrew Martin" wrote: > Just wanted to weigh in with my two cents. I also prefer to use the module > system for the most part rather than prefixing function names with > something that indicates the data type they operate on. However, when it > comes to types, I would much rather they have different names. I like that > the data constructor of :~~: is HRefl. However, for the functions sym, > trans, etc., I would rather have a Data.Type.Equality.Hetero that exports > all of these without any kind of prefixes on them. Then there's the > question of where we export :~~: from. It could be exported only from the > Hetero module, or it could be exported from both. > > Sent from my iPhone > > > On Jul 8, 2017, at 7:56 PM, Wolfgang Jeltsch > wrote: > > > > Hi! > > > > Unfortunately, my wish has not been granted, as I wanted the data > > constructor of (:~~:) to be named Refl and (:~~:) to be defined in a > > separate module. I see that there are no heterogeneous versions of sym, > > trans, and so on in base at the moment. If they will be available at > > some time, how will they be called? Will they be named hsym, htrans, and > > so on? This would be awful, in my opinion. > > > > In Haskell, we have the module system for qualification. I very well > > understand the issues Julien Moutinho pointed out. For example, you > > cannot have a module that just reexports all the functions from > > Data.Sequence and Data.Map, because you would get name clashes. > > > > However, I think that the solution to these kinds of problems is to fix > > the module system. An idea would be to allow for exporting qualified > > names. Then a module could import Data.Sequence and Data.Map qualified > > as Seq and Map, respectively, and export Seq.empty, Map.empty, and so > > on. > > > > If we try to work around those issues with the module system by putting > > qualification into the actual identifiers in the form of single letters > > (like in mappend, HRef, and so on), we will be stuck with this > > workaround forever, even if the module system will be changed at some > > time, because identifiers in core libraries are typically not changed. > > Just imagine, we would have followed this practice for the containers > > package. We would have identifiers like “smap”, “munion”, > > “imintersection”, and so on. > > > > All the best, > > Wolfgang > > > > Am Freitag, den 07.07.2017, 08:15 -0700 schrieb Ryan Scott: > >> Sorry for only just discovering this thread now. A lot of this > >> discussion is in fact moot, since (:~~:) already is in base! > >> Specifically, it's landing in Data.Type.Equality [1] in the next > >> version of base (bundled with GHC 8.2). Moreover, it's constructor is > >> named HRefl, so your wish has been granted ;) > >> > >> As for why it's being introduced in base, it ended up being useful for > >> the new Type-indexed Typeable that's also landing in GHC 8.2. In > >> particular, the eqTypeRep function [2] must return heterogeneous > >> equality (:~~:), not homogeneous equality (:~:), since it's possible > >> that you'll compare two TypeReps with different kinds. > >> > >> Ryan S. > >> ----- > >> [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718 > d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 > >> [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5f718 > d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311> > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Jul 9 16:27:58 2017 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 9 Jul 2017 12:27:58 -0400 Subject: Heterogeneous equality into base? In-Reply-To: References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> Message-ID: I think it also needs to be available to all clients of new typeable too! right? On Sat, Jul 8, 2017 at 9:37 PM, David Feuer wrote: > FWIW, I agree with Andrew Martin on this one. > > On Jul 8, 2017 9:26 PM, "Andrew Martin" wrote: > >> Just wanted to weigh in with my two cents. I also prefer to use the >> module system for the most part rather than prefixing function names with >> something that indicates the data type they operate on. However, when it >> comes to types, I would much rather they have different names. I like that >> the data constructor of :~~: is HRefl. However, for the functions sym, >> trans, etc., I would rather have a Data.Type.Equality.Hetero that exports >> all of these without any kind of prefixes on them. Then there's the >> question of where we export :~~: from. It could be exported only from the >> Hetero module, or it could be exported from both. >> >> Sent from my iPhone >> >> > On Jul 8, 2017, at 7:56 PM, Wolfgang Jeltsch >> wrote: >> > >> > Hi! >> > >> > Unfortunately, my wish has not been granted, as I wanted the data >> > constructor of (:~~:) to be named Refl and (:~~:) to be defined in a >> > separate module. I see that there are no heterogeneous versions of sym, >> > trans, and so on in base at the moment. If they will be available at >> > some time, how will they be called? Will they be named hsym, htrans, and >> > so on? This would be awful, in my opinion. >> > >> > In Haskell, we have the module system for qualification. I very well >> > understand the issues Julien Moutinho pointed out. For example, you >> > cannot have a module that just reexports all the functions from >> > Data.Sequence and Data.Map, because you would get name clashes. >> > >> > However, I think that the solution to these kinds of problems is to fix >> > the module system. An idea would be to allow for exporting qualified >> > names. Then a module could import Data.Sequence and Data.Map qualified >> > as Seq and Map, respectively, and export Seq.empty, Map.empty, and so >> > on. >> > >> > If we try to work around those issues with the module system by putting >> > qualification into the actual identifiers in the form of single letters >> > (like in mappend, HRef, and so on), we will be stuck with this >> > workaround forever, even if the module system will be changed at some >> > time, because identifiers in core libraries are typically not changed. >> > Just imagine, we would have followed this practice for the containers >> > package. We would have identifiers like “smap”, “munion”, >> > “imintersection”, and so on. >> > >> > All the best, >> > Wolfgang >> > >> > Am Freitag, den 07.07.2017, 08:15 -0700 schrieb Ryan Scott: >> >> Sorry for only just discovering this thread now. A lot of this >> >> discussion is in fact moot, since (:~~:) already is in base! >> >> Specifically, it's landing in Data.Type.Equality [1] in the next >> >> version of base (bundled with GHC 8.2). Moreover, it's constructor is >> >> named HRefl, so your wish has been granted ;) >> >> >> >> As for why it's being introduced in base, it ended up being useful for >> >> the new Type-indexed Typeable that's also landing in GHC 8.2. In >> >> particular, the eqTypeRep function [2] must return heterogeneous >> >> equality (:~~:), not homogeneous equality (:~:), since it's possible >> >> that you'll compare two TypeReps with different kinds. >> >> >> >> Ryan S. >> >> ----- >> >> [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0 >> e5f718d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 >> >> [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0 >> e5f718d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311> >> > _______________________________________________ >> > Libraries mailing list >> > Libraries at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From wolfgang-it at jeltsch.info Sun Jul 9 19:47:57 2017 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Sun, 09 Jul 2017 22:47:57 +0300 Subject: Heterogeneous equality into base? In-Reply-To: <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> Message-ID: <1499629677.2497.247.camel@jeltsch.info> Hi! I agree with you, Andrew, that types should have different names. However, (H)Refl is not a type. It is a data constructor; so it is a special kind of value and as such very similar to sym, trans, and friends. The similarity of Refl to the ordinary functions of the Heterogeneous module becomes even more obvious when considering that Refl is a proof, like sym, trans, and so on. All the best, Wolfgang Am Samstag, den 08.07.2017, 21:25 -0400 schrieb Andrew Martin: > Just wanted to weigh in with my two cents. I also prefer to use the > module system for the most part rather than prefixing function names > with something that indicates the data type they operate on. However, > when it comes to types, I would much rather they have different names. > I like that the data constructor of :~~: is HRefl. However, for the > functions sym, trans, etc., I would rather have a > Data.Type.Equality.Hetero that exports all of these without any kind > of prefixes on them. Then there's the question of where we export :~~: > from. It could be exported only from the Hetero module, or it could be > exported from both. > > Sent from my iPhone > > > > > On Jul 8, 2017, at 7:56 PM, Wolfgang Jeltsch > fo> wrote: > > > > Hi! > > > > Unfortunately, my wish has not been granted, as I wanted the data > > constructor of (:~~:) to be named Refl and (:~~:) to be defined in a > > separate module. I see that there are no heterogeneous versions of > > sym, > > trans, and so on in base at the moment. If they will be available at > > some time, how will they be called? Will they be named hsym, htrans, > > and > > so on? This would be awful, in my opinion. > > > > In Haskell, we have the module system for qualification. I very well > > understand the issues Julien Moutinho pointed out. For example, you > > cannot have a module that just reexports all the functions from > > Data.Sequence and Data.Map, because you would get name clashes. > > > > However, I think that the solution to these kinds of problems is to > > fix > > the module system. An idea would be to allow for exporting qualified > > names. Then a module could import Data.Sequence and Data.Map > > qualified > > as Seq and Map, respectively, and export Seq.empty, Map.empty, and > > so > > on.  > > > > If we try to work around those issues with the module system by > > putting > > qualification into the actual identifiers in the form of single > > letters > > (like in mappend, HRef, and so on), we will be stuck with this > > workaround forever, even if the module system will be changed at > > some > > time, because identifiers in core libraries are typically not > > changed. > > Just imagine, we would have followed this practice for the > > containers > > package. We would have identifiers like “smap”, “munion”, > > “imintersection”, and so on. > > > > All the best, > > Wolfgang > > > > Am Freitag, den 07.07.2017, 08:15 -0700 schrieb Ryan Scott: > > > > > > Sorry for only just discovering this thread now. A lot of this > > > discussion is in fact moot, since (:~~:) already is in base! > > > Specifically, it's landing in Data.Type.Equality [1] in the next > > > version of base (bundled with GHC 8.2). Moreover, it's constructor > > > is > > > named HRefl, so your wish has been granted ;) > > > > > > As for why it's being introduced in base, it ended up being useful > > > for > > > the new Type-indexed Typeable that's also landing in GHC 8.2. In > > > particular, the eqTypeRep function [2] must return heterogeneous > > > equality (:~~:), not homogeneous equality (:~:), since it's > > > possible > > > that you'll compare two TypeReps with different kinds. > > > > > > Ryan S. > > > ----- > > > [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5 > > > f718d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 > > > [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5 > > > f718d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311>;  > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From oleg.grenrus at iki.fi Sun Jul 9 21:35:05 2017 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Mon, 10 Jul 2017 00:35:05 +0300 Subject: Heterogeneous equality into base? In-Reply-To: <1499629677.2497.247.camel@jeltsch.info> References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> <1499629677.2497.247.camel@jeltsch.info> Message-ID: <78602EF8-3A8B-4B35-B18D-E96C6AC42FCE@iki.fi> It's not only a value, it's also a pattern. We have PatternSynonyms, but IMHO it's not a strong argument for having constructors with a same name. - Oleg Sent from my iPhone > On 9 Jul 2017, at 22.47, Wolfgang Jeltsch wrote: > > Hi! > > I agree with you, Andrew, that types should have different names. > However, (H)Refl is not a type. It is a data constructor; so it is a > special kind of value and as such very similar to sym, trans, and > friends. The similarity of Refl to the ordinary functions of the > Heterogeneous module becomes even more obvious when considering that > Refl is a proof, like sym, trans, and so on. > > All the best, > Wolfgang > > Am Samstag, den 08.07.2017, 21:25 -0400 schrieb Andrew Martin: >> Just wanted to weigh in with my two cents. I also prefer to use the >> module system for the most part rather than prefixing function names >> with something that indicates the data type they operate on. However, >> when it comes to types, I would much rather they have different names. >> I like that the data constructor of :~~: is HRefl. However, for the >> functions sym, trans, etc., I would rather have a >> Data.Type.Equality.Hetero that exports all of these without any kind >> of prefixes on them. Then there's the question of where we export :~~: >> from. It could be exported only from the Hetero module, or it could be >> exported from both. >> >> Sent from my iPhone >> >>> >>> On Jul 8, 2017, at 7:56 PM, Wolfgang Jeltsch >> fo> wrote: >>> >>> Hi! >>> >>> Unfortunately, my wish has not been granted, as I wanted the data >>> constructor of (:~~:) to be named Refl and (:~~:) to be defined in a >>> separate module. I see that there are no heterogeneous versions of >>> sym, >>> trans, and so on in base at the moment. If they will be available at >>> some time, how will they be called? Will they be named hsym, htrans, >>> and >>> so on? This would be awful, in my opinion. >>> >>> In Haskell, we have the module system for qualification. I very well >>> understand the issues Julien Moutinho pointed out. For example, you >>> cannot have a module that just reexports all the functions from >>> Data.Sequence and Data.Map, because you would get name clashes. >>> >>> However, I think that the solution to these kinds of problems is to >>> fix >>> the module system. An idea would be to allow for exporting qualified >>> names. Then a module could import Data.Sequence and Data.Map >>> qualified >>> as Seq and Map, respectively, and export Seq.empty, Map.empty, and >>> so >>> on. >>> >>> If we try to work around those issues with the module system by >>> putting >>> qualification into the actual identifiers in the form of single >>> letters >>> (like in mappend, HRef, and so on), we will be stuck with this >>> workaround forever, even if the module system will be changed at >>> some >>> time, because identifiers in core libraries are typically not >>> changed. >>> Just imagine, we would have followed this practice for the >>> containers >>> package. We would have identifiers like “smap”, “munion”, >>> “imintersection”, and so on. >>> >>> All the best, >>> Wolfgang >>> >>> Am Freitag, den 07.07.2017, 08:15 -0700 schrieb Ryan Scott: >>>> >>>> Sorry for only just discovering this thread now. A lot of this >>>> discussion is in fact moot, since (:~~:) already is in base! >>>> Specifically, it's landing in Data.Type.Equality [1] in the next >>>> version of base (bundled with GHC 8.2). Moreover, it's constructor >>>> is >>>> named HRefl, so your wish has been granted ;) >>>> >>>> As for why it's being introduced in base, it ended up being useful >>>> for >>>> the new Type-indexed Typeable that's also landing in GHC 8.2. In >>>> particular, the eqTypeRep function [2] must return heterogeneous >>>> equality (:~~:), not homogeneous equality (:~:), since it's >>>> possible >>>> that you'll compare two TypeReps with different kinds. >>>> >>>> Ryan S. >>>> ----- >>>> [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5 >>>> f718d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 >>>> [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5 >>>> f718d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311>; >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Mon Jul 10 00:31:32 2017 From: ekmett at gmail.com (Edward Kmett) Date: Sun, 9 Jul 2017 20:31:32 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <78602EF8-3A8B-4B35-B18D-E96C6AC42FCE@iki.fi> References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> <1499629677.2497.247.camel@jeltsch.info> <78602EF8-3A8B-4B35-B18D-E96C6AC42FCE@iki.fi> Message-ID: I for one favor the HRefl constructor name for practical reasons. These types will commonly be used in similar scopes. Also, there is a theoretical quibble for why this shouldn't just replace :~: directly in any code that would otherwise use both and why both will be used in much the same code going forward: Heterogenous equality is a form of what Conor McBride calls "John Major" equality. In a more general type theory, HRefl doesn't imply Refl! You can't show HRefl implies Refl in MLTT. This extra power is granted by dependent pattern matching most dependent type theories or in Haskell by the way we implement ~. In Haskell, today, it works out because we have "uniqueness of identity proofs" or "axiom K". This means that anything going on in the world of homotopy type theory today can't be used in Haskell directly as univalence and axiom k are inconsistent. Some work has been put into pattern matching in Agda without axiom K. Do I expect that folks are going to run out and implement it in Haskell? No, but in general I want to be very clear in my code when I rely upon this extra power that Haskell grants us kinda by accident or fiat today as those results don't transfer, and could be dangerous to assume if we decide to go in a different direction in the far flung future. -Edward Sent from my iPad > On Jul 9, 2017, at 5:35 PM, Oleg Grenrus wrote: > > It's not only a value, it's also a pattern. We have PatternSynonyms, but IMHO it's not a strong argument for having constructors with a same name. > > - Oleg > > Sent from my iPhone > >> On 9 Jul 2017, at 22.47, Wolfgang Jeltsch wrote: >> >> Hi! >> >> I agree with you, Andrew, that types should have different names. >> However, (H)Refl is not a type. It is a data constructor; so it is a >> special kind of value and as such very similar to sym, trans, and >> friends. The similarity of Refl to the ordinary functions of the >> Heterogeneous module becomes even more obvious when considering that >> Refl is a proof, like sym, trans, and so on. >> >> All the best, >> Wolfgang >> >> Am Samstag, den 08.07.2017, 21:25 -0400 schrieb Andrew Martin: >>> Just wanted to weigh in with my two cents. I also prefer to use the >>> module system for the most part rather than prefixing function names >>> with something that indicates the data type they operate on. However, >>> when it comes to types, I would much rather they have different names. >>> I like that the data constructor of :~~: is HRefl. However, for the >>> functions sym, trans, etc., I would rather have a >>> Data.Type.Equality.Hetero that exports all of these without any kind >>> of prefixes on them. Then there's the question of where we export :~~: >>> from. It could be exported only from the Hetero module, or it could be >>> exported from both. >>> >>> Sent from my iPhone >>> >>>> >>>> On Jul 8, 2017, at 7:56 PM, Wolfgang Jeltsch >>> fo> wrote: >>>> >>>> Hi! >>>> >>>> Unfortunately, my wish has not been granted, as I wanted the data >>>> constructor of (:~~:) to be named Refl and (:~~:) to be defined in a >>>> separate module. I see that there are no heterogeneous versions of >>>> sym, >>>> trans, and so on in base at the moment. If they will be available at >>>> some time, how will they be called? Will they be named hsym, htrans, >>>> and >>>> so on? This would be awful, in my opinion. >>>> >>>> In Haskell, we have the module system for qualification. I very well >>>> understand the issues Julien Moutinho pointed out. For example, you >>>> cannot have a module that just reexports all the functions from >>>> Data.Sequence and Data.Map, because you would get name clashes. >>>> >>>> However, I think that the solution to these kinds of problems is to >>>> fix >>>> the module system. An idea would be to allow for exporting qualified >>>> names. Then a module could import Data.Sequence and Data.Map >>>> qualified >>>> as Seq and Map, respectively, and export Seq.empty, Map.empty, and >>>> so >>>> on. >>>> >>>> If we try to work around those issues with the module system by >>>> putting >>>> qualification into the actual identifiers in the form of single >>>> letters >>>> (like in mappend, HRef, and so on), we will be stuck with this >>>> workaround forever, even if the module system will be changed at >>>> some >>>> time, because identifiers in core libraries are typically not >>>> changed. >>>> Just imagine, we would have followed this practice for the >>>> containers >>>> package. We would have identifiers like “smap”, “munion”, >>>> “imintersection”, and so on. >>>> >>>> All the best, >>>> Wolfgang >>>> >>>> Am Freitag, den 07.07.2017, 08:15 -0700 schrieb Ryan Scott: >>>>> >>>>> Sorry for only just discovering this thread now. A lot of this >>>>> discussion is in fact moot, since (:~~:) already is in base! >>>>> Specifically, it's landing in Data.Type.Equality [1] in the next >>>>> version of base (bundled with GHC 8.2). Moreover, it's constructor >>>>> is >>>>> named HRefl, so your wish has been granted ;) >>>>> >>>>> As for why it's being introduced in base, it ended up being useful >>>>> for >>>>> the new Type-indexed Typeable that's also landing in GHC 8.2. In >>>>> particular, the eqTypeRep function [2] must return heterogeneous >>>>> equality (:~~:), not homogeneous equality (:~:), since it's >>>>> possible >>>>> that you'll compare two TypeReps with different kinds. >>>>> >>>>> Ryan S. >>>>> ----- >>>>> [1] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5 >>>>> f718d18fcaa66a:/libraries/base/Data/Type/Equality.hs#l37 >>>>> [2] http://git.haskell.org/ghc.git/blob/99adcc8804e91161b35ff1d0e5 >>>>> f718d18fcaa66a:/libraries/base/Data/Typeable/Internal.hs#l311>; >>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at cs.brynmawr.edu Mon Jul 10 12:58:10 2017 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Mon, 10 Jul 2017 08:58:10 -0400 Subject: Heterogeneous equality into base? In-Reply-To: References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> <1499629677.2497.247.camel@jeltsch.info> <78602EF8-3A8B-4B35-B18D-E96C6AC42FCE@iki.fi> Message-ID: <4DA5EE0D-4A68-4D95-93C1-C25F9B492321@cs.brynmawr.edu> > On Jul 9, 2017, at 8:31 PM, Edward Kmett wrote: > > Heterogenous equality is a form of what Conor McBride calls "John Major" equality. In a more general type theory, HRefl doesn't imply Refl! You can't show HRefl implies Refl in MLTT. This extra power is granted by dependent pattern matching most dependent type theories or in Haskell by the way we implement ~. In Haskell, today, it works out because we have "uniqueness of identity proofs" or "axiom K". This means that anything going on in the world of homotopy type theory today can't be used in Haskell directly as univalence and axiom k are inconsistent. > > Some work has been put into pattern matching in Agda without axiom K. Do I expect that folks are going to run out and implement it in Haskell? No, but in general I want to be very clear in my code when I rely upon this extra power that Haskell grants us kinda by accident or fiat today as those results don't transfer, and could be dangerous to assume if we decide to go in a different direction in the far flung future. This is all true, of course, but you'd be hard-pressed to detect or avoid all uses of Axiom K in Haskell. Note that (:~~:) is a perfectly ordinary GADT, and you (or a dependency of yours) might define a similar GADT that implicitly uses Axiom K when compared with MLTT. Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Mon Jul 10 13:57:31 2017 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 10 Jul 2017 09:57:31 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <4DA5EE0D-4A68-4D95-93C1-C25F9B492321@cs.brynmawr.edu> References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> <1499629677.2497.247.camel@jeltsch.info> <78602EF8-3A8B-4B35-B18D-E96C6AC42FCE@iki.fi> <4DA5EE0D-4A68-4D95-93C1-C25F9B492321@cs.brynmawr.edu> Message-ID: <34ED9D8D-F799-4F2F-9C43-8232330E9CF2@gmail.com> I definitely agree that it'd be difficult if not near impossible to fully root out, even if we did decide it was worth the pain, which is very much up for debate. Sent from my iPad > On Jul 10, 2017, at 8:58 AM, Richard Eisenberg wrote: > > >> On Jul 9, 2017, at 8:31 PM, Edward Kmett wrote: >> >> Heterogenous equality is a form of what Conor McBride calls "John Major" equality. In a more general type theory, HRefl doesn't imply Refl! You can't show HRefl implies Refl in MLTT. This extra power is granted by dependent pattern matching most dependent type theories or in Haskell by the way we implement ~. In Haskell, today, it works out because we have "uniqueness of identity proofs" or "axiom K". This means that anything going on in the world of homotopy type theory today can't be used in Haskell directly as univalence and axiom k are inconsistent. >> >> Some work has been put into pattern matching in Agda without axiom K. Do I expect that folks are going to run out and implement it in Haskell? No, but in general I want to be very clear in my code when I rely upon this extra power that Haskell grants us kinda by accident or fiat today as those results don't transfer, and could be dangerous to assume if we decide to go in a different direction in the far flung future. > > This is all true, of course, but you'd be hard-pressed to detect or avoid all uses of Axiom K in Haskell. Note that (:~~:) is a perfectly ordinary GADT, and you (or a dependency of yours) might define a similar GADT that implicitly uses Axiom K when compared with MLTT. > > Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Mon Jul 10 15:24:58 2017 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Mon, 10 Jul 2017 08:24:58 -0700 Subject: Heterogeneous equality into base? Message-ID: I also agree that we should keep HRefl a distinct name, and moreover, we should keep :~: and :~~: as distinct datatypes. I'm also on-board with the idea that we should introduce a separate Data.Type.Equality.Hetero module that reexports :~~: and defines heterogeneous counterparts for sym, trans, etc. from Data.Type.Equality. I don't have a strong opinion on how they should be named (e.g., sym vs. hsym). Ryan S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Jul 10 16:20:17 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 10 Jul 2017 12:20:17 -0400 Subject: Heterogeneous equality into base? In-Reply-To: References: Message-ID: There's another version of heterogeneous equality that takes its arguments in the other order. I'm not sure if this is generally useful enough to want to include. -- (:~~:) :: forall j k. j -> k -> * data OtherEquality :: forall j. j -> forall k. k -> Type where OtherRefl :: OtherEquality a a On Mon, Jul 10, 2017 at 11:24 AM, Ryan Scott wrote: > I also agree that we should keep HRefl a distinct name, and moreover, we > should keep :~: and :~~: as distinct datatypes. > > I'm also on-board with the idea that we should introduce a separate > Data.Type.Equality.Hetero module that reexports :~~: and defines > heterogeneous counterparts for sym, trans, etc. from Data.Type.Equality. I > don't have a strong opinion on how they should be named (e.g., sym vs. > hsym). > > Ryan S. > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > From rae at cs.brynmawr.edu Mon Jul 10 17:03:32 2017 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Mon, 10 Jul 2017 13:03:32 -0400 Subject: Heterogeneous equality into base? In-Reply-To: References: Message-ID: <987DD2C8-9315-4F9B-82D4-97751858B8BD@cs.brynmawr.edu> This OtherEquality is actually a tad bit more general, given that GHC can't (currently) reorder type indices. But would anyone take advantage of the generality? I tend to doubt it... Richard > On Jul 10, 2017, at 12:20 PM, David Feuer wrote: > > There's another version of heterogeneous equality that takes its > arguments in the other order. I'm not sure if this is generally useful > enough to want to include. > > -- (:~~:) :: forall j k. j -> k -> * > > data OtherEquality :: forall j. j -> forall k. k -> Type where > OtherRefl :: OtherEquality a a > > On Mon, Jul 10, 2017 at 11:24 AM, Ryan Scott wrote: >> I also agree that we should keep HRefl a distinct name, and moreover, we >> should keep :~: and :~~: as distinct datatypes. >> >> I'm also on-board with the idea that we should introduce a separate >> Data.Type.Equality.Hetero module that reexports :~~: and defines >> heterogeneous counterparts for sym, trans, etc. from Data.Type.Equality. I >> don't have a strong opinion on how they should be named (e.g., sym vs. >> hsym). >> >> Ryan S. >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From david.feuer at gmail.com Mon Jul 10 17:11:47 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 10 Jul 2017 13:11:47 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <987DD2C8-9315-4F9B-82D4-97751858B8BD@cs.brynmawr.edu> References: <987DD2C8-9315-4F9B-82D4-97751858B8BD@cs.brynmawr.edu> Message-ID: Well, I came up with another notion of heterogeneous equality (much, much more limited in practice): newtype HEqual (a :: j) (b :: k) = HEqual (forall (f :: forall l. l -> Type). f a -> f b) Implementing fromHEqual :: forall j k (a :: j) (b :: k). HEqual a b -> a :~~: b seems to require something like OtherEquality. I'm not sure what you mean about not being able to reorder type indices. OtherEquality can also be defined as a newtype around (:~~:): newtype OtherEquality :: forall j. j -> forall k. k -> Type where OtherEquality :: a :~~: q -> OtherEquality a q But perhaps you mean it's more convenient than :~~:? On Mon, Jul 10, 2017 at 1:03 PM, Richard Eisenberg wrote: > This OtherEquality is actually a tad bit more general, given that GHC can't (currently) reorder type indices. But would anyone take advantage of the generality? I tend to doubt it... > > Richard > >> On Jul 10, 2017, at 12:20 PM, David Feuer wrote: >> >> There's another version of heterogeneous equality that takes its >> arguments in the other order. I'm not sure if this is generally useful >> enough to want to include. >> >> -- (:~~:) :: forall j k. j -> k -> * >> >> data OtherEquality :: forall j. j -> forall k. k -> Type where >> OtherRefl :: OtherEquality a a >> >> On Mon, Jul 10, 2017 at 11:24 AM, Ryan Scott wrote: >>> I also agree that we should keep HRefl a distinct name, and moreover, we >>> should keep :~: and :~~: as distinct datatypes. >>> >>> I'm also on-board with the idea that we should introduce a separate >>> Data.Type.Equality.Hetero module that reexports :~~: and defines >>> heterogeneous counterparts for sym, trans, etc. from Data.Type.Equality. I >>> don't have a strong opinion on how they should be named (e.g., sym vs. >>> hsym). >>> >>> Ryan S. >>> >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > From ekmett at gmail.com Mon Jul 10 18:06:43 2017 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 10 Jul 2017 14:06:43 -0400 Subject: Heterogeneous equality into base? In-Reply-To: References: <987DD2C8-9315-4F9B-82D4-97751858B8BD@cs.brynmawr.edu> Message-ID: <4EE59A40-1C51-4C05-A70B-E8BD9E1F0958@gmail.com> Sent from my iPad > On Jul 10, 2017, at 1:11 PM, David Feuer wrote: > > Well, I came up with another notion of heterogeneous equality (much, > much more limited in practice): > > newtype HEqual (a :: j) (b :: k) = HEqual (forall (f :: forall l. l -> > Type). f a -> f b) This is "heterogeneous Leibnizian equality". > Implementing > > fromHEqual :: forall j k (a :: j) (b :: k). HEqual a b -> a :~~: b > seems to require something like OtherEquality. > > I'm not sure what you mean about not being able to reorder type > indices. OtherEquality can also be defined as a newtype around (:~~:): > > newtype OtherEquality :: forall j. j -> forall k. k -> Type where > OtherEquality :: a :~~: q -> OtherEquality a q > > But perhaps you mean it's more convenient than :~~:? > >> On Mon, Jul 10, 2017 at 1:03 PM, Richard Eisenberg wrote: >> This OtherEquality is actually a tad bit more general, given that GHC can't (currently) reorder type indices. But would anyone take advantage of the generality? I tend to doubt it... >> >> Richard >> >>> On Jul 10, 2017, at 12:20 PM, David Feuer wrote: >>> >>> There's another version of heterogeneous equality that takes its >>> arguments in the other order. I'm not sure if this is generally useful >>> enough to want to include. >>> >>> -- (:~~:) :: forall j k. j -> k -> * >>> >>> data OtherEquality :: forall j. j -> forall k. k -> Type where >>> OtherRefl :: OtherEquality a a >>> >>>> On Mon, Jul 10, 2017 at 11:24 AM, Ryan Scott wrote: >>>> I also agree that we should keep HRefl a distinct name, and moreover, we >>>> should keep :~: and :~~: as distinct datatypes. >>>> >>>> I'm also on-board with the idea that we should introduce a separate >>>> Data.Type.Equality.Hetero module that reexports :~~: and defines >>>> heterogeneous counterparts for sym, trans, etc. from Data.Type.Equality. I >>>> don't have a strong opinion on how they should be named (e.g., sym vs. >>>> hsym). >>>> >>>> Ryan S. >>>> >>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From david.feuer at gmail.com Mon Jul 10 18:18:23 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 10 Jul 2017 14:18:23 -0400 Subject: Heterogeneous equality into base? In-Reply-To: <4EE59A40-1C51-4C05-A70B-E8BD9E1F0958@gmail.com> References: <987DD2C8-9315-4F9B-82D4-97751858B8BD@cs.brynmawr.edu> <4EE59A40-1C51-4C05-A70B-E8BD9E1F0958@gmail.com> Message-ID: That's the idea I was after. Is it good for anything? On Jul 10, 2017 2:06 PM, "Edward Kmett" wrote: > > > Sent from my iPad > > > On Jul 10, 2017, at 1:11 PM, David Feuer wrote: > > > > Well, I came up with another notion of heterogeneous equality (much, > > much more limited in practice): > > > > newtype HEqual (a :: j) (b :: k) = HEqual (forall (f :: forall l. l -> > > Type). f a -> f b) > > This is "heterogeneous Leibnizian equality". > > > Implementing > > > > fromHEqual :: forall j k (a :: j) (b :: k). HEqual a b -> a :~~: b > > seems to require something like OtherEquality. > > > > I'm not sure what you mean about not being able to reorder type > > indices. OtherEquality can also be defined as a newtype around (:~~:): > > > > newtype OtherEquality :: forall j. j -> forall k. k -> Type where > > OtherEquality :: a :~~: q -> OtherEquality a q > > > > But perhaps you mean it's more convenient than :~~:? > > > >> On Mon, Jul 10, 2017 at 1:03 PM, Richard Eisenberg > wrote: > >> This OtherEquality is actually a tad bit more general, given that GHC > can't (currently) reorder type indices. But would anyone take advantage of > the generality? I tend to doubt it... > >> > >> Richard > >> > >>> On Jul 10, 2017, at 12:20 PM, David Feuer > wrote: > >>> > >>> There's another version of heterogeneous equality that takes its > >>> arguments in the other order. I'm not sure if this is generally useful > >>> enough to want to include. > >>> > >>> -- (:~~:) :: forall j k. j -> k -> * > >>> > >>> data OtherEquality :: forall j. j -> forall k. k -> Type where > >>> OtherRefl :: OtherEquality a a > >>> > >>>> On Mon, Jul 10, 2017 at 11:24 AM, Ryan Scott > wrote: > >>>> I also agree that we should keep HRefl a distinct name, and moreover, > we > >>>> should keep :~: and :~~: as distinct datatypes. > >>>> > >>>> I'm also on-board with the idea that we should introduce a separate > >>>> Data.Type.Equality.Hetero module that reexports :~~: and defines > >>>> heterogeneous counterparts for sym, trans, etc. from > Data.Type.Equality. I > >>>> don't have a strong opinion on how they should be named (e.g., sym vs. > >>>> hsym). > >>>> > >>>> Ryan S. > >>>> > >>>> _______________________________________________ > >>>> Libraries mailing list > >>>> Libraries at haskell.org > >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > >>>> > >>> _______________________________________________ > >>> Libraries mailing list > >>> Libraries at haskell.org > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > >> > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Mon Jul 10 18:38:01 2017 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 10 Jul 2017 14:38:01 -0400 Subject: Heterogeneous equality into base? In-Reply-To: References: <987DD2C8-9315-4F9B-82D4-97751858B8BD@cs.brynmawr.edu> <4EE59A40-1C51-4C05-A70B-E8BD9E1F0958@gmail.com> Message-ID: <19033EAE-1D00-43EF-A983-E698DB2952F4@gmail.com> Not sure. You can go back and forth between normal Leibnizian equality and :~: in Haskell. The notion of an Equality in lens can be seen as a Leibnizian equality, just with an extra set of parameters and encoding it that way lets us compose them with (.) from the Prelude. I suppose if you stripped off your newtype you could do the same here. Other than that? If we didn't have ~ or ~~ already it'd bring something to the table as it provides you some ability to talk about type equality without them in your language. But we do have them. Sent from my iPhone > On Jul 10, 2017, at 2:18 PM, David Feuer wrote: > > That's the idea I was after. Is it good for anything? > >> On Jul 10, 2017 2:06 PM, "Edward Kmett" wrote: >> >> >> Sent from my iPad >> >> > On Jul 10, 2017, at 1:11 PM, David Feuer wrote: >> > >> > Well, I came up with another notion of heterogeneous equality (much, >> > much more limited in practice): >> > >> > newtype HEqual (a :: j) (b :: k) = HEqual (forall (f :: forall l. l -> >> > Type). f a -> f b) >> >> This is "heterogeneous Leibnizian equality". >> >> > Implementing >> > >> > fromHEqual :: forall j k (a :: j) (b :: k). HEqual a b -> a :~~: b >> > seems to require something like OtherEquality. >> > >> > I'm not sure what you mean about not being able to reorder type >> > indices. OtherEquality can also be defined as a newtype around (:~~:): >> > >> > newtype OtherEquality :: forall j. j -> forall k. k -> Type where >> > OtherEquality :: a :~~: q -> OtherEquality a q >> > >> > But perhaps you mean it's more convenient than :~~:? >> > >> >> On Mon, Jul 10, 2017 at 1:03 PM, Richard Eisenberg wrote: >> >> This OtherEquality is actually a tad bit more general, given that GHC can't (currently) reorder type indices. But would anyone take advantage of the generality? I tend to doubt it... >> >> >> >> Richard >> >> >> >>> On Jul 10, 2017, at 12:20 PM, David Feuer wrote: >> >>> >> >>> There's another version of heterogeneous equality that takes its >> >>> arguments in the other order. I'm not sure if this is generally useful >> >>> enough to want to include. >> >>> >> >>> -- (:~~:) :: forall j k. j -> k -> * >> >>> >> >>> data OtherEquality :: forall j. j -> forall k. k -> Type where >> >>> OtherRefl :: OtherEquality a a >> >>> >> >>>> On Mon, Jul 10, 2017 at 11:24 AM, Ryan Scott wrote: >> >>>> I also agree that we should keep HRefl a distinct name, and moreover, we >> >>>> should keep :~: and :~~: as distinct datatypes. >> >>>> >> >>>> I'm also on-board with the idea that we should introduce a separate >> >>>> Data.Type.Equality.Hetero module that reexports :~~: and defines >> >>>> heterogeneous counterparts for sym, trans, etc. from Data.Type.Equality. I >> >>>> don't have a strong opinion on how they should be named (e.g., sym vs. >> >>>> hsym). >> >>>> >> >>>> Ryan S. >> >>>> >> >>>> _______________________________________________ >> >>>> Libraries mailing list >> >>>> Libraries at haskell.org >> >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >>>> >> >>> _______________________________________________ >> >>> Libraries mailing list >> >>> Libraries at haskell.org >> >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> >> > _______________________________________________ >> > Libraries mailing list >> > Libraries at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From wolfgang-it at jeltsch.info Mon Jul 10 18:57:45 2017 From: wolfgang-it at jeltsch.info (Wolfgang Jeltsch) Date: Mon, 10 Jul 2017 21:57:45 +0300 Subject: Heterogeneous equality into base? In-Reply-To: References: Message-ID: <1499713065.2497.298.camel@jeltsch.info> Why not define (:~~:) in Data.Type.Equality.Heterogeneous in the first place instead of defining it in Data.Type.Equality and reexporting it from Data.Type.Equality.Heterogeneous? All the best, Wolfgang Am Montag, den 10.07.2017, 08:24 -0700 schrieb Ryan Scott: > I also agree that we should keep HRefl a distinct name, and moreover, > we should keep :~: and :~~: as distinct datatypes. > > I'm also on-board with the idea that we should introduce a separate > Data.Type.Equality.Hetero module that reexports :~~: and defines > heterogeneous counterparts for sym, trans, etc. from > Data.Type.Equality. I don't have a strong opinion on how they should > be named (e.g., sym vs. hsym). > > Ryan S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Tue Jul 11 03:50:40 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 10 Jul 2017 23:50:40 -0400 Subject: Removing bitSize Message-ID: The long-deprecated bitSize method of the Bits class is slated to be removed in base-4.11 (GHC 8.4). There is one remaining question: should we replace it with a *function* by that name with a FiniteBits constraint? I don't feel very strongly either way, but Ryan Scott seems in favor and Edward Kmett seems opposed. So it seems best to bring it to the libraries list and let the CLC make the call. If the function is added, it would look like this: bitSize :: FiniteBits a => a -> Int bitSize = finiteBitSize The biggest downside I see is that we might one day want to reuse the name for something with a better type, such as bitSize :: forall proxy a. FiniteBits a => proxy a -> Int bitSize _ = finiteBitSize (undefined :: a) or bitSize :: forall a. FiniteBits a => Tagged a Int bitSize = Tagged (finiteBitSize (undefined :: a)) or (with type applications) bitSize :: forall a. FiniteBits a => Int bitSize = finiteBitSize (undefined :: a) Thanks, David Feuer From ivan.miljenovic at gmail.com Tue Jul 11 04:51:32 2017 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Tue, 11 Jul 2017 14:51:32 +1000 Subject: Removing bitSize In-Reply-To: References: Message-ID: On 11 July 2017 at 13:50, David Feuer wrote: > The long-deprecated bitSize method of the Bits class is slated to be > removed in base-4.11 (GHC 8.4). There is one remaining question: > should we replace it with a *function* by that name with a FiniteBits > constraint? I don't feel very strongly either way, but Ryan Scott > seems in favor and Edward Kmett seems opposed. So it seems best to > bring it to the libraries list and let the CLC make the call. As it's already DEPRECATED, I think it should be removed for a release first (in case anyone is still using it to help drive home the change in behaviour) before any alternative with that name is added. -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From lemming at henning-thielemann.de Tue Jul 11 13:38:24 2017 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Tue, 11 Jul 2017 15:38:24 +0200 (CEST) Subject: Removing bitSize In-Reply-To: References: Message-ID: On Mon, 10 Jul 2017, David Feuer wrote: > The long-deprecated bitSize method of the Bits class is slated to be > removed in base-4.11 (GHC 8.4). There is one remaining question: > should we replace it with a *function* by that name with a FiniteBits > constraint? I don't feel very strongly either way, but Ryan Scott > seems in favor and Edward Kmett seems opposed. So it seems best to > bring it to the libraries list and let the CLC make the call. If the > function is added, it would look like this: > > bitSize :: FiniteBits a => a -> Int > bitSize = finiteBitSize I'd like to have a solution that allows me to make my code compilable by many GHC versions. The top-level function with an almost identical signature seems to fit that requirement best. The solutions using Proxy, Tagged, and TypeApplication are nice, too, but since there are many sensible choices there might also be many functions like bitSizeProxy, bitSizeTagged, bitSizeTypeApp. From yom at artyom.me Tue Jul 18 11:25:55 2017 From: yom at artyom.me (Artyom) Date: Tue, 18 Jul 2017 14:25:55 +0300 Subject: Heterogeneous equality into base? In-Reply-To: References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> Message-ID: > In a more general type theory, HRefl doesn't imply Refl! You can't show HRefl implies Refl in MLTT. This extra power is granted by dependent pattern matching most dependent type theories or in Haskell by the way we implement ~. In Haskell, today, it works out because we have "uniqueness of identity proofs" or "axiom K". What does it mean that HRefl doesn't imply Refl? I tried to google Axiom K but quickly got lost :( I naively thought that HRefl is just Refl but without the “kinds have to be equal or else GHC will bark” restriction. Is there some situation (in current Haskell or some variant of Haskell) where we can have HRefl for a pair of types but not Refl? From oleg.grenrus at iki.fi Tue Jul 18 11:41:42 2017 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Tue, 18 Jul 2017 14:41:42 +0300 Subject: Heterogeneous equality into base? In-Reply-To: References: <1499558162.2497.231.camel@jeltsch.info> <0F46312D-A44C-46E1-8C75-5970EC1A1CAB@gmail.com> Message-ID: <125dcc44-2ddb-6731-de14-671a482cfb2b@iki.fi> Adam Chipala's CPDT book has a good chapter, http://adam.chlipala.net/cpdt/html/Equality.html It talks about Axiom K, and Jonh Mayor equality - Oleg On 18.07.2017 14:25, Artyom wrote: >> In a more general type theory, HRefl doesn't imply Refl! You can't > show HRefl implies Refl in MLTT. This extra power is granted by > dependent pattern matching most dependent type theories or in Haskell by > the way we implement ~. In Haskell, today, it works out because we have > "uniqueness of identity proofs" or "axiom K". > > What does it mean that HRefl doesn't imply Refl? I tried to google Axiom > K but quickly got lost :( > > I naively thought that HRefl is just Refl but without the “kinds have to > be equal or else GHC will bark” restriction. Is there some situation (in > current Haskell or some variant of Haskell) where we can have HRefl for > a pair of types but not Refl? > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: OpenPGP digital signature URL: From andrew.thaddeus at gmail.com Thu Jul 20 15:50:33 2017 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Thu, 20 Jul 2017 11:50:33 -0400 Subject: Exporting ioToST from Control.Monad.ST Message-ID: There's a function stToIO that is defined in GHC.IO and exported from Control.Monad.ST. There's another function, ioToST, that's also defined in IO, but it isn't exported from Control.Monad.ST. I propose that it be exported from Control.Monad.ST. -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Thu Jul 20 16:02:07 2017 From: david.feuer at gmail.com (David Feuer) Date: Thu, 20 Jul 2017 12:02:07 -0400 Subject: Exporting ioToST from Control.Monad.ST In-Reply-To: References: Message-ID: This seems to commit to ST and IO really being the same. Does stToIO already make this commitment? I can't tell, but if not, I oppose making that commitment in the "public" interface. On Jul 20, 2017 11:51 AM, "Andrew Martin" wrote: There's a function stToIO that is defined in GHC.IO and exported from Control.Monad.ST. There's another function, ioToST, that's also defined in IO, but it isn't exported from Control.Monad.ST. I propose that it be exported from Control.Monad.ST. -- -Andrew Thaddeus Martin _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Thu Jul 20 17:36:47 2017 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Thu, 20 Jul 2017 13:36:47 -0400 Subject: Exporting ioToST from Control.Monad.ST In-Reply-To: References: Message-ID: My understanding is that `ST RealWorld` and `IO` are genuinely the same thing. But I'd want someone with better understanding to corroborate that claim. On Thu, Jul 20, 2017 at 12:02 PM, David Feuer wrote: > This seems to commit to ST and IO really being the same. Does stToIO > already make this commitment? I can't tell, but if not, I oppose making > that commitment in the "public" interface. > > On Jul 20, 2017 11:51 AM, "Andrew Martin" > wrote: > > There's a function stToIO that is defined in GHC.IO and exported from > Control.Monad.ST. There's another function, ioToST, that's also defined > in IO, but it isn't exported from Control.Monad.ST. I propose that it be > exported from Control.Monad.ST. > > -- > -Andrew Thaddeus Martin > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Thu Jul 20 17:57:35 2017 From: david.feuer at gmail.com (David Feuer) Date: Thu, 20 Jul 2017 13:57:35 -0400 Subject: Exporting ioToST from Control.Monad.ST In-Reply-To: References: Message-ID: IO and ST RealWorld are indeed represented the same--in today's GHC. It would be possible to implement the same ST interface differently (e.g., as an operational monad). Adding ioToST to the public interface commits not only GHC, but also future Haskell implementations, to a similar representation. Note: I recently noticed a real difference between IO and ST with regard to strictness analysis. In IO, m >>= undefined is *not* bottom: it may perform an observable action. In ST, it is bottom; anything it mutates is guaranteed to vanish in a puff of smoke. So assuming that these have the same representation actually introduces some complications for optimization. On Jul 20, 2017 1:36 PM, "Andrew Martin" wrote: My understanding is that `ST RealWorld` and `IO` are genuinely the same thing. But I'd want someone with better understanding to corroborate that claim. On Thu, Jul 20, 2017 at 12:02 PM, David Feuer wrote: > This seems to commit to ST and IO really being the same. Does stToIO > already make this commitment? I can't tell, but if not, I oppose making > that commitment in the "public" interface. > > On Jul 20, 2017 11:51 AM, "Andrew Martin" > wrote: > > There's a function stToIO that is defined in GHC.IO and exported from > Control.Monad.ST. There's another function, ioToST, that's also defined > in IO, but it isn't exported from Control.Monad.ST. I propose that it be > exported from Control.Monad.ST. > > -- > -Andrew Thaddeus Martin > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben.franksen at online.de Wed Jul 26 21:51:12 2017 From: ben.franksen at online.de (Ben Franksen) Date: Wed, 26 Jul 2017 23:51:12 +0200 Subject: Data.List.singleton Message-ID: ...is a function that seems to be missing from base. It is trivial, of course, but still would be nice to have for symmetry with the modules in container. (apologies if this has been discussed before) Cheers Ben From abela at chalmers.se Thu Jul 27 07:10:55 2017 From: abela at chalmers.se (Andreas Abel) Date: Thu, 27 Jul 2017 09:10:55 +0200 Subject: Data.List.singleton In-Reply-To: References: Message-ID: <81ef1ae8-1b9a-8f05-d69a-b46589bfecd7@chalmers.se> +1. "singleton" is clearly more readable in code than the orangutan face (:[]). On 26.07.2017 23:51, Ben Franksen wrote: > ...is a function that seems to be missing from base. It is trivial, of > course, but still would be nice to have for symmetry with the modules in > container. > > (apologies if this has been discussed before) > > Cheers > Ben -- Andreas Abel <>< Du bist der geliebte Mensch. Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden andreas.abel at gu.se http://www.cse.chalmers.se/~abela/ From lemming at henning-thielemann.de Thu Jul 27 07:14:03 2017 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Thu, 27 Jul 2017 09:14:03 +0200 (CEST) Subject: Data.List.singleton In-Reply-To: <81ef1ae8-1b9a-8f05-d69a-b46589bfecd7@chalmers.se> References: <81ef1ae8-1b9a-8f05-d69a-b46589bfecd7@chalmers.se> Message-ID: On Thu, 27 Jul 2017, Andreas Abel wrote: > +1. "singleton" is clearly more readable in code than the orangutan > face (:[]). An alternative would be Applicative.pure or Monad.return. But yes, List.singleton is still more readable. From david.feuer at gmail.com Thu Jul 27 22:45:40 2017 From: david.feuer at gmail.com (David Feuer) Date: Thu, 27 Jul 2017 18:45:40 -0400 Subject: Discussion: Allow custom constraint for elem in Foldable Message-ID: The Foldable class offers the method elem :: Eq a => a -> t a -> Bool Unfortunately, this is really awful for sets, hash maps, etc. See https://stackoverflow.com/questions/45361801/implement-an-olog-n-foldable-elem-for-binary-search-trees-in-haskell#45362110 for an example. We could fix it, kinda: class Foldable t where type ElemConstr t :: * -> Constraint type ElemConstr t = Eq elem :: ElemConstr t a => a -> t a -> Bool default elem :: (ElemConstr t ~ Eq, Eq a) => a -> t a -> Bool One might legitimately complain that such a wild type is ad hoc, but one might counter that complaint by saying that most of Foldable is already ad hoc. David From emertens at gmail.com Thu Jul 27 23:35:13 2017 From: emertens at gmail.com (Eric Mertens) Date: Thu, 27 Jul 2017 16:35:13 -0700 Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: References: Message-ID: <9AFD09E3-FE63-4237-BEBE-6EAC6493A978@gmail.com> I would prefer to see designs for something like this explored in a separate package before we worried about changing base’s Foldable class. > On Jul 27, 2017, at 3:45 PM, David Feuer wrote: > > The Foldable class offers the method > > elem :: Eq a => a -> t a -> Bool > > Unfortunately, this is really awful for sets, hash maps, etc. See > https://stackoverflow.com/questions/45361801/implement-an-olog-n-foldable-elem-for-binary-search-trees-in-haskell#45362110 > for an example. We could fix it, kinda: > > class Foldable t where > type ElemConstr t :: * -> Constraint > type ElemConstr t = Eq > > elem :: ElemConstr t a => a -> t a -> Bool > default elem :: (ElemConstr t ~ Eq, Eq a) => a -> t a -> Bool > > One might legitimately complain that such a wild type is ad hoc, but > one might counter that complaint by saying that most of Foldable is > already ad hoc. > > David > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From mail at nh2.me Thu Jul 27 23:37:50 2017 From: mail at nh2.me (=?UTF-8?Q?Niklas_Hamb=c3=bcchen?=) Date: Fri, 28 Jul 2017 01:37:50 +0200 Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: References: Message-ID: <6a054e75-f728-fd53-45b9-cb15b453032b@nh2.me> On 28/07/17 00:45, David Feuer wrote: > Unfortunately, this is really awful for sets, hash maps, etc. If this is done at some point, I suppose we could fix `nub` in the same way? From david.feuer at gmail.com Thu Jul 27 23:58:45 2017 From: david.feuer at gmail.com (David Feuer) Date: Thu, 27 Jul 2017 19:58:45 -0400 Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: <9AFD09E3-FE63-4237-BEBE-6EAC6493A978@gmail.com> References: <9AFD09E3-FE63-4237-BEBE-6EAC6493A978@gmail.com> Message-ID: What would that exploration look like in your view? Could you sketch a path? On Jul 27, 2017 7:35 PM, "Eric Mertens" wrote: I would prefer to see designs for something like this explored in a separate package before we worried about changing base’s Foldable class. > On Jul 27, 2017, at 3:45 PM, David Feuer wrote: > > The Foldable class offers the method > > elem :: Eq a => a -> t a -> Bool > > Unfortunately, this is really awful for sets, hash maps, etc. See > https://stackoverflow.com/questions/45361801/implement- an-olog-n-foldable-elem-for-binary-search-trees-in-haskell#45362110 > for an example. We could fix it, kinda: > > class Foldable t where > type ElemConstr t :: * -> Constraint > type ElemConstr t = Eq > > elem :: ElemConstr t a => a -> t a -> Bool > default elem :: (ElemConstr t ~ Eq, Eq a) => a -> t a -> Bool > > One might legitimately complain that such a wild type is ad hoc, but > one might counter that complaint by saying that most of Foldable is > already ad hoc. > > David > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Fri Jul 28 00:01:33 2017 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Fri, 28 Jul 2017 10:01:33 +1000 Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: <6a054e75-f728-fd53-45b9-cb15b453032b@nh2.me> References: <6a054e75-f728-fd53-45b9-cb15b453032b@nh2.me> Message-ID: On 28 July 2017 at 09:37, Niklas Hambüchen wrote: > On 28/07/17 00:45, David Feuer wrote: >> Unfortunately, this is really awful for sets, hash maps, etc. > If this is done at some point, I suppose we could fix `nub` in the same way? I'd prefer we have a "needs only Eq" function like nub, as I've used it in the past. -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From carter.schonwald at gmail.com Fri Jul 28 00:25:12 2017 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 27 Jul 2017 20:25:12 -0400 Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: <9AFD09E3-FE63-4237-BEBE-6EAC6493A978@gmail.com> References: <9AFD09E3-FE63-4237-BEBE-6EAC6493A978@gmail.com> Message-ID: agreed. this needs to be tested out in a user space lib first. On Thu, Jul 27, 2017 at 7:35 PM, Eric Mertens wrote: > I would prefer to see designs for something like this explored in a > separate package before we worried about changing base’s Foldable class. > > > On Jul 27, 2017, at 3:45 PM, David Feuer wrote: > > > > The Foldable class offers the method > > > > elem :: Eq a => a -> t a -> Bool > > > > Unfortunately, this is really awful for sets, hash maps, etc. See > > https://stackoverflow.com/questions/45361801/implement- > an-olog-n-foldable-elem-for-binary-search-trees-in-haskell#45362110 > > for an example. We could fix it, kinda: > > > > class Foldable t where > > type ElemConstr t :: * -> Constraint > > type ElemConstr t = Eq > > > > elem :: ElemConstr t a => a -> t a -> Bool > > default elem :: (ElemConstr t ~ Eq, Eq a) => a -> t a -> Bool > > > > One might legitimately complain that such a wild type is ad hoc, but > > one might counter that complaint by saying that most of Foldable is > > already ad hoc. > > > > David > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Jul 28 00:49:16 2017 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 27 Jul 2017 20:49:16 -0400 Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: References: <9AFD09E3-FE63-4237-BEBE-6EAC6493A978@gmail.com> Message-ID: i wasnt aware of such guidelines for the libraries list constrained monads/ functors are still an area of study / experimentation, they need experimentation and more community knowledge before they land in base for core type classes On Thu, Jul 27, 2017 at 8:37 PM, David Feuer wrote: > Off-list: Repeating what Eric Mertens said does not contribute to the > discussion. Perhaps you can offer an answer to my follow-up question to him. > > On Jul 27, 2017 8:26 PM, "Carter Schonwald" > wrote: > >> agreed. >> >> this needs to be tested out in a user space lib first. >> >> >> On Thu, Jul 27, 2017 at 7:35 PM, Eric Mertens wrote: >> >>> I would prefer to see designs for something like this explored in a >>> separate package before we worried about changing base’s Foldable class. >>> >>> > On Jul 27, 2017, at 3:45 PM, David Feuer >>> wrote: >>> > >>> > The Foldable class offers the method >>> > >>> > elem :: Eq a => a -> t a -> Bool >>> > >>> > Unfortunately, this is really awful for sets, hash maps, etc. See >>> > https://stackoverflow.com/questions/45361801/implement-an-ol >>> og-n-foldable-elem-for-binary-search-trees-in-haskell#45362110 >>> > for an example. We could fix it, kinda: >>> > >>> > class Foldable t where >>> > type ElemConstr t :: * -> Constraint >>> > type ElemConstr t = Eq >>> > >>> > elem :: ElemConstr t a => a -> t a -> Bool >>> > default elem :: (ElemConstr t ~ Eq, Eq a) => a -> t a -> Bool >>> > >>> > One might legitimately complain that such a wild type is ad hoc, but >>> > one might counter that complaint by saying that most of Foldable is >>> > already ad hoc. >>> > >>> > David >>> > _______________________________________________ >>> > Libraries mailing list >>> > Libraries at haskell.org >>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >> >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Fri Jul 28 04:19:01 2017 From: ekmett at gmail.com (Edward Kmett) Date: Fri, 28 Jul 2017 00:19:01 -0400 Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: References: Message-ID: On Thu, Jul 27, 2017 at 6:45 PM, David Feuer wrote: > One might legitimately complain that such a wild type is ad hoc, but > one might counter that complaint by saying that most of Foldable is > already ad hoc. My feelings largely echo Eric's in this regard. Ultimately, the difference is that the rest of Foldable exists in a form that can be standardized as part of Haskell' without requiring us to be able to describe how type families, equality constraints, constraint kinds, and default signatures work and also standardize them. The last one of which being something that I'd say we really don't want in the language standard as it causes all sorts of contortions about where you put code by virtue of information flowing the wrong way, and all of which are highly ghc specific. Moreover, it interacts with non-trivial awkwardness with many of the more complicated existing Foldable instances, e.g. Product, Sum, or really, almost anybody else's Foldable instance that glues together more than one 'f' pretty much then has to override this member. I'm pretty strongly -1 on changing `elem` in this manner. -Edward -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Fri Jul 28 06:42:57 2017 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 28 Jul 2017 08:42:57 +0200 (CEST) Subject: Discussion: Allow custom constraint for elem in Foldable In-Reply-To: References: Message-ID: On Thu, 27 Jul 2017, David Feuer wrote: > The Foldable class offers the method > > elem :: Eq a => a -> t a -> Bool > > Unfortunately, this is really awful for sets, hash maps, etc. See > https://stackoverflow.com/questions/45361801/implement-an-olog-n-foldable-elem-for-binary-search-trees-in-haskell#45362110 > for an example. I'd prefer to keep Foldable Haskell-98. You may introduce methods with advanced types in a sub-class. I also think that the Set type does not perfectly fit to Foldable. Most Set methods require Ord constraint, but Set.toList does not. Only this allows to have instance Foldable Set. This looks to me like an implementation detail. E.g. for Vector.Storable this trick does not work. You cannot omit the Storable constraint in Vector.toList.