Merijn,

Perhaps only for the sake of discussion: have you considered doing
something at the type-level instead of using TH? I mean that you could
change the type of 42 from `forall a. Num a => a` to `forall a.
HasIntLiteral a '42 => a` where HasIntegerLiteral is a type class of
kind `* -> 'Integer -> Constraint` and people can instantiate it for
their types:

class HasIntegerLiteral (a :: *) (k :: 'Integer) where
  literal :: a

The desugarer could then just generate an invocation of "literal".

An advantage would be that you don't need TH (although you do need
DataKinds and type-level computation).  Specifically, type-checking
remains decidable and you can do it in safe haskell and so on.  I
haven't thought this through very far, so there may be other
advantages/disadvantages/glaring-holes-in-the-idea that I'm missing.

Regards,
Dominique

2015-02-06 11:07 GMT+01:00 Merijn Verstraaten <mer...@inconsistent.nl>:
> And no one of my proofreaders noticed that >.>
>
> I would propose to have the extension replace the 'fromString "foo"', 
> 'fromIntegral 5' and 'fromList [1,2,3]' calls (for monomorphic cases) in the 
> AST with the relevant Typed TH splice.
>
> I considered quasi-quotation initially too, but there's no quasi quotation 
> syntax for Typed TH. I'm guessing that's just an oversight, but I'd really be 
> in favour of adding a typed quasiquoter too. Similarly to thinking we should 
> have an easier way to obtain Lift  instances since, to me at least, it seems 
> that the Lift instance for most ADTs should be fairly trivial?
>
> I'll quickly clarify the proposal on the wiki :)
>
> Cheers,
> Merijn
>
>> On 5 Feb 2015, at 22:48, Simon Peyton Jones <simo...@microsoft.com> wrote:
>>
>> I'm all for it.  Syntax sounds like the main difficulty.  Today you could 
>> use quasiquotatoin
>>       [even| 38 |]
>> and get the same effect as $$(validate 38).  But it's still noisy.
>>
>> So: what is the non-noisy scheme you want to propose?  You don't quite get 
>> to that in the wiki page!
>>
>> Simon
>>
>> | -----Original Message-----
>> | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Merijn
>> | Verstraaten
>> | Sent: 05 February 2015 14:46
>> | To: ghc-d...@haskell.org; GHC users
>> | Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion
>> |
>> | I've been repeatedly running into problems with overloaded literals and
>> | partial conversion functions, so I wrote up an initial proposal
>> | (https://ghc.haskell.org/trac/ghc/wiki/ValidateMonoLiterals) and I'd like
>> | to commence with the bikeshedding and hearing other opinions :)
>> |
>> | Cheers,
>> | Merijn
>
>
> _______________________________________________
> 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

Reply via email to