I've always considered Unit to just be a nullary tuple. This intuition has
never steered me wrong, and it seems that Template Haskell is making the same
assumption. If there's some reason that this conflation of ideas is wrong, I
would be eager to know -- th-desugar makes this assumption in seve
Hi Jose and Richard,
haskell-src-meta has Language.Haskell.Meta.Utils.normalizeT which can
help with making code "treat the two constructs equivalently", though
I imagine using th-desugar instead will make that process harder to
mess up.
Adam
On Thu, Aug 29, 2013 at 10:13 AM, Richard Eisenberg
> I can't answer about "expected behavior", but I can say that those
> two constructions should be considered identical by the $(…) splice
> construct. For better or worse, Template Haskell often offers
> multiple ways of encoding the same source Haskell phrase, and any
> code that processes Templa
I can't answer about "expected behavior", but I can say that those two
constructions should be considered identical by the $(…) splice construct. For
better or worse, Template Haskell often offers multiple ways of encoding the
same source Haskell phrase, and any code that processes Template Hask
Hi,
I am positive about the following situation, but I can't find any
concrete answer on the Web. Can anyone confirm this ?
In template-haskell-2.7.0, the following quote
[t| () |]
appears as a (ConT name), where "name" is the name for unit. However,
in template-haskell-2.8.0, the same quote
adam vogt wrote:
> TH quotes limited as you've noticed. One way to generate similar code
> is to note that:
>
> do
> let x = y
> z
>
> is the same as let x = y in do z. You can generate the latter with
> something like the following file, but the `a' isn't in scope for the
> second argument
Thanks,
Jose
--
Jose Antonio Lopes
Ganeti Engineering
Google Germany GmbH
Dienerstr. 12, 80331, München
Registergericht und -nummer: Hamburg, HRB 86891
Sitz der Gesellschaft: Hamburg
Geschäftsführer: Graham Law, Christine Elizabeth Flores
Steuernummer: 48/725/00206
Umsatzsteueridentifikationsnumm
Hi Jose,
Template Haskell doesn't parse code.
haskell-src-exts and the GHC API can do that.
Have a look at:
* ghc-mod browse (using ghc api)
* hscope (using haskell-src-exts)
On 27/08/13 15:45, Jose A. Lopes wrote:
> Hi,
>
> Is it possible to retrieve all definitions contained in a module usi
Hi,
Is it possible to retrieve all definitions contained in a module using
Template Haskell ?
Thanks,
Jose
--
Jose Antonio Lopes
Ganeti Engineering
Google Germany GmbH
Dienerstr. 12, 80331, München
Registergericht und -nummer: Hamburg, HRB 86891
Sitz der Gesellschaft: Hamburg
Geschäftsführer:
On Sat, Aug 24, 2013 at 11:00 AM, TP wrote:
> that has type Stmt, in an ExpQ that seems to be the only thing that we can
> put in a splice. I have found that it can only be done by doE (or DoE) and
> compE (or CompE) according to
>
> http://www.haskell.org/ghc/docs/latest/html/libraries/template-h
Brandon Allbery wrote:
>> main = do
>>
>> $(makeLetStatement "a")
>> -- print a
>>
>
> Is that the actual indentation you used? Because it's wrong if so, and the
> error you would get is the one you're reporting. Indentation matters in
> Haskell.
Yes, it matters, but not after "main = do": all t
On Sat, Aug 24, 2013 at 11:00 AM, TP wrote:
> main = do
>
> $(makeLetStatement "a")
> -- print a
>
Is that the actual indentation you used? Because it's wrong if so, and the
error you would get is the one you're reporting. Indentation matters in
Haskell.
In an equation for `main': main = do
Hi,
I continue to test Template Haskell, and I have some difficulties to use a
splice $() in a "do" contained in the "main" part of a program. Here is an
example. I want to make a splice that does `let a="a"` in my code.
$ cat MakeLetStatement.hs
{-# LANGUAGE Templ
On Wed, Jul 31, 2013 at 08:29:18PM +0300, kudah wrote:
> On Wed, 31 Jul 2013 15:18:32 +0200 "Jose A. Lopes"
> wrote:
>
> > Is there a way to access docstrings through Template Haskell ?
> > For example, access the docstring of a function declaration ?
>
> No, but I believe you can access comment
On Wed, 31 Jul 2013 15:18:32 +0200 "Jose A. Lopes"
wrote:
> Is there a way to access docstrings through Template Haskell ?
> For example, access the docstring of a function declaration ?
No, but I believe you can access comments and annotations using a
ghc plugin. See https://github.com/thoughtp
Hi,
Is there a way to access docstrings through Template Haskell ?
For example, access the docstring of a function declaration ?
Best regards,
Jose
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-c
On Sat, Dec 15, 2012 at 9:24 AM, satvik chauhan wrote:
> Yeah, that is the problem. I have a function inside which I need to generate
> some declarations using TH. I can not generate these at the top level as
> these generations depend on the function's parameters which are local to the
> function
On Sat, Dec 15, 2012 at 1:30 PM, Michael Sloan wrote:
> I don't think that there is a particular reason for not supporting
> quasi-quotes in where clauses.. It should be added!
>
> The reason for /splices/ to not be supported in here statements is that
> they are run during type checking. That
I don't think that there is a particular reason for not supporting
quasi-quotes in where clauses.. It should be added!
The reason for /splices/ to not be supported in here statements is that
they are run during type checking. That way calls to "reify" can access
type information for things befor
Is there any way to splice declarations inside where? If not, then what is
the reason for not supporting this?
-Satvik
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
'Ello,
I'm using TH in a big project and whenever TH starts-up in the GHC
(6.4.2) compilation process it loads a number of packages:
[119 o 119] Compiling Main ( src/Main.hs,
dist/build/eudl/eudl-tmp/Main.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp .
(oops, sorry, didn't do reply to all)
I use haskell-src-meta in QuasiText (on hackage) also. It would certainly
be nice to have "native" anti-quotations, but for now haskell-src-meta does
a very good job.
Mike
On Sat, May 26, 2012 at 8:31 AM, Geoffrey Mainland wrote:
> On 05/25/2012 21:46, Antoi
On 05/25/2012 21:46, Antoine Latter wrote:
> On Fri, May 25, 2012 at 2:51 PM, Sam Lindley wrote:
>> Template Haskell supports antiquotation for built-in quasiquotes, e.g.:
>>
>> [| \x -> x + $([|3 * 4|]) |]
>>
>> However, as far as I can tell, there is no way of supporting antiquotation
>> in use
On Fri, May 25, 2012 at 2:51 PM, Sam Lindley wrote:
> Template Haskell supports antiquotation for built-in quasiquotes, e.g.:
>
> [| \x -> x + $([|3 * 4|]) |]
>
> However, as far as I can tell, there is no way of supporting antiquotation
> in user-defined quasiquoters, because the only way to spe
Template Haskell supports antiquotation for built-in quasiquotes, e.g.:
[| \x -> x + $([|3 * 4|]) |]
However, as far as I can tell, there is no way of supporting
antiquotation in user-defined quasiquoters, because the only way to
specify a new quasiquoter is through a quoteExp function of ty
Hi Michael, I was able to do what I wanted using reify instead of
reifyInstances, and also I used applyT instead of substT.
Thanks
2012/4/13 Ismael Figueroa Palet
> Thanks for your reply, in particular the reference to subsT!
> I will work more on this next monday, and report my progress
>
> Ch
I once experimented with something similar. This is a preprocessor.
This was a long time ago, and I don't use it.
https://patch-tag.com/r/jmcarthur/overloaded-whitespace/snapshot/current/content/pretty/Main.hs
On Thu, Apr 19, 2012 at 8:40 AM, Ismael Figueroa Palet
wrote:
> Hi Michael!
>
> Thanks
Hi Michael!
Thanks (again) for your answer.
I'm not quite confident using TH yet, but it seems in your code you must
define an 'app' function, and then use [overloadedApp|... |] as a
quasiquoteator to inject the overloaded app, right?
Thanks for the zeroth reference too, one question remains for
You're in luck! This is something I've wanted to implement before in
the past, and your email reminded me. While pretty awful, it could be
used for doing some interesting value-interception instrumentation in
Haskell. Recently I've been messing with TH a lot, so this initial
implementation was r
I'm working on getting annotated versions of all instances of a function of
a typeclass, and was wondering what are the relation/differences between
Template Haskell and the Rewrite Rules section. Of course this is specific
to GHC.
Another question, in Racket, primitive function application is den
Thanks for your reply, in particular the reference to subsT!
I will work more on this next monday, and report my progress
Cheers!
2012/4/13 Michael Sloan
> Hello!
>
> It seems like you would want to use "reifyInstances" in order to get
> all of the instances associated with a class. Then, you
Hello!
It seems like you would want to use "reifyInstances" in order to get
all of the instances associated with a class. Then, you can match up
the variables in each instance with the variables in the class
declaration, and create a mapping from the class variables to the
instance parameters. T
Hi all, I think this is the right place for the following questions and I
thank beforehand for your answers :-)
I'm experimenting with typeclasses and TH, and I want to define a 'macro'
that works more or less like this:
Given the name of a typeclass and a function, return the expressions
corres
A quick follow-up:
1) I had a typo: it should say "N4 is like N1 with a phantom type variable".
2) In my larger code base, the constructor that is visible to TH when
I think it shouldn't be is part of a type that is alpha-equivalent to
N3. It's odd that N3 doesn't exhibit the leakiness here but a
Whith the three modules at the end of this email, I get some
interesting results. Note that none of the constructors are exported,
yet Template Haskell can see (and splice in variable occurrences of!)
T, C2, W1, and W4.
If you load Dump into GHCi, you get to see the Info that TH provides
when you
to
> produce TupleT and ListT!
>
> Simon
>
> | -Original Message-
> | From: haskell-cafe-boun...@haskell.org
> [mailto:haskell-cafe-boun...@haskell.org] On
> | Behalf Of Serguey Zefirov
> | Sent: 09 May 2011 14:43
> | To: haskell
> | Subject: [Haskell
| Subject: [Haskell-cafe] Template Haskell reified type.
|
| Language.Haskell.TH.Type contains, among others, two constructors:
| TupleT Int and ListT.
|
| I can safely construct types using them, but reification returns ConT
| "GHC.Tuple.(,)" and ConT "GHC.Types.[]" respective
Language.Haskell.TH.Type contains, among others, two constructors:
TupleT Int and ListT.
I can safely construct types using them, but reification returns ConT
"GHC.Tuple.(,)" and ConT "GHC.Types.[]" respectively.
This is not fair asymmetry, I think.
Also, it took purity from one of my functions
Hi all!
I am writing a library which allows to refer to the separate fields of
a datatype. The fields are described as GADT with one constructor for
each field. The constructors return GADT with the field type. The
auxiliary data structures for this should be generated automatically
via Template H
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 #-}
> m
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
On Wed, Apr 13, 2011 at 10:43 PM, Kenneth Hoste wrote:
> Hi,
> The links to the supposedly brilliant Template Haskell tutorials by Bulat are
> broken.
>
> http://www.haskell.org/bz/thdoc.htm
> http://www.haskell.org/bz/th3.htm
>
> Does anyone know if these tutorials moved to somewhere else?
>
> g
Hi,
The links to the supposedly brilliant Template Haskell tutorials by Bulat are
broken.
http://www.haskell.org/bz/thdoc.htm
http://www.haskell.org/bz/th3.htm
Does anyone know if these tutorials moved to somewhere else?
greetings,
Kenneth___
Haske
On Tue, Jan 04, 2011 at 04:15:07PM +0100, Christian Maeder wrote:
> Am 04.01.2011 15:48, schrieb Henning Thielemann:
> > Christian Maeder schrieb:
> >> Am 27.12.2010 08:44, schrieb Henning Thielemann:
> >>> On Mon, 27 Dec 2010, Jonathan Geddes wrote:
> >>>
> #2 Provide instances automatically.
Am 04.01.2011 15:48, schrieb Henning Thielemann:
> Christian Maeder schrieb:
>> Am 27.12.2010 08:44, schrieb Henning Thielemann:
>>> On Mon, 27 Dec 2010, Jonathan Geddes wrote:
>>>
#2 Provide instances automatically.
>>> http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/generic-class
Christian Maeder schrieb:
> Am 27.12.2010 08:44, schrieb Henning Thielemann:
>> On Mon, 27 Dec 2010, Jonathan Geddes wrote:
>>
>>> #2 Provide instances automatically.
>> http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/generic-classes.html
>
> I see the text below and have no idea where
All,
2010/12/27 Jonathan Geddes :
> I see TH used most for the following tasks:
>
> #1 Parse a string at compile-time so that a custom syntax for
> representing data can be used. At the extreme, this "data" might even
> be an EDSL.
> #2 Provide instances automatically.
Just a note that TH is also
Am 27.12.2010 08:44, schrieb Henning Thielemann:
>
> On Mon, 27 Dec 2010, Jonathan Geddes wrote:
>
>> #1 Parse a string at compile-time so that a custom syntax for
>> representing data can be used. At the extreme, this "data" might even
>> be an EDSL.
>
> I think it would be enough, if the compi
On Tue, Dec 28, 2010 at 8:17 AM, Tillmann Rendel
wrote:
> This seems simple enough to me, so it looks as if your use case is already
> supported as a library on top of the more general API.
This is exactly what I was looking for, and much simpler than my
previous experiences with quasiQuoters.
I
Hi,
Jonathan Geddes wrote:
For TH use #1, compile-time parsing of arbitrary strings, I think it
would be nice for quasiquote semantics to be modified so that code
like
json :: String -> JsonObject
json = ...
data = [ json |
{ "name" : "Jonathan"
, "favorite language": "Haskell"
}
Thanks, everyone, for the responses.
> I don't understand why the library/extension duality is a problem.
I don't think it is a _problem_ it just feels strange to me. Maybe I'm
misunderstanding, is it possible to use TH without using the library
components?
> Shouldn't specialized features be de
On Mon, Dec 27, 2010 at 1:14 AM, Stephen Tetley
wrote:
> By this are you meaning to add quasiquoting to the language "Haskell"
> or the "Glasgow Haskell", taking it out of the domain of Template
> Haskell?
I believe that all new features should start as extensions and as an
extension, these thin
On Mon, Dec 27, 2010 at 12:44 AM, Henning Thielemann
wrote:
> I think it would be enough, if the compiler could be told to unfold an
> expression like
> parse "text in a domain specific language"
> at compile time.
I'm afraid I have to disagree with you here. Being able to specify
that the stri
2010/12/27 Henning Thielemann :
> Or look into package 'encoding'. It uses TemplateHaskell in order to convert
> Text descriptions of character sets into Haskell tables. I think the
> character tables could be simply rewritten to Haskell syntax, or they could
> be parsed by a function, where the pa
On Mon, 27 Dec 2010, Jonas Almström Duregård wrote:
Hi Henning,
> I also think that Template Haskell is used too much. Several
> things that are done in existing libraries could be done in plain
> Haskell in a better way.
Can you give any examples of this? I'm not saying it's not true, I'm ju
Hi Henning,
> I also think that Template Haskell is used too much. Several
> things that are done in existing libraries could be done in plain
> Haskell in a better way.
Can you give any examples of this? I'm not saying it's not true, I'm just
curious as to why you would venture into the realm of
Hi,
> But TH gives me the same feeling as other language features that have
> been described as "bolted on." Also, TH is both library and built-in
> syntax (via an extension) which feels strange to me.
I don't understand why the library/extension duality is a problem. I would
say that the best ap
On 27 December 2010 07:35, Jonathan Geddes wrote:
> #1 Parse a string at compile-time so that a custom syntax for
> representing data can be used. At the extreme, this "data" might even
> be an EDSL.
Hello Jonathan
By this are you meaning to add quasiquoting to the language "Haskell"
or the "G
On Mon, 27 Dec 2010, Jonathan Geddes wrote:
#1 Parse a string at compile-time so that a custom syntax for
representing data can be used. At the extreme, this "data" might even
be an EDSL.
I think it would be enough, if the compiler could be told to unfold an
expression like
parse "text in
Cafe,
First let me say that Template Haskell is very powerful and a lot of
great work has been done in this area. It fills in a number of holes
in Haskell's feature set.
But TH gives me the same feeling as other language features that have
been described as "bolted on." Also, TH is both library a
Hello,
Does anyone know a clean solution to pass information between 2 executions
of splicers.
Ex.
$(splicer ) -- first invocation gather and store some data
$(splicer ...) -- second one use the data gathered above.
Thank you
Regards
J-C
__
Well, Template Haskell is what you go to when what you want -can't- be
reasonably expressed with standard GHC Haskell. It's something of a
last resort (at least in my case). Typeclass synonyms can be faked
reasonably well with UndecidableInstances, but if you want to, for
example, automatically gen
It's first time I use TH. It would be nice to point out the motivations for
using it.
If everything TH does is doable without it, the point of using it is write
less code, eliminating some necessary and automatically computable code.
But I guess there is some more .
paolino
2010/11/2 Antoine
2010/11/1 Paolino :
> I think I've got something nice in the end.
>
> http://hpaste.org/41042/classsynonymhs
>
> example:
>
> class ( ParteDi (Servizio a) s
> , Read a
> , Eq a
> , Show a
> , Integer `ParteDi` s
> ) ⇒ SClass s a
>
> $(classS
I think I've got something nice in the end.
http://hpaste.org/41042/classsynonymhs
example:
class (ParteDi (Servizio a) s
,Read a
,Eq a
, Show a
, Integer `ParteDi` s
) => SClass s a
$(classSynonym ''SClass)
ghci ":i SClass" command
Thanks. I annotated the function
http://hpaste.org/paste/41035/test_simpleclasssynonym
It seems to produce the right code.
How should I use the "Parents" synonym in my functions?
This is a noob question I suppose.
paolino
2010/11/1 Gábor Lehel
> On Mon, Nov 1, 2010 at 6:09 PM, Christopher Do
On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done
wrote:
> On 1 November 2010 17:53, Paolino wrote:
>> I'd like to have a template haskell function that take some constraints and
>> a class name and write an empty class from those and relative empty instance
>> to simulate typeclass synonyms.
>>
>
On 1 November 2010 17:53, Paolino wrote:
> I'd like to have a template haskell function that take some constraints and
> a class name and write an empty class from those and relative empty instance
> to simulate typeclass synonyms.
>
> As I've never written TH and couldn't find a easily adaptable
Hello.
I'd like to have a template haskell function that take some constraints and
a class name and write an empty class from those and relative empty instance
to simulate typeclass synonyms.
As I've never written TH and couldn't find a easily adaptable code around, I
ask here for the code, or so
>From: Simon Peyton-Jones
>Sent: Mon, October 18, 2010 5:02:57 PM
>
>Folks
>
>Following lots of feedback from users, especially at ICFP, I’ve evolved some
>proposals for Template Haskell, that should make it both more expressive, and
>more secure.
>
>http://hackage.haskell.org/trac/ghc/blog/
Since you are proposing creating an abstract type TExp that can't be
created manually in contrast to Exp, I have a question that might simply
be a reflection of ignorance on my part on how TH works now.
As far as I can tell by looking through the documentation, when I want
to create an identi
Folks
Following lots of feedback from users, especially at ICFP, I've evolved some
proposals for Template Haskell, that should make it both more expressive, and
more secure.
http://hackage.haskell.org/trac/ghc/blog/Template%20Haskell%20Proposal
Do let me know what you think. Discussion by ema
Perhaps try importing the huge module with lots of imports in another
module, and then only export the ones you want.
Cheers.
~Liam
2010/10/4 Vo Minh Thu :
> 2010/10/4 Jonas Almström Duregård :
>> Hi Café,
>>
>> I'm doing some code generation with Template Haskell that results in
>> few hundred
2010/10/4 Jonas Almström Duregård :
> Hi Café,
>
> I'm doing some code generation with Template Haskell that results in
> few hundred top level declaration, of which only 10 or so should
> actually be exposed to the user (the rest are only used by generated
> code).
>
> Since I cant splice stuff in
Hi Café,
I'm doing some code generation with Template Haskell that results in
few hundred top level declaration, of which only 10 or so should
actually be exposed to the user (the rest are only used by generated
code).
Since I cant splice stuff into the module header (i.e. into the export
list),
2010/7/28 Simon Peyton-Jones :
> I assume you've seen http://hackage.haskell.org/trac/ghc/ticket/4222
> There are non-obvious design choices here
Yes, I've seen that. Right now I just cannot grok it fully. I feel
like I should share my current understanding with cafe, so I wrote
them in my answer
| To: Jonas Almström Duregård
| Cc: Ivan Lazar Miljenovic; haskell
| Subject: Re: [Haskell-cafe] Template Haskell sees into abstract data types
|
| 2010/7/28 Jonas Almström Duregård :
| > Hi,
| >
| >> I cannot write classes that see into internal structure. For example,
| >> I
On Wed, Jul 28, 2010 at 12:55 PM, Gábor Lehel wrote:
> 2010/7/28 Serguey Zefirov :
>> 2010/7/28 Jonas Almström Duregård :
>>> Hi,
>>>
I cannot write classes that see into internal structure. For example,
I cannot write my own (de)serialization without using from/toAscList.
>>>
>>> Actual
2010/7/28 Serguey Zefirov :
> 2010/7/28 Jonas Almström Duregård :
>> Hi,
>>
>>> I cannot write classes that see into internal structure. For example,
>>> I cannot write my own (de)serialization without using from/toAscList.
>>
>> Actually I don't believe you can do this with TH either. TH splices
>
2010/7/28 Jonas Almström Duregård :
> Hi,
>
>> I cannot write classes that see into internal structure. For example,
>> I cannot write my own (de)serialization without using from/toAscList.
>
> Actually I don't believe you can do this with TH either. TH splices
> code into the module where you use
Hi,
> I cannot write classes that see into internal structure. For example,
> I cannot write my own (de)serialization without using from/toAscList.
Actually I don't believe you can do this with TH either. TH splices
code into the module where you use it. The generated code is then type
checked in
| Data.Map.Map and Data.Set.Set are exported abstractly, without
| exposing knowledge about their internal structure.
|
| I cannot directly create my own class instances for them because of
| that. But I found that I can write Template Haskell code that could do
| that - those data types cou
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On 7/4/10 00:29 , Ivan Lazar Miljenovic wrote:
> David Menendez writes:
>> I believe the point is that Template Haskell can see the internal
>> structure of a type even when the constructors are not exported. The
>> question is whether or not that is
David Menendez writes:
> I believe the point is that Template Haskell can see the internal
> structure of a type even when the constructors are not exported. The
> question is whether or not that is intentional.
I was under the impression that the question was whether the hiding of
the construct
On Sat, Jul 3, 2010 at 7:20 PM, Ivan Lazar Miljenovic
wrote:
> Serguey Zefirov writes:
>
I cannot directly create my own class instances for them because of
that. But I found that I can write Template Haskell code that could do
that - those data types could be reified just fine.
>
Serguey Zefirov writes:
>>> I cannot directly create my own class instances for them because of
>>> that. But I found that I can write Template Haskell code that could do
>>> that - those data types could be reified just fine.
>> Huh? Sure you can write class instances for them.
>> ,
>> | in
>> I cannot directly create my own class instances for them because of
>> that. But I found that I can write Template Haskell code that could do
>> that - those data types could be reified just fine.
> Huh? Sure you can write class instances for them.
> ,
> | instance SizeOf (Map k v) where
>
Serguey Zefirov writes:
> Data.Map.Map and Data.Set.Set are exported abstractly, without
> exposing knowledge about their internal structure.
>
> I cannot directly create my own class instances for them because of
> that. But I found that I can write Template Haskell code that could do
> that - t
Data.Map.Map and Data.Set.Set are exported abstractly, without
exposing knowledge about their internal structure.
I cannot directly create my own class instances for them because of
that. But I found that I can write Template Haskell code that could do
that - those data types could be reified just
Hi Rafael
There is a paper describing a variant of Conal Elliott's Pan
implemented with Template Haskell - PanTH - which you might find
interesting:
Optimising Embedded DSLs using Template Haskell
Sean Seefried, Manuel Chakravarty, and Gabriele Keller
http://www.haskell.org/th/papers/th-pan.ps
On Mar 19, 2010, at 12:01 , Rafael Almeida wrote:
I got the printf example to run, and it is an alright example of
something to do with template haskell. You lose the ability to use a
dynamic generated string for the format, but that's not a practical
drawback (I can't think of a practical reason
I was reading the good old template haskell paper by Sheard and Peyton
Jones [1]. It looks like some API have changed, but things seems to be
more or less the same.
I got the printf example to run, and it is an alright example of
something to do with template haskell. You lose the ability to use a
Cool, Burat! Those are the first tutorials I've read on TH that have succeeded
in giving me a sense of how I can actually use it! Thanks for writing them up.
:-D
Cheers,
Greg
On Jan 4, 2010, at 3:12 AM, Bulat Ziganshin wrote:
> Hello Patrick,
>
> Monday, January 4, 2010, 5:59:18 AM, you wr
Hello Patrick,
Monday, January 4, 2010, 5:59:18 AM, you wrote:
> I'm guessing no such syntax exists?
you are right. look at
http://www.haskell.org/bz/th3.htm
http://www.haskell.org/bz/thdoc.htm
--
Best regards,
Bulatmailto:bulat.zigans...@gmail.com
__
Tuomas Tynkkynen wrote:
Here's something pretty generic that gets the patterns right:
Thanks for that - about 2/3rds of the length of my proposed solution!
Cheers, Patrick.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.o
2010/1/4 Patrick Caldon
>
> I'm trying to write some template haskell which will transform:
>
> $(buildCP 0) into \(SimpleM d1 d2 d3) (SimpleM _ _ _) -> (SimpleM d1 d2 d3)
> $(buildCP 1) into \(SimpleM _ d2 d3) (SimpleM d1 _ _) -> (SimpleM d1 d2 d3)
> $(buildCP 1) into \(SimpleM d1 _ d3) (Simpl
Antoine Latter wrote:
On Sun, Jan 3, 2010 at 8:30 PM, Patrick Caldon wrote:
I'm trying to write some template haskell which will transform:
$(buildCP 0) into \(SimpleM d1 d2 d3) (SimpleM _ _ _) -> (SimpleM d1 d2 d3)
$(buildCP 1) into \(SimpleM _ d2 d3) (SimpleM d1 _ _) -> (SimpleM d1 d2 d
On Sun, Jan 3, 2010 at 8:30 PM, Patrick Caldon wrote:
>
> I'm trying to write some template haskell which will transform:
>
> $(buildCP 0) into \(SimpleM d1 d2 d3) (SimpleM _ _ _) -> (SimpleM d1 d2 d3)
> $(buildCP 1) into \(SimpleM _ d2 d3) (SimpleM d1 _ _) -> (SimpleM d1 d2 d3)
> $(buildCP 1)
I'm trying to write some template haskell which will transform:
$(buildCP 0) into \(SimpleM d1 d2 d3) (SimpleM _ _ _) -> (SimpleM d1 d2 d3)
$(buildCP 1) into \(SimpleM _ d2 d3) (SimpleM d1 _ _) -> (SimpleM d1 d2 d3)
$(buildCP 1) into \(SimpleM d1 _ d3) (SimpleM _ d2 _) -> (SimpleM d1 d2 d3)
a
ine: my nose tells me this is a swamp and I'm steering clear of it for
now.
Simon
From: Matt Morrow [mailto:moonpa...@gmail.com]
Sent: 28 May 2009 00:08
To: Simon Peyton-Jones
Cc: Ross Mellgren; Haskell Cafe; GHC users
Subject: Re: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Ty
1 - 100 of 186 matches
Mail list logo