[Haskell-cafe] Template haskell: This pattern-binding binds no variables
Michael Baikov
manpacket at gmail.com
Sun Dec 21 08:50:00 UTC 2014
I'm trying to introduce a new local variable to some scope, in this
example this scope is represented by print $( varE ohNoes)
Everything works as expected, but I'm getting a warning message which
I don't seem quite right to me. Am I doing anything wrong?
---- Blah.hs ----
{-# LANGUAGE TemplateHaskell #-}
module Blah where
import Language.Haskell.TH
sample :: Q Exp
sample = newName "ohNoes" >>= \ohNoes -> [| let $( varP ohNoes ) =
"Teh warning!" in print $( varE ohNoes ) |]
---- Main.hs ----
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Blah
main :: IO ()
main = $( sample )
---- output ----
Blah.hs:8:49: Warning:
This pattern-binding binds no variables:
$(varP ohNoes) = "Teh warning!"
sample
======>
let ohNoes_a2Al = "Teh warning!" in print ohNoes_a2Al
More information about the Haskell-Cafe
mailing list