Ryan,

Unfortunately, yes, you are understanding that correctly.

The reason I qualified it with "monomorphic only" is that, I want to avoid 
breakage that would render the extension practically unusable in real code.

Let's say I right now have:

foo :: Num a => [a] -> [a]
foo = map (+1)

I have two options 1) we compile this as currently using fromIntegral and it 
WILL break for Even or 2) we reject any polymorphic use of literals like this. 
Given the amount of numerical code relying on the polymorphism of Num, I think 
the option of not being able to compile Num polymorphic code is completely out 
of the question. Almost no application  would work.

I would advocate in favour of not requiring an IsList/IsString instance for the 
validation class, this would allow you to write a conversion that ONLY converts 
literals in a validated way and will never successfully convert literals 
without the extension, since with the extension disabled GHC would try to use 
the fromList/fromString from the IsString/IsList classes which do not exist.

Unfortunately, given how deeply fromIntegral is tied to the Num class I don't 
see any way to achieve the same for Num. The only option would be to not make 
Even an instance of Num, that way the same trick as above could work. Removing 
fromIntegral from Num is obviously not going to happen and without doing that I 
don't see how we could prevent someone using fromIntegral manually to convert 
to Even in a way that won't break Num polymorphic functions. If you have any 
ideas on how to tackle this, I'm all open to hearing them!

I agree with you that this is ugly, but I console myself with the thought that 
being able to check all monomorphic literals is already a drastic improvement 
over the current state. And in the case of lists and strings we could actually 
ensure that things work well, since almost no one writes "IsString polymorphic" 
code.

Cheers,
Merijn

> On 6 Feb 2015, at 16:59, Ryan Trinkle <ryan.trin...@gmail.com> wrote:
> 
> I think the idea of compile-time validation for overloaded literals is 
> fantastic, and doing it with nicer syntax than quasiquoting would really 
> improve things.  However, I'm a bit confused about specifically how the 
> requirement that it be monomorphic will play into this.  For example, if I 
> have:
> 
> x = 1
> 
> Presumably this will compile, and give a run-time error if I ever instantiate 
> its type to Even.  However, if I have:
> 
> x :: Even
> x = 1
> 
> it will fail to compile?  Furthermore, if I have the former, and type 
> inference determines that its type is Even, it sounds like that will also 
> fail to compile, but if type inference determines that its type is forall a. 
> Nat a => a, then it will successfully compile and then fail at runtime.
> 
> Am I understanding this correctly?
> 
> 
> Ryan
> 
> On Fri, Feb 6, 2015 at 8:55 AM, Erik Hesselink <hessel...@gmail.com> wrote:
> On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese
> <dominique.devri...@cs.kuleuven.be> wrote:
> > Agreed.  For the idea to scale, good support for type-level
> > programming with Integers/Strings/... is essential.  Something else
> > that would be useful is an unsatisfiable primitive constraint
> > constructor `UnsatisfiableConstraint :: String -> Constraint` that can
> > be used to generate custom error messages. Then one could write
> > something like
> >
> >   type family MustBeTrue (t :: Bool) (error :: String) :: Constraint
> >   type family MustBeTrue True _ = ()
> >   type family MustBeTrue False error = UnsatisfiableConstraint error
> >
> >   type family MustBeEven (n :: Nat) :: Constraint
> >   type family MustBeEven n = MustBeTrue (IsEven n) ("Error in Even
> > literal :'" ++ show n ++ "' is not even!")
> >
> >   instance (KnownNat n, MustBeEven n) => HasIntegerLiteral Even n where ...
> 
> Note that there is a trick to fake this with current GHC: you can
> write an equality constraint that is false, involving the type level
> string:
> 
> >   type family MustBeTrue False error = (() ~ error)
> 
> Erik
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Attachment: signature.asc
Description: Message signed with OpenPGP using GPGMail

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

Reply via email to