[Haskell-cafe] Template Haskell question

2011-04-17 Thread Alexey Karakulov
I'm interested if it's possible to use functions from some module without explicitly importing it. In ghci it's done on the fly, like this: Prelude Data.Map.empty Loading package array-0.3.0.2 ... linking ... done. Loading package containers-0.4.0.0 ... linking ... done. fromList [] But without

Re: [Haskell-cafe] Template Haskell question

2011-04-17 Thread Daniel Schüssler
Hello, assuming you mean avoiding the import of Data.Map in the module *using* x, you can use name quotations: A.hs: {-# LANGUAGE TemplateHaskell #-} module A where import Data.Map import Language.Haskell.TH x = varE 'empty B.hs: {-# LANGUAGE TemplateHaskell #-} module B

RE: [Haskell-cafe] Template Haskell question

2009-01-08 Thread Simon Peyton-Jones
| To: Jeff Heard | Cc: haskell | Subject: Re: [Haskell-cafe] Template Haskell question | | On Wed, Jan 7, 2009 at 12:58 PM, Jeff Heard jefferson.r.he...@gmail.com wrote: | And how do I encode | | a{ mousePositionf = b } | | in template haskell without using the [| |] syntax, so that I can use

Re: [Haskell-cafe] Template Haskell question

2009-01-07 Thread Jeff Heard
It doesn't typecheck, no, but it also doesn't check out in scope. It complains in [FunD 'mousePosition [| mousePositionf |] ... that mousePositionf isn't in scope. What I believe I need to do is use mkName mousePositionf, but how do I bind the record getter mousePositionf that is defined by

Re: [Haskell-cafe] Template Haskell question

2009-01-07 Thread Ryan Ingram
On Wed, Jan 7, 2009 at 12:58 PM, Jeff Heard jefferson.r.he...@gmail.com wrote: And how do I encode a{ mousePositionf = b } in template haskell without using the [| |] syntax, so that I can use mkName? Whenever I have a question like that, I just ask ghci: $ ghci -fth ghci :m

Re: [Haskell-cafe] Template Haskell question

2009-01-07 Thread David Menendez
On Wed, Jan 7, 2009 at 8:54 PM, Ryan Ingram ryani.s...@gmail.com wrote: You can also use $() and [| |] inside [| |] to generate additional data in TH directly: ghci runQ $ do { VarE n - [| runIdentity |] ; [| \x - $(recUpdE [| x |] [ fmap (\e - (n,e)) [| 1 |] ]) |] } LamE [VarP x_2]

[Haskell-cafe] Template Haskell question

2009-01-06 Thread Jeff Heard
Alright... I *think* I'm nearly there, but I can't figure out how to derive a class instance using record accessors and updaters... Can anyone help? There are [| XXXf |] instances at the end of the module and they all need replaced, but I can't figure out what to replace them with. The basic

Re: [Haskell-cafe] Template Haskell question

2009-01-06 Thread Eelco Lempsink
On 6 jan 2009, at 18:08, Jeff Heard wrote: Alright... I *think* I'm nearly there, but I can't figure out how to derive a class instance using record accessors and updaters... Can anyone help? There are [| XXXf |] instances at the end of the module and they all need replaced, but I can't

Re: [Haskell-cafe] Template Haskell question

2009-01-06 Thread Henning Thielemann
Jeff Heard schrieb: Alright... I *think* I'm nearly there, but I can't figure out how to derive a class instance using record accessors and updaters... Has this something to do with http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor-template ?

RE: [Haskell-cafe] Template Haskell question?

2004-02-12 Thread Simon Peyton-Jones
] [mailto:[EMAIL PROTECTED] On Behalf Of | Jeremy Shaw | Sent: 11 February 2004 16:44 | To: Per Larsson | Cc: [EMAIL PROTECTED] | Subject: Re: [Haskell-cafe] Template Haskell question? | | Hello, | | I had very similar problems due to bugs in 6.2 that are fixed in cvs head. If you build ghc out

[Haskell-cafe] Template Haskell question?

2004-02-11 Thread Per Larsson
I have written a small TH application (module THRecord) which creates update functions for records. It is intended to be used like this: import THRecord data Record = R {... ... $(THRecord.generateRecordModifiers (reifyDecl Record)) It works great, but only if the splice is

Re: [Haskell-cafe] Template Haskell question?

2004-02-11 Thread Keith Wansbrough
I have written a small TH application (module THRecord) which creates update functions for records. It is intended to be used like this: You should probably ask on the Template Haskell mailing list: http://www.haskell.org/mailman/listinfo/template-haskell --KW 8-) -- Keith Wansbrough [EMAIL

Re: [Haskell-cafe] Template Haskell question?

2004-02-11 Thread Jeremy Shaw
Hello, I had very similar problems due to bugs in 6.2 that are fixed in cvs head. If you build ghc out of cvs head that may fix your problem. If not, you can report the bug on the [EMAIL PROTECTED] mailing list. Jeremy Shaw. On Feb 11, 2004 01:39 AM, Per Larsson [EMAIL PROTECTED] wrote: I