is this change in TH error message intentional?

Ömer Sinan Ağacan omeragacan at gmail.com
Tue Oct 20 13:10:09 UTC 2015


Originally I had this file:

    {-# LANGUAGE TemplateHaskell #-}

    module Main where

    import Language.Haskell.TH
    import Language.Haskell.TH.Syntax

    -- import LiftLoc

    main :: IO ()
    main = do
      let loc :: Loc
          loc = $(locaton)
          -- loc = $(locaton >>= lift)
      print loc

But any code with a undefined name inside TH splice would work, I think:

    {-# LANGUAGE TemplateHaskell #-}
    module Main where
    import Language.Haskell.TH
    main = print $(blah)



    ➜  th-test  ghc --make Main.hs
    [1 of 1] Compiling Main             ( Main.hs, Main.o )

    Main.hs:10:16:
        Not in scope: ‘blah’
        In the splice: $blah

    Main.hs:10:16:
        GHC stage restriction:
          ‘blah’ is used in a top-level splice or annotation,
          and must be imported, not defined locally
        In the expression: blah
        In the splice: $blah

    ➜  th-test  ghc-stage2 --make Main.hs
    [1 of 1] Compiling Main             ( Main.hs, Main.o )

    Main.hs:10:16: error: Variable not in scope: blah :: ExpQ

2015-10-20 2:04 GMT-04:00 Jan Stolarek <jan.stolarek at p.lodz.pl>:
> Ömer, can you show us the source of Main.hs?
>
> Janek
>
> Dnia poniedziałek, 19 października 2015, Ömer Sinan Ağacan napisał:
>> Hi all,
>>
>> I realized this change in TH error messages:
>>
>> GHC 7.10.2:
>>
>>     ➜  th-test  ghc --make Main.hs
>>     [1 of 1] Compiling Main             ( Main.hs, Main.o )
>>
>>     Main.hs:13:15:
>>         Not in scope: ‘locaton’
>>         Perhaps you meant ‘location’ (imported from
>> Language.Haskell.TH.Syntax) In the splice: $locaton
>>
>>     Main.hs:13:15:
>>         GHC stage restriction:
>>           ‘locaton’ is used in a top-level splice or annotation,
>>           and must be imported, not defined locally
>>         In the expression: locaton
>>         In the splice: $locaton
>>
>> I think both error messages are quite useful in this context. I don't see
>> second one as redundant.
>>
>> However, with HEAD:
>>
>>     ➜  th-test  ghc-stage2 --make Main.hs
>>     [1 of 1] Compiling Main             ( Main.hs, Main.o )
>>
>>     Main.hs:13:15: error:
>>         Variable not in scope: locaton :: ExpQ
>>         Perhaps you meant ‘location’ (imported from
>> Language.Haskell.TH.Syntax)
>>
>> I think this new message is quite worse than previous one. First, "In the
>> splice ..." part is missing. Second, "It must be imported, not defined
>> locally" message is not given at all.
>>
>> Was this change intentional? May I ask why it's changed?
>> _______________________________________________
>> ghc-devs mailing list
>> ghc-devs at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
>
> ---
> Politechnika Łódzka
> Lodz University of Technology
>
> Treść tej wiadomości zawiera informacje przeznaczone tylko dla adresata.
> Jeżeli nie jesteście Państwo jej adresatem, bądź otrzymaliście ją przez pomyłkę
> prosimy o powiadomienie o tym nadawcy oraz trwałe jej usunięcie.
>
> This email contains information intended solely for the use of the individual to whom it is addressed.
> If you are not the intended recipient or if you have received this message in error,
> please notify the sender and delete it from your system.


More information about the ghc-devs mailing list