[Haskell-cafe] TH: quoting name and value
Sylvain Henry
sylvain at haskus.fr
Tue Feb 2 18:17:38 UTC 2021
Hi Richard,
Thanks for the pointer. It's not exactly what I am after though because
I don't need the RHS (AST) of `bar` in my example but the result of
running it at compile time. I think it should be simpler than reifying a
Name into a TH AST.
I will open a new ticket.
Thanks,
Sylvain
On 01/02/2021 18:06, Richard Eisenberg wrote:
> Hi Sylvain,
>
> I think you're after https://gitlab.haskell.org/ghc/ghc/-/issues/14474
> <https://gitlab.haskell.org/ghc/ghc/-/issues/14474>. There is some
> real work to do there, but it should be quite possible.
>
> Richard
>
>> On Feb 1, 2021, at 4:51 AM, Sylvain Henry <sylvain at haskus.fr
>> <mailto:sylvain at haskus.fr>> wrote:
>>
>> Hi,
>>
>> I have the following kind of template haskell code:
>>
>> module Foo where
>> foo :: String -> Name -> Q [Dec]
>> foo str name = return []
>>
>> module Bar where
>> bar :: String
>> bar = "whatever"
>>
>> module FooBar where
>> import Foo
>> import Bar
>> foo bar 'bar
>>
>> It works great as in `foo` I can use both bar's Name and bar's value
>> computed at compile time.
>>
>> But it's unsafe for my purpose because a user could call: `foo
>> "fakeBarValue" 'bar`
>>
>> So the question is: is there a way to write `foo` so that it can only
>> be used safely?
>>
>>
>> If not, I guess it could be possible to add a new kind of quote to
>> TH, something like:
>>
>> data Named a = Named Name a -- constructor not exported so that Named
>> values can't be forged by users.
>>
>> [namedValue||bar||] :: Named String -- new quote
>>
>> What do you think?
>>
>> Thanks,
>> Sylvain
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> <http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe>
>> Only members subscribed via the mailman list are allowed to post.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20210202/1cec9491/attachment.html>
More information about the Haskell-Cafe
mailing list