[Haskell-cafe] Remove redundancy with Template Haskell

Mike Ledger eleventynine at gmail.com
Fri Mar 29 05:17:18 CET 2013


argh, always forget to reply to all

It's possible, just somewhat painful because TH /requires/ you to
build an AST -- you can't just return a string representing what you
want to splice in.

Here's one using haskell-src-meta:

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.Meta

call :: Name -> String -> Q Exp
call name exp' = case parseExp exp' of
    Right expr ->
        let fun = [| name |]
            str = stringE exp'
        in [| $fun $(return expr) $str |]
    _       -> error "Invalid expression."

This can be then used to make a QuasiQuoter:

call' :: QuasiQuoter
call' = QuasiQuoter { quoteExp = call 'functionYouWantHere }

On Fri, Mar 29, 2013 at 8:40 AM, Corentin Dupont
<corentin.dupont at gmail.com> wrote:
> Thanks Daniel, that's very simple!
>
> Realizing this in TH seems be impossible, is it right?
>
>
>
>
> On Wed, Mar 27, 2013 at 10:33 PM, Daniel Trstenjak
> <daniel.trstenjak at gmail.com> wrote:
>>
>>
>> Hi Corentin,
>>
>> On Wed, Mar 27, 2013 at 09:13:41PM +0100, Corentin Dupont wrote:
>> > I have a function that looks like this:
>> > call :: SomeFunction -> String -> SomeState
>> >
>> > The string is actually the representation of the function passed in
>> > parameter. It is stored in the state for documentation.
>> > So a call looks like that:
>> > call (\a -> putStrLn a)   "\a -> putStrLn a"
>> >
>> > There is a clear redundancy here, how could I remove it with Template
>> > Haskell?
>> > I cannot figure out...
>>
>> You can even use cpp to get something like:
>>
>> #define CALL(func) call (func) #func
>>
>> CALL(\a -> a + 1) => call (\a -> a + 1) "\a -> a + 1"
>>
>>
>> Greetings,
>> Daniel
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list