Re: Proposal: ValidateMonoLiterals - Initial bikeshed discussion

Assuming a separate syntax, I believe that the criterion would be as simple
as ensuring that no ValidateFoo constraints are left outstanding. The
syntax would add the relevant validate call, and type variables involved in
a ValidateFoo constraint would not be generalizable, and would have to be
defaulted or inferred from elsewhere, similar to the monomorphism
restriction. I'm not sure how difficult that would be to implement.
I'm not terribly gung ho on this, though. It feels very ad hoc. Making
validation vs. non-validation syntactic rather than just based on
polymorphism seems somewhat less so, though; so I'd prefer that direction.
Finding unused syntax is always a problem, of course.
On Fri, Feb 6, 2015 at 11:38 AM, Ryan Trinkle
My greatest concern here would be that, as an application is maintained, a literal might go from monomorphic to polymorphic, or vice versa, without anybody noticing. It sounds like this could result in a value silently becoming partial, which would be a big problem for application stability; in the opposite case - a partial value becoming a compile-time error - I am somewhat less concerned, but it could still be confusing and disruptive.
I would prefer that there be some syntactic indication that I want my literal to be checked at compile time. This syntax could also add whatever monomorphism requirement is needed, and then it would become a compile-time error for the value to become polymorphic. I don't know nearly enough about the type system to know whether this is possible.
Also, it seems to me that it might not be so clean as "monomorphic" versus "polymorphic". For example, suppose I have this:
newtype PostgresTableName s = PostgresTableName String
where 's' is a phantom type representing the DB schema that the name lives in. The validation function is independent of the schema - it simply fails if there are illegal characters in the name, or if the name is too long. So, ideally, ("foo\0bar" :: forall s. PostgresTableName s) would fail at compile time, despite being polymorphic.
Ryan
On Fri, Feb 6, 2015 at 11:16 AM, Merijn Verstraaten < merijn@inconsistent.nl> wrote:
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
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
wrote: On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese 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
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

If we go for a separate syntax, what do we gain over normal quasiquotes or $$(validate x)? Sure, literals could be made a little more beautiful, but I'm not sure it justifies stealing more syntax (and what would that syntax be?). Without a separate syntax, I'm not sure I understand the original proposal. The wiki page says "GHC would replace fromString/fromInteger/fromList expressions originating from literals with a Typed TH splice along the lines of validate for all monomorphic cases." What does "all monomorphic cases" mean? Is the idea what GHC would typecheck an expression involving a literal integer, determine that the occurrence had type Even, then evaluate the TH splice *after* typechecking? Whereas if the occurrence had a non-ground type, it would do something else? None of this is particularly persuasive, I'm afraid. Is it worthwhile introducing something new just to avoid having to write a quasiquote? I *am* attracted to the idea of indexed classes in place of IsString/Num class KnownSymbol s => IsIndexedString (a :: *) (s :: Symbol) where fromIndexedString :: a class KnownInteger i => IsIndexedInteger (a :: *) (i :: Integer) where fromIndexedInteger :: a These have a smooth upgrade path from the existing class instances via default fromIndexedString :: (KnownSymbol s, IsString a) => a fromIndexedString = fromString (symbolVal (Proxy :: Proxy s)) default fromIndexedInteger :: (KnownInteger i, Num a) => a fromIndexedInteger = fromInteger (integerVal (Proxy :: Proxy i)) and other instances can take advantage of the additional type information. perhaps we need to bring Dependent Haskell a bit closer before this is justifiable... Adam On 06/02/15 17:24, Dan Doel wrote:
Assuming a separate syntax, I believe that the criterion would be as simple as ensuring that no ValidateFoo constraints are left outstanding. The syntax would add the relevant validate call, and type variables involved in a ValidateFoo constraint would not be generalizable, and would have to be defaulted or inferred from elsewhere, similar to the monomorphism restriction. I'm not sure how difficult that would be to implement.
I'm not terribly gung ho on this, though. It feels very ad hoc. Making validation vs. non-validation syntactic rather than just based on polymorphism seems somewhat less so, though; so I'd prefer that direction. Finding unused syntax is always a problem, of course.
-- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

Hi Adam,
On 6 Feb 2015, at 21:31, Adam Gundry
wrote: What does "all monomorphic cases" mean? Is the idea what GHC would typecheck an expression involving a literal integer, determine that the occurrence had type Even, then evaluate the TH splice *after* typechecking? Whereas if the occurrence had a non-ground type, it would do something else?
Yes, Typed TH already runs *after* type checking, which is what allows you to do validation based on the resulting type. The main reason why I was only proposing to do this for monomorphic values is, because, how could you possible validate a polymorphic literal? Which validation function would you use? You could ban polymorphic literals, but that'd involve eliminating most uses of polymorphic Num functions (as I mentioned as another email), which would break so much code it would render the extension unusable in "real" code. I'm open to better ideas on how to tackle this, the main reason I started this discussion is because I don't really like this "polymorphic literals fail at compile time" thing either. I just don't see how to solve it without going all dependent types on the problem.
None of this is particularly persuasive, I'm afraid. Is it worthwhile introducing something new just to avoid having to write a quasi quote?
Actually, I would be mildly ok with quasi quoters, BUT there currently is no Typed TH quasi quoter (as mentioned on the wiki page), additionally, such a quoter does not have access to Lift instances for all but a handful of datatypes until we have a more comprehensive way to generate Lift instances. I think both of these points are also highly relevant for this dicussion.
I *am* attracted to the idea of indexed classes in place of IsString/Num
class KnownSymbol s => IsIndexedString (a :: *) (s :: Symbol) where fromIndexedString :: a
class KnownInteger i => IsIndexedInteger (a :: *) (i :: Integer) where fromIndexedInteger :: a These have a smooth upgrade path from the existing class instances via
default fromIndexedString :: (KnownSymbol s, IsString a) => a fromIndexedString = fromString (symbolVal (Proxy :: Proxy s))
default fromIndexedInteger :: (KnownInteger i, Num a) => a fromIndexedInteger = fromInteger (integerVal (Proxy :: Proxy i))
and other instances can take advantage of the additional type information. perhaps we need to bring Dependent Haskell a bit closer before this is justifiable...
The main reason I don't like the "dependent haskell" approach or your approach is how much boiler plate it introduces for beginners. ANYONE knows how to write a "String -> Maybe a" function, I barely know how to use your example and I'm very comfortable with the type families/datakinds stuff, how would "ordinary haskellers" use that? Not to mention, how would I use your "IsIndexedString" in real code? It seems you'd need at least a FunDep + cumbersome annotation? Not to mention that it still performs the conversion at runtime (I would *much* rather have a Lift based approach that just splices finished conversions into the resulting program. Cheers, Merijn

Hi Merijn, Thanks for persevering with explaining things to me. :-) On 09/02/15 09:47, Merijn Verstraaten wrote:
On 6 Feb 2015, at 21:31, Adam Gundry
wrote: What does "all monomorphic cases" mean? Is the idea what GHC would typecheck an expression involving a literal integer, determine that the occurrence had type Even, then evaluate the TH splice *after* typechecking? Whereas if the occurrence had a non-ground type, it would do something else? Yes, Typed TH already runs *after* type checking, which is what allows you to do validation based on the resulting type. The main reason why I was only proposing to do this for monomorphic values is, because, how could you possible validate a polymorphic literal? Which validation function would you use?
You could ban polymorphic literals, but that'd involve eliminating most uses of polymorphic Num functions (as I mentioned as another email), which would break so much code it would render the extension unusable in "real" code. I'm open to better ideas on how to tackle this, the main reason I started this discussion is because I don't really like this "polymorphic literals fail at compile time" thing either. I just don't see how to solve it without going all dependent types on the problem.
In the absence of a coherent story for polymorphism, I think the right thing to do is to be able to specify a particular validator, rather than try to have type inference determine a monomorphic type and otherwise get stuck...
None of this is particularly persuasive, I'm afraid. Is it worthwhile introducing something new just to avoid having to write a quasi quote?
Actually, I would be mildly ok with quasi quoters, BUT there currently is no Typed TH quasi quoter (as mentioned on the wiki page), additionally, such a quoter does not have access to Lift instances for all but a handful of datatypes until we have a more comprehensive way to generate Lift instances. I think both of these points are also highly relevant for this dicussion.
...so is the right solution to introduce Typed TH quasiquoters for expressions? Sorry, I presumed such a thing existed, as Typed TH is rather regrettably underdocumented. Is there any particular difficulty with them, or is it just a Small Matter of Programming? I think the lack of Lift instances is a separate problem; while it looks like 7.10 will be better in this respect and dataToExpQ goes a fair way, I agree that making them easier to generate would be nice. Perhaps a generics-based default method combined with DeriveAnyClass would make "deriving Lift" possible? Adam -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

Hi Adam,
On 9 Feb 2015, at 17:44, Adam Gundry
wrote: In the absence of a coherent story for polymorphism, I think the right thing to do is to be able to specify a particular validator, rather than try to have type inference determine a monomorphic type and otherwise get stuck...
I was planning to write a TH library for this sort of thing anyway, I was just curious if people had better solutions for the polymorphic story/solutions to take away this annoyance. But maybe a better solution in this direction is Gershom's solution to allow proper compile time functions.
...so is the right solution to introduce Typed TH quasiquoters for expressions? Sorry, I presumed such a thing existed, as Typed TH is rather regrettably underdocumented. Is there any particular difficulty with them, or is it just a Small Matter of Programming?
I don't actually know the answer to this, it was one of the questions I was hoping to answer in this discussion :)
I think the lack of Lift instances is a separate problem; while it looks like 7.10 will be better in this respect and dataToExpQ goes a fair way, I agree that making them easier to generate would be nice. Perhaps a generics-based default method combined with DeriveAnyClass would make "deriving Lift" possible?
It's not directly related to whatever solution we pick, but I do think it's an important issue. There's currently a TH library for deriving them, but from what I've seen about writing them by hand I don't understand how GHC couldn't trivially generate them for most (all?) ADTs. Cheers, Merijn
participants (3)
-
Adam Gundry
-
Dan Doel
-
Merijn Verstraaten