[Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread Jose A. Lopes
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 appears as (TupleT 0).

Is this the expected behaviour ?

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
Umsatzsteueridentifikationsnummer: DE813741370

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread 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 Template Haskell syntax 
should probably treat the two constructs equivalently.

In a week or so, I'm hoping to release the first version of a new th-desugar 
package, which attempts to remove these redundancies by converting TH syntax 
into a smaller syntax tree. I'll announce here when it's ready for public 
consumption.

I hope this helps,
Richard

On Aug 29, 2013, at 9:03 AM, Jose A. Lopes wrote:

 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 appears as (TupleT 0).
 
 Is this the expected behaviour ?
 
 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
 Umsatzsteueridentifikationsnummer: DE813741370
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread Jose A. Lopes
 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 Haskell syntax should probably treat
 the two constructs equivalently.

I am not sure I agree that those two constructions should be
identical.  The Unit type is just a normal type with a single
inhabitant: the unit value.  How is this related to tuples ?

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
Umsatzsteueridentifikationsnummer: DE813741370

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread adam vogt
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 e...@cis.upenn.edu wrote:
 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 Haskell 
 syntax should probably treat the two constructs equivalently.

 In a week or so, I'm hoping to release the first version of a new th-desugar 
 package, which attempts to remove these redundancies by converting TH syntax 
 into a smaller syntax tree. I'll announce here when it's ready for public 
 consumption.

 I hope this helps,
 Richard

 On Aug 29, 2013, at 9:03 AM, Jose A. Lopes wrote:

 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 appears as (TupleT 0).

 Is this the expected behaviour ?

 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
 Umsatzsteueridentifikationsnummer: DE813741370

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread Richard Eisenberg
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 several places.

Thanks,
Richard

On Aug 29, 2013, at 11:08 AM, Jose A. Lopes jabolo...@google.com wrote:

 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 Haskell syntax should probably treat
 the two constructs equivalently.
 
 I am not sure I agree that those two constructions should be
 identical.  The Unit type is just a normal type with a single
 inhabitant: the unit value.  How is this related to tuples ?
 
 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
 Umsatzsteueridentifikationsnummer: DE813741370


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell

2013-08-27 Thread Jose A. Lopes
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: Graham Law, Christine Elizabeth Flores
Steuernummer: 48/725/00206
Umsatzsteueridentifikationsnummer: DE813741370

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell

2013-08-27 Thread Niklas Hambüchen
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 using
 Template Haskell ?
 
 Thanks,
 Jose
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell

2013-08-27 Thread Jose A. Lopes
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
Umsatzsteueridentifikationsnummer: DE813741370

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-27 Thread TP
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 to makeLetStatement. The uglier $(dyn a) works,
 though I suppose it's more verbose than manually in-lining the
 variable a.
 
 {-# LANGUAGE TemplateHaskell #-}
 import Language.Haskell.TH
 
 main = $(let
 
 makeLetStatement :: String - ExpQ - ExpQ
 makeLetStatement s rest = letE [ valD (varP (mkName s))
 (normalB $ stringE s) []]
 rest
 
 in makeLetStatement a [| print $(dyn a) |] )

Thanks Adam.
Unfortunately, this solution is not satisfying because the goal is to put 
only one mention to a in the main part, putting all the repetitive code 
and ExpQ's in a separate module. Tonight, I've tried hard one more time 
without more success.
Maybe I have to stick to non-let expressions in the main part of a script, 
when it comes to TH. It should nevertheless allow me to call functions, make 
tests, etc.

Thanks,

TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-25 Thread adam vogt
On Sat, Aug 24, 2013 at 11:00 AM, TP paratribulati...@free.fr 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-haskell-2.8.0.0/Language-Haskell-TH.html#v:doE

 But doE is not a solution as we have seen above, and compE is to construct
 list comprehensions, which is a different thing.

 So, is there any solution to my problem?

Hi TP,

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 to makeLetStatement. The uglier $(dyn a) works,
though I suppose it's more verbose than manually in-lining the
variable a.

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

main = $(let

makeLetStatement :: String - ExpQ - ExpQ
makeLetStatement s rest = letE [ valD (varP (mkName s))
(normalB $ stringE s) []]
rest

in makeLetStatement a [| print $(dyn a) |] )


--
Adam

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-24 Thread TP
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 TemplateHaskell #-}

module MakeLetStatement where

import Language.Haskell.TH

makeLetStatement :: String - ExpQ
makeLetStatement s = return $ DoE $ [ LetS $ [ ValD (VarP $ mkName s)
(NormalB $ LitE $ StringL s) [] ]]


$ cat test_MakeLetStatement.hs

{-# LANGUAGE TemplateHaskell #-}

import MakeLetStatement

main = do

$(makeLetStatement a)
-- print a


Note I have commented print a because otherwise I obtain Not in scope: 
`a' that shows that `a` has not been defined correctly, but does not show 
whether my splice has been correctly expanded (I use --dump-splices GHC 
option, but it seems it is not working for splices in the main = do part).

I obtain:
$ runghc -ddump-splices test_MakeLetStatement.hs 

test_MakeLetStatement.hs:7:3:
Illegal last statement of a 'do' block:
  let a = a
(It should be an expression.)
When splicing a TH expression: do let a = a
In a stmt of a 'do' block: $(makeLetStatement a)
In the expression: do { $(makeLetStatement a) }
In an equation for `main': main = do { $(makeLetStatement a) }

That shows that my splice has been correctly expanded: we have `let a = 
a`. However, what happens is the same as in the following dummy script, we 
have in fact defined a do inside the first do (with DoE), and so we 
obtain an error because the last statement in a do block should be an 
expression.

main = do
do let a = a
print a


So my code does not work, without surprise, but in fact my problem is to 
transform a LetS statement:

http://www.haskell.org/ghc/docs/latest/html/libraries/template-haskell-2.8.0.0/Language-Haskell-TH.html#v:LetS

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-haskell-2.8.0.0/Language-Haskell-TH.html#v:doE

But doE is not a solution as we have seen above, and compE is to construct 
list comprehensions, which is a different thing.

So, is there any solution to my problem?

Thanks in advance,

TP



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-24 Thread Brandon Allbery
On Sat, Aug 24, 2013 at 11:00 AM, TP paratribulati...@free.fr 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 { $(makeLetStatement a) }


You cannot *end* a do with a let-statement; it requires something else
following it. You have nothing following it, as shown by the above fragment
from the error message.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-24 Thread TP
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 the lines can start at the 
beginning of the line. Am I wrong? Or do I not understand what you say?

 In an equation for `main': main = do { $(makeLetStatement a) }

 
 You cannot *end* a do with a let-statement; it requires something else
 following it. You have nothing following it, as shown by the above
 fragment from the error message.

Yes, I have explained why: to be able to see the evaluation of the splice; 
otherwise I obtain Not in scope: `a' if I uncomment -- print a at the 
end of my code; I have explained everything in my initial post.

TP



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell and Haddock

2013-07-31 Thread Jose A. Lopes
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-cafe


Re: [Haskell-cafe] Template Haskell and Haddock

2013-07-31 Thread kudah
On Wed, 31 Jul 2013 15:18:32 +0200 Jose A. Lopes
jabolo...@google.com 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/thoughtpolice/strict-ghc-plugin for example.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell and Haddock

2013-07-31 Thread Simon Hengel
On Wed, Jul 31, 2013 at 08:29:18PM +0300, kudah wrote:
 On Wed, 31 Jul 2013 15:18:32 +0200 Jose A. Lopes
 jabolo...@google.com 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/thoughtpolice/strict-ghc-plugin for 
 example.

By default, Haddock comments are not part of GHC's AST.  You need to
explicitly enable it (see e.g. [1]).  For code that extracts all Haddock
comments by using the GHC API, you can look at [2].

Cheers,
Simon

[1] https://github.com/sol/doctest-haskell/blob/master/src/GhcUtil.hs#L66
[2] https://github.com/sol/doctest-haskell/blob/master/src/Extract.hs

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell Splicing

2012-12-15 Thread Michael Sloan
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 before your splice.  It also allows checking
any AST quotes used inside your splice.  Since type-checking comes after
renaming, splices can't be used in patterns (because it would affect the
lexical scope).

Quasi-quotes, on the other hand, are run in the renamer, and ought to be
able to be used in where clauses.  Yet for some reason they can't - I get
parse error (possibly incorrect indentation or mismatched brackets) when
I try to put one under a where.

Good catch!
-Michael


On Fri, Dec 14, 2012 at 11:09 PM, satvik chauhan mystic.sat...@gmail.comwrote:

 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell Splicing

2012-12-15 Thread satvik chauhan
On Sat, Dec 15, 2012 at 1:30 PM, Michael Sloan mgsl...@gmail.com 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 way calls to reify can access
 type information for things before your splice.  It also allows checking
 any AST quotes used inside your splice.  Since type-checking comes after
 renaming, splices can't be used in patterns (because it would affect the
 lexical scope).

 Quasi-quotes, on the other hand, are run in the renamer, and ought to be
 able to be used in where clauses.  Yet for some reason they can't - I get
 parse error (possibly incorrect indentation or mismatched brackets) when
 I try to put one under a where.

 Good catch!
 -Michael


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.

Something like

f p1 p2= ...
  where
-- this has to be generated by TH
 g_1 = p1
 g_2 = p2
 g_3 = p1 `xor` p2

something like the above. In the above I have shown only 2 parameters but
in my case it is much more. I am able to get the above splice as toplevel
declaration but I am still unsuccessful in getting it inside the where.
I can always make `g` a function and take parameters of `f` as arguments in
the top level splice but that will defeat the purpose of optimization
here(which I am trying to do), as that would result in a function call
every time I use `g` instead of above variables.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell Splicing

2012-12-15 Thread adam vogt
On Sat, Dec 15, 2012 at 9:24 AM, satvik chauhan mystic.sat...@gmail.com 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.

 Something like

 f p1 p2= ...
   where
 -- this has to be generated by TH
  g_1 = p1
  g_2 = p2
  g_3 = p1 `xor` p2

 something like the above. In the above I have shown only 2 parameters but in
 my case it is much more. I am able to get the above splice as toplevel
 declaration but I am still unsuccessful in getting it inside the where.
 I can always make `g` a function and take parameters of `f` as arguments in
 the top level splice but that will defeat the purpose of optimization
 here(which I am trying to do), as that would result in a function call every
 time I use `g` instead of above variables.

Hi Satvik

Perhaps you could put the variables whose evaluations are shared in a 'let':

 f p1 p2 = $(mkG [| g_1 |])
 mkG body = liftM2 LetE [d| g_1 = $(dyn p1) |] body

The above example won't work exactly because the two occurences of g_1
are different names. But you could replace the [d|  |] with something
that has a [Dec] with variables defined in such a way that they can be
captured.

On a somewhat unrelated note, GHC is less able to infer types for
expression splices than for top level bindings. The issue had
something to do with needing to typecheck all the $( x :: ExpQ ) as a
group, even if the values could be defined in separate modules. It
might not be an issue in your case, but one possible way around it is
have the definition of 'f p1 p2 = ... ' done by template haskell. But
then there is the issue that top level splices are run in order, so


-- this doesn't work:
{-# LANGUAGE TemplateHaskell #-}
[d| y = x |]
[d| x = 1 |]


-- This does work:
{-# LANGUAGE TemplateHaskell #-}
[d| x = 1 |]
[d| y = x |]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell Splicing

2012-12-14 Thread satvik chauhan
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


[Haskell-cafe] Template-haskell loading packages

2012-06-28 Thread Christopher Done
'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 ... linking ... done.
Loading package base ... linking ... done.
Loading package array-0.4.0.0 ... linking ... done.
Loading package strict-0.3.2 ... linking ... done.
Loading package split-0.1.4.3 ... linking ... done.
Loading package safe-0.3.3 ... linking ... done.
Loading package bytestring-0.9.2.1 ... linking ... done.
Loading package deepseq-1.3.0.0 ... linking ... done.
Loading package containers-0.4.2.1 ... linking ... done.
Loading package binary-0.5.1.0 ... linking ... done.
Loading package cereal-0.3.5.2 ... linking ... done.
Loading package entropy-0.2.1 ... linking ... done.
Loading package largeword-1.0.1 ... linking ... done.
Loading package tagged-0.4.2.1 ... linking ... done.
Loading package crypto-api-0.10.2 ... linking ... done.
Loading package pureMD5-2.1.0.3 ... linking ... done.
Loading package dlist-0.5 ... linking ... done.
Loading package old-locale-1.0.0.4 ... linking ... done.
Loading package data-default-0.4.0 ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Loading package utf8-string-0.3.7 ... linking ... done.
Loading package printf-mauke-3000.0.5.0.1 ... linking ... done.
Loading package haskell-lexer-1.0 ... linking ... done.
Loading package pretty-show-1.2 ... linking ... done.
Loading package parallel-3.2.0.3 ... linking ... done.
Loading package transformers-0.2.2.0 ... linking ... done.
Loading package mtl-2.0.1.0 ... linking ... done.
Loading package text-0.11.2.1 ... linking ... done.
Loading package parsec-3.1.3 ... linking ... done.
Loading package unix-2.5.1.1 ... linking ... done.
Loading package network-2.3.0.14 ... linking ... done.
Loading package old-time-1.1.0.0 ... linking ... done.
Loading package HTTP-4000.2.3 ... linking ... done.
Loading package base64-bytestring-0.1.1.1 ... linking ... done.
Loading package blaze-builder-0.3.1.0 ... linking ... done.
Loading package blaze-html-0.4.3.4 ... linking ... done.
Loading package filepath-1.3.0.0 ... linking ... done.
Loading package directory-1.1.0.2 ... linking ... done.
Loading package syb-0.3.6.1 ... linking ... done.
Loading package hs-bibutils-4.12 ... linking ... done.
Loading package json-0.5 ... linking ... done.
Loading package pandoc-types-1.9.1 ... linking ... done.
Loading package time-1.4 ... linking ... done.
Loading package xml-1.3.12 ... linking ... done.
Loading package citeproc-hs-0.3.4 ... linking ... done.
Loading package extensible-exceptions-0.1.1.4 ... linking ... done.
Loading package regex-base-0.93.2 ... linking ... done.
Loading package regex-pcre-builtin-0.94.2.1.7.7 ... linking ... done.
Loading package highlighting-kate-0.5.1 ... linking ... done.
Loading package process-1.1.0.1 ... linking ... done.
Loading package random-1.0.1.1 ... linking ... done.
Loading package tagsoup-0.12.6 ... linking ... done.
Loading package temporary-1.1.2.3 ... linking ... done.
Loading package texmath-0.6.0.6 ... linking ... done.
Loading package digest-0.0.1.1 ... linking ... done.
Loading package zlib-0.5.3.3 ... linking ... done.
Loading package zip-archive-0.1.1.8 ... linking ... done.
Loading package pandoc-1.9.4.1 ... linking ... done.
Loading package convertible-1.0.11.1 ... linking ... done.
Loading package HDBC-2.3.1.1 ... linking ... done.
Loading package HDBC-postgresql-2.3.2.1 ... linking ... done.
Loading package haskelldb-2.1.3 ... linking ... done.
Loading package haskelldb-hdbc-2.1.0 ... linking ... done.
Loading package haskelldb-hdbc-postgresql-2.1.0 ... linking ... done.
Loading package QuickCheck-2.4.2 ... linking ... done.
Loading package has-0.5.0.1 ... linking ... done.
Loading package feed-0.3.8 ... linking ... done.
Loading package MonadCatchIO-mtl-0.3.0.4 ... linking ... done.
Loading package xhtml-3000.2.1 ... linking ... done.
Loading package cgi-3001.1.8.2 ... linking ... done.
Loading package fastcgi-3001.0.2.3 ... linking ... done.
Loading package ranges-0.2.4 ... linking ... done.
Loading package email-validate-0.2.8 ... linking ... done.
Loading package digestive-functors-0.2.0.0 ... linking ... done.
Loading package digestive-functors-blaze-0.2.1.0 ... linking ... done.
Loading package curl-1.3.7 ... linking ... done.
Loading package csv-0.1.2 ... linking ... done.
Loading package MonadRandom-0.1.6 ... linking ... done.
Loading package HUnit-1.2.4.3 ... linking ... done.
Loading package hslogger-1.1.5 ... linking ... done.
Loading package regex-posix-0.95.2 ... linking ... done.
Loading package regex-compat-0.95.1 ... linking ... done.
Loading package MissingH-1.1.1.0 ... linking ... done.
Loading package ConfigFile-1.1.1 ... linking ... done.

The TH is declared in a separate module, e.g.


[Haskell-cafe] Template Haskell antiquotation in user-defined quasiquoters

2012-05-25 Thread Sam Lindley

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 type String 
- Q Exp. Of course, it is perfectly possible to write a parser for some 
fragment of Haskell inside your quoteExp function, but that seems crazy 
given that Template Haskell or rather GHC already implements a parser 
for the whole language.


I know about Language.Haskell.Exts.Parser in haskell-src-exts, which 
provides parseExp :: String - ParseResult Exp, but that Exp is a 
different type to the one provided by Template 
Haskell.http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/doc/html/Language-Haskell-Exts-Syntax.html#t:Exp 
I'm also aware of Dominic Orchard's syntax-trees package, which supports 
converting between the two representations using a cunning hack that 
pretty-prints the haskell-src-exts representation to a string and uses 
Template Haskell to parse it back.


Is there a saner way of simulating antiquotation in user-defined 
quasiquoters?


Sam


--
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell antiquotation in user-defined quasiquoters

2012-05-25 Thread Antoine Latter
On Fri, May 25, 2012 at 2:51 PM, Sam Lindley sam.lind...@ed.ac.uk 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 specify a new
 quasiquoter is through a quoteExp function of type String - Q Exp. Of
 course, it is perfectly possible to write a parser for some fragment of
 Haskell inside your quoteExp function, but that seems crazy given that
 Template Haskell or rather GHC already implements a parser for the whole
 language.

 I know about Language.Haskell.Exts.Parser in haskell-src-exts, which
 provides parseExp :: String - ParseResult Exp, but that Exp is a different
 type to the one provided by Template
 Haskell.http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/doc/html/Language-Haskell-Exts-Syntax.html#t:Exp
 I'm also aware of Dominic Orchard's syntax-trees package, which supports
 converting between the two representations using a cunning hack that
 pretty-prints the haskell-src-exts representation to a string and uses
 Template Haskell to parse it back.

 Is there a saner way of simulating antiquotation in user-defined
 quasiquoters?


Have you looked at:

http://hackage.haskell.org/package/haskell-src-exts-qq
http://hackage.haskell.org/package/haskell-src-meta

The might help you pull something together.


Antoine

 Sam


 --
 The University of Edinburgh is a charitable body, registered in
 Scotland, with registration number SC005336.


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell antiquotation in user-defined quasiquoters

2012-05-25 Thread Geoffrey Mainland
On 05/25/2012 21:46, Antoine Latter wrote:
 On Fri, May 25, 2012 at 2:51 PM, Sam Lindley sam.lind...@ed.ac.uk 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 specify a new
 quasiquoter is through a quoteExp function of type String - Q Exp. Of
 course, it is perfectly possible to write a parser for some fragment of
 Haskell inside your quoteExp function, but that seems crazy given that
 Template Haskell or rather GHC already implements a parser for the whole
 language.

 I know about Language.Haskell.Exts.Parser in haskell-src-exts, which
 provides parseExp :: String - ParseResult Exp, but that Exp is a different
 type to the one provided by Template
 Haskell.http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/doc/html/Language-Haskell-Exts-Syntax.html#t:Exp
 I'm also aware of Dominic Orchard's syntax-trees package, which supports
 converting between the two representations using a cunning hack that
 pretty-prints the haskell-src-exts representation to a string and uses
 Template Haskell to parse it back.

 Is there a saner way of simulating antiquotation in user-defined
 quasiquoters?

 
 Have you looked at:
 
 http://hackage.haskell.org/package/haskell-src-exts-qq
 http://hackage.haskell.org/package/haskell-src-meta
 
 The might help you pull something together.
 
 
 Antoine
 
 Sam

I use haskell-src-meta in language-c-quote (also on hackage) to support
antiquotation and heartily endorse it. I have not used haskell-src-exts-qq.

Geoff


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell antiquotation in user-defined quasiquoters

2012-05-25 Thread Mike Ledger
(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 mainl...@apeiron.netwrote:

 On 05/25/2012 21:46, Antoine Latter wrote:
  On Fri, May 25, 2012 at 2:51 PM, Sam Lindley sam.lind...@ed.ac.uk
 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 specify a new
  quasiquoter is through a quoteExp function of type String - Q Exp. Of
  course, it is perfectly possible to write a parser for some fragment of
  Haskell inside your quoteExp function, but that seems crazy given that
  Template Haskell or rather GHC already implements a parser for the whole
  language.
 
  I know about Language.Haskell.Exts.Parser in haskell-src-exts, which
  provides parseExp :: String - ParseResult Exp, but that Exp is a
 different
  type to the one provided by Template
  Haskell.
 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/doc/html/Language-Haskell-Exts-Syntax.html#t:Exp
 
  I'm also aware of Dominic Orchard's syntax-trees package, which supports
  converting between the two representations using a cunning hack that
  pretty-prints the haskell-src-exts representation to a string and uses
  Template Haskell to parse it back.
 
  Is there a saner way of simulating antiquotation in user-defined
  quasiquoters?
 
 
  Have you looked at:
 
  http://hackage.haskell.org/package/haskell-src-exts-qq
  http://hackage.haskell.org/package/haskell-src-meta
 
  The might help you pull something together.
 
 
  Antoine
 
  Sam

 I use haskell-src-meta in language-c-quote (also on hackage) to support
 antiquotation and heartily endorse it. I have not used haskell-src-exts-qq.

 Geoff


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: Generate annotated function of a typeclass

2012-05-10 Thread Ismael Figueroa Palet
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 ifiguer...@gmail.com

 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 mgsl...@gmail.com

 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.  Then, you can apply these mappings with substT:

 http://hackage.haskell.org/packages/archive/haskell-src-meta/0.5.1.2/doc/html/Language-Haskell-Meta-Utils.html#v:substT

 The result would also need to have the context of the instance,
 perhaps reduced to just the constraints that mention the type
 variables used in the selected function.

 -Michael Sloan

 On Fri, Apr 13, 2012 at 11:37 AM, Ismael Figueroa Palet
 ifiguer...@gmail.com wrote:
  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
  corresponding to the type-annotated instances, for instance
 
  $(foo Show show)
 
  should translate to:
 
  [(show :: Int - String),  (show :: Bool - String), ]
 
  for all instances currently in scope.
 
  I'm currently playing with the isInstance function (I'm running GHC
 7.4.1)
  and can get a list of instances, and check if a given type is part of a
  typeclass or not. But I don't know how to create the expression
  corresponding to instantiated function, as above.
 
  Thanks!
  --
  Ismael
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 




 --
 Ismael




-- 
Ismael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell vs Rewrite Rules?

2012-04-19 Thread Michael Sloan
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 rather straightforward.

https://github.com/mgsloan/overload-app/blob/master/src/Language/Haskell/TH/OverloadApp.hs

Usage:
https://github.com/mgsloan/overload-app/blob/master/examples/Example1.hs

Note: Relatively untested implementation, let me know if you find any problems!

It only does this transformation to direct function application,
unfortunately.  In order to properly overload apply for infix
operators, you'll need to be able to resolve fixities at compile time.
 This could be done by using the code in
http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution
and using the fixity information yielded by TH's reify.  Someone
aught to have done this before, but I haven't seen it.

Handling the applications involved in do-notation, comprehensions,
enumerations, and anything else that's such direct syntax sugar would
also be a bit of work (but could be very useful for other TH
quasiquoting stuff!).

You might also be interested in this:

http://hackage.haskell.org/package/zeroth-2009.6.23.3

Hope that helps!

-Michael Sloan

On Wed, Apr 18, 2012 at 9:49 AM, Ismael Figueroa Palet
ifiguer...@gmail.com wrote:
 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 denoted
 #%app. And using macros I can re-export #%app to be a different function f,
 so a program:

 (g a) is rewritten into (f g a)

 is there a way to do the same thing using TH or Rewrite Rules?

 Thanks

 --
 Ismael


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell vs Rewrite Rules?

2012-04-19 Thread Ismael Figueroa Palet
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 me: what are
the constrasts/differences between TH and RewriteRules? :-)


2012/4/19 Michael Sloan mgsl...@gmail.com

 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 rather straightforward.


 https://github.com/mgsloan/overload-app/blob/master/src/Language/Haskell/TH/OverloadApp.hs

 Usage:
 https://github.com/mgsloan/overload-app/blob/master/examples/Example1.hs

 Note: Relatively untested implementation, let me know if you find any
 problems!

 It only does this transformation to direct function application,
 unfortunately.  In order to properly overload apply for infix
 operators, you'll need to be able to resolve fixities at compile time.
  This could be done by using the code in
 http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution
 and using the fixity information yielded by TH's reify.  Someone
 aught to have done this before, but I haven't seen it.

 Handling the applications involved in do-notation, comprehensions,
 enumerations, and anything else that's such direct syntax sugar would
 also be a bit of work (but could be very useful for other TH
 quasiquoting stuff!).

 You might also be interested in this:

 http://hackage.haskell.org/package/zeroth-2009.6.23.3

 Hope that helps!

 -Michael Sloan

 On Wed, Apr 18, 2012 at 9:49 AM, Ismael Figueroa Palet
 ifiguer...@gmail.com wrote:
  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 denoted
  #%app. And using macros I can re-export #%app to be a different function
 f,
  so a program:
 
  (g a) is rewritten into (f g a)
 
  is there a way to do the same thing using TH or Rewrite Rules?
 
  Thanks
 
  --
  Ismael
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 




-- 
Ismael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell vs Rewrite Rules?

2012-04-19 Thread Jake McArthur
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
ifiguer...@gmail.com wrote:
 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 me: what are
 the constrasts/differences between TH and RewriteRules? :-)


 2012/4/19 Michael Sloan mgsl...@gmail.com

 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 rather straightforward.


 https://github.com/mgsloan/overload-app/blob/master/src/Language/Haskell/TH/OverloadApp.hs

 Usage:
 https://github.com/mgsloan/overload-app/blob/master/examples/Example1.hs

 Note: Relatively untested implementation, let me know if you find any
 problems!

 It only does this transformation to direct function application,
 unfortunately.  In order to properly overload apply for infix
 operators, you'll need to be able to resolve fixities at compile time.
  This could be done by using the code in
 http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution
 and using the fixity information yielded by TH's reify.  Someone
 aught to have done this before, but I haven't seen it.

 Handling the applications involved in do-notation, comprehensions,
 enumerations, and anything else that's such direct syntax sugar would
 also be a bit of work (but could be very useful for other TH
 quasiquoting stuff!).

 You might also be interested in this:

 http://hackage.haskell.org/package/zeroth-2009.6.23.3

 Hope that helps!

 -Michael Sloan

 On Wed, Apr 18, 2012 at 9:49 AM, Ismael Figueroa Palet
 ifiguer...@gmail.com wrote:
  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 denoted
  #%app. And using macros I can re-export #%app to be a different function
  f,
  so a program:
 
  (g a) is rewritten into (f g a)
 
  is there a way to do the same thing using TH or Rewrite Rules?
 
  Thanks
 
  --
  Ismael
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 




 --
 Ismael


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell vs Rewrite Rules?

2012-04-18 Thread Ismael Figueroa Palet
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 denoted
#%app. And using macros I can re-export #%app to be a different function f,
so a program:

(g a) is rewritten into (f g a)

is there a way to do the same thing using TH or Rewrite Rules?

Thanks

-- 
Ismael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell: Generate annotated function of a typeclass

2012-04-13 Thread Ismael Figueroa Palet
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
corresponding to the type-annotated instances, for instance

$(foo Show show)

should translate to:

[(show :: Int - String),  (show :: Bool - String), ]

for all instances currently in scope.

I'm currently playing with the isInstance function (I'm running GHC 7.4.1)
and can get a list of instances, and check if a given type is part of a
typeclass or not. But I don't know how to create the expression
corresponding to instantiated function, as above.

Thanks!
-- 
Ismael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: Generate annotated function of a typeclass

2012-04-13 Thread 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 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.  Then, you can apply these mappings with substT:
http://hackage.haskell.org/packages/archive/haskell-src-meta/0.5.1.2/doc/html/Language-Haskell-Meta-Utils.html#v:substT

The result would also need to have the context of the instance,
perhaps reduced to just the constraints that mention the type
variables used in the selected function.

-Michael Sloan

On Fri, Apr 13, 2012 at 11:37 AM, Ismael Figueroa Palet
ifiguer...@gmail.com wrote:
 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
 corresponding to the type-annotated instances, for instance

 $(foo Show show)

 should translate to:

 [(show :: Int - String),  (show :: Bool - String), ]

 for all instances currently in scope.

 I'm currently playing with the isInstance function (I'm running GHC 7.4.1)
 and can get a list of instances, and check if a given type is part of a
 typeclass or not. But I don't know how to create the expression
 corresponding to instantiated function, as above.

 Thanks!
 --
 Ismael


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: Generate annotated function of a typeclass

2012-04-13 Thread 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

Cheers!


2012/4/13 Michael Sloan mgsl...@gmail.com

 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.  Then, you can apply these mappings with substT:

 http://hackage.haskell.org/packages/archive/haskell-src-meta/0.5.1.2/doc/html/Language-Haskell-Meta-Utils.html#v:substT

 The result would also need to have the context of the instance,
 perhaps reduced to just the constraints that mention the type
 variables used in the selected function.

 -Michael Sloan

 On Fri, Apr 13, 2012 at 11:37 AM, Ismael Figueroa Palet
 ifiguer...@gmail.com wrote:
  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
  corresponding to the type-annotated instances, for instance
 
  $(foo Show show)
 
  should translate to:
 
  [(show :: Int - String),  (show :: Bool - String), ]
 
  for all instances currently in scope.
 
  I'm currently playing with the isInstance function (I'm running GHC
 7.4.1)
  and can get a list of instances, and check if a given type is part of a
  typeclass or not. But I don't know how to create the expression
  corresponding to instantiated function, as above.
 
  Thanks!
  --
  Ismael
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 




-- 
Ismael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sometimes sees hidden constructors

2011-05-30 Thread Nicolas Frisby
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 an
alpha-equivalent type does exhibit it in my larger program.

On Fri, May 27, 2011 at 12:04 PM, Nicolas Frisby
nicolas.fri...@gmail.com wrote:
 With 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 reify each of the data types. For T, T2, N1, and N4, their
 construct is visible in the Info even though M doesn't export it.

 As a consequence, you can load Unhide with no errors. Thus c = C, c2 =
 C2, w1 = N1, and w4 = N4, even though those constructors were not
 supposed to be imported.

 I couldn't find any mention of this on the GHC Trac for Template
 Haskell or for a general search of reify.

  * http://j.mp/l9Ztjz (Description contains reify)
  * http://j.mp/mprUmq (Component = Template Haskell)
  * Disclaimer: I didn't take the time to inspect this one
 http://hackage.haskell.org/trac/ghc/ticket/4946

 T is isomorphic to (), T2 is like T with a phantom type argument, N1
 is a newtype wrapping an Int, and N4 is like N3 with a phantom type
 variable. This seems too inconsistent to be an intended behavior. Am I
 missing something? Thanks.

 == M.hs ==
 module M (T(), T1(), T2(), T3(), T4(), N1(), N3(), N4()) where

 data T = C
 data T1 = C1 Int
 data T2 a = C2
 data T3 a = C3 a
 data T4 a = C4 Int
 newtype N1 = W1 Int
 newtype N3 a = W3 a
 newtype N4 a = W4 Int

 == Dump.hs ==
 {-# LANGUAGE TemplateHaskell #-}

 module Dump where

 import Language.Haskell.TH
 import M

 dumpT, dumpT1, dumpT2, dumpT3, dumpT4, dumpN1, dumpN3, dumpN4 :: ()
 dumpT = $(reify ''T = fail . show)
 dumpT1 = $(reify ''T1 = fail . show)
 dumpT2 = $(reify ''T2 = fail . show)
 dumpT3 = $(reify ''T3 = fail . show)
 dumpT4 = $(reify ''T4 = fail . show)
 dumpN1 = $(reify ''N1 = fail . show)
 dumpN3 = $(reify ''N3 = fail . show)
 dumpN4 = $(reify ''N4 = fail . show)

 == Unhide.hs ==
 {-# LANGUAGE TemplateHaskell #-}

 module Unhide where

 import Language.Haskell.TH
 import M

 c :: T
 c = $((\(TyConI (DataD _ _ _ [NormalC n _] _)) - ConE n) `fmap` reify ''T)
 c2 :: T2 a
 c2 = $((\(TyConI (DataD _ _ _ [NormalC n _] _)) - ConE n) `fmap` reify ''T2)
 w1 :: Int - N1
 w1 = $((\(TyConI (NewtypeD _ _ _ (NormalC n _) _)) - ConE n) `fmap` reify 
 ''N1)
 w4 :: Int - N4 a
 w4 = $((\(TyConI (NewtypeD _ _ _ (NormalC n _) _)) - ConE n) `fmap` reify 
 ''N4)



 - for convenience, this is what I get when I load Dump in ghci

 Dump.hs:9:11:
    TyConI (DataD [] M.T [] [NormalC M.C []] [])
    In the expression: $(reify 'T = fail . show)
    In an equation for `dumpT': dumpT = $(reify 'T = fail . show)

 Dump.hs:10:12:
    TyConI (DataD [] M.T1 [] [] [])
    In the expression: $(reify 'T1 = fail . show)
    In an equation for `dumpT1': dumpT1 = $(reify 'T1 = fail . show)

 Dump.hs:11:12:
    TyConI (DataD [] M.T2 [PlainTV a_1627390697] [NormalC M.C2 []] [])
    In the expression: $(reify 'T2 = fail . show)
    In an equation for `dumpT2': dumpT2 = $(reify 'T2 = fail . show)

 Dump.hs:12:12:
    TyConI (DataD [] M.T3 [PlainTV a_1627390696] [] [])
    In the expression: $(reify 'T3 = fail . show)
    In an equation for `dumpT3': dumpT3 = $(reify 'T3 = fail . show)

 Dump.hs:13:12:
    TyConI (DataD [] M.T4 [PlainTV a_1627390695] [] [])
    In the expression: $(reify 'T4 = fail . show)
    In an equation for `dumpT4': dumpT4 = $(reify 'T4 = fail . show)

 Dump.hs:14:12:
    TyConI (NewtypeD [] M.N1 [] (NormalC M.W1 [(NotStrict,ConT
 GHC.Types.Int)]) [])
    In the expression: $(reify 'N1 = fail . show)
    In an equation for `dumpN1': dumpN1 = $(reify 'N1 = fail . show)

 Dump.hs:15:12:
    TyConI (DataD [] M.N3 [PlainTV a_1627390694] [] [])
    In the expression: $(reify 'N3 = fail . show)
    In an equation for `dumpN3': dumpN3 = $(reify 'N3 = fail . show)

 Dump.hs:16:12:
    TyConI (NewtypeD [] M.N4 [PlainTV a_1627390693] (NormalC M.W4
 [(NotStrict,ConT GHC.Types.Int)]) [])
    In the expression: $(reify 'N4 = fail . show)
    In an equation for `dumpN4': dumpN4 = $(reify 'N4 = fail . show)
 Failed, modules loaded: M.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell sometimes sees hidden constructors

2011-05-27 Thread Nicolas Frisby
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 reify each of the data types. For T, T2, N1, and N4, their
construct is visible in the Info even though M doesn't export it.

As a consequence, you can load Unhide with no errors. Thus c = C, c2 =
C2, w1 = N1, and w4 = N4, even though those constructors were not
supposed to be imported.

I couldn't find any mention of this on the GHC Trac for Template
Haskell or for a general search of reify.

 * http://j.mp/l9Ztjz (Description contains reify)
 * http://j.mp/mprUmq (Component = Template Haskell)
 * Disclaimer: I didn't take the time to inspect this one
http://hackage.haskell.org/trac/ghc/ticket/4946

T is isomorphic to (), T2 is like T with a phantom type argument, N1
is a newtype wrapping an Int, and N4 is like N3 with a phantom type
variable. This seems too inconsistent to be an intended behavior. Am I
missing something? Thanks.

== M.hs ==
module M (T(), T1(), T2(), T3(), T4(), N1(), N3(), N4()) where

data T = C
data T1 = C1 Int
data T2 a = C2
data T3 a = C3 a
data T4 a = C4 Int
newtype N1 = W1 Int
newtype N3 a = W3 a
newtype N4 a = W4 Int

== Dump.hs ==
{-# LANGUAGE TemplateHaskell #-}

module Dump where

import Language.Haskell.TH
import M

dumpT, dumpT1, dumpT2, dumpT3, dumpT4, dumpN1, dumpN3, dumpN4 :: ()
dumpT = $(reify ''T = fail . show)
dumpT1 = $(reify ''T1 = fail . show)
dumpT2 = $(reify ''T2 = fail . show)
dumpT3 = $(reify ''T3 = fail . show)
dumpT4 = $(reify ''T4 = fail . show)
dumpN1 = $(reify ''N1 = fail . show)
dumpN3 = $(reify ''N3 = fail . show)
dumpN4 = $(reify ''N4 = fail . show)

== Unhide.hs ==
{-# LANGUAGE TemplateHaskell #-}

module Unhide where

import Language.Haskell.TH
import M

c :: T
c = $((\(TyConI (DataD _ _ _ [NormalC n _] _)) - ConE n) `fmap` reify ''T)
c2 :: T2 a
c2 = $((\(TyConI (DataD _ _ _ [NormalC n _] _)) - ConE n) `fmap` reify ''T2)
w1 :: Int - N1
w1 = $((\(TyConI (NewtypeD _ _ _ (NormalC n _) _)) - ConE n) `fmap` reify ''N1)
w4 :: Int - N4 a
w4 = $((\(TyConI (NewtypeD _ _ _ (NormalC n _) _)) - ConE n) `fmap` reify ''N4)



- for convenience, this is what I get when I load Dump in ghci

Dump.hs:9:11:
TyConI (DataD [] M.T [] [NormalC M.C []] [])
In the expression: $(reify 'T = fail . show)
In an equation for `dumpT': dumpT = $(reify 'T = fail . show)

Dump.hs:10:12:
TyConI (DataD [] M.T1 [] [] [])
In the expression: $(reify 'T1 = fail . show)
In an equation for `dumpT1': dumpT1 = $(reify 'T1 = fail . show)

Dump.hs:11:12:
TyConI (DataD [] M.T2 [PlainTV a_1627390697] [NormalC M.C2 []] [])
In the expression: $(reify 'T2 = fail . show)
In an equation for `dumpT2': dumpT2 = $(reify 'T2 = fail . show)

Dump.hs:12:12:
TyConI (DataD [] M.T3 [PlainTV a_1627390696] [] [])
In the expression: $(reify 'T3 = fail . show)
In an equation for `dumpT3': dumpT3 = $(reify 'T3 = fail . show)

Dump.hs:13:12:
TyConI (DataD [] M.T4 [PlainTV a_1627390695] [] [])
In the expression: $(reify 'T4 = fail . show)
In an equation for `dumpT4': dumpT4 = $(reify 'T4 = fail . show)

Dump.hs:14:12:
TyConI (NewtypeD [] M.N1 [] (NormalC M.W1 [(NotStrict,ConT
GHC.Types.Int)]) [])
In the expression: $(reify 'N1 = fail . show)
In an equation for `dumpN1': dumpN1 = $(reify 'N1 = fail . show)

Dump.hs:15:12:
TyConI (DataD [] M.N3 [PlainTV a_1627390694] [] [])
In the expression: $(reify 'N3 = fail . show)
In an equation for `dumpN3': dumpN3 = $(reify 'N3 = fail . show)

Dump.hs:16:12:
TyConI (NewtypeD [] M.N4 [PlainTV a_1627390693] (NormalC M.W4
[(NotStrict,ConT GHC.Types.Int)]) [])
In the expression: $(reify 'N4 = fail . show)
In an equation for `dumpN4': dumpN4 = $(reify 'N4 = fail . show)
Failed, modules loaded: M.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell reified type.

2011-05-10 Thread Simon Peyton-Jones
Can you give a concrete example?  There is code in GHC that is supposed 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-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.[] respectively.
| 
| This is not fair asymmetry, I think.
| 
| Also, it took purity from one of my functions while I debugged that
| problem. I had to make it into Q monad. ;)
| 
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell reified type.

2011-05-10 Thread Serguey Zefirov
I turned out that it is in ghc 6.12.

The same code in ghc 7.0.1 works just fine, Reification produces
TupleT and ListT. I just rechecked it.

I forgot that I use 6.12. Sorry about that.

2011/5/10 Simon Peyton-Jones simo...@microsoft.com:
 Can you give a concrete example?  There is code in GHC that is supposed 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-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.[] respectively.
 |
 | This is not fair asymmetry, I think.
 |
 | Also, it took purity from one of my functions while I debugged that
 | problem. I had to make it into Q monad. ;)
 |
 | ___
 | Haskell-Cafe mailing list
 | Haskell-Cafe@haskell.org
 | http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell reified type.

2011-05-09 Thread Serguey Zefirov
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 while I debugged that
problem. I had to make it into Q monad. ;)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell support for GADTs

2011-04-30 Thread Boris Lykah
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 Haskell.

I found that the GADTs produced by TH are not equivalent to the usual
ones. They require additional  extension -XTypeFamilies(for the
equality constraints) along with -XGADTs, and, which is more
important, are less type-safe. To describe the data structure I used
ForallC as it was suggested in the closed ticket
http://hackage.haskell.org/trac/ghc/ticket/3497 (Template Haskell
support for GADTs)

This is simplified code for data Sample = Sample {foo::String,
bar::Int} written manually:

data SampleField a where
  FooField :: SampleField String
  BarField :: SampleField Int

and a GADT with similar structure generated via TH.

$(do
let gadt = mkName THSampleField
let tv = mkName a
let con1 = forallC [plainTV tv] (cxt $ [equalP (varT tv) (conT
''String)]) $ normalC (mkName THFooField) []
let con2 = forallC [plainTV tv] (cxt $ [equalP (varT tv) (conT
''Int)]) $ normalC (mkName THBarField) []
result - dataD (cxt []) gadt [plainTV tv] [con1, con2] []
return [result]
 )
which produces
data THSampleField a where
  THFooField :: a ~ String = THSampleField a
  THBarField :: a ~ Int = THSampleField a

The expression
asTypeOf FooField BarField
fails to compile as expected because String cannot match Int, but
asTypeOf THFooField THBarField
is a valid expression of type (THSampleField a), which is very
confusing and breaks the existing code.

Am I missing something? If this is the only way to create the GADTs
then I think we should consider reopening the ticket.

-- 
Regards,
Boris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 gchi it seems impossible.

I have the file Test.hs:

 {-# LANGUAGE TemplateHaskell #-}
 module Test where
 import Language.Haskell.TH

 x :: ExpQ
 x = global $ mkName Data.Map.empty

When I load it in ghci, all works:

$ ghci -XTemplateHaskell Test.hs
*Test $x
Loading package pretty-1.0.1.2 ... linking ... done.
Loading package array-0.3.0.2 ... linking ... done.
Loading package containers-0.4.0.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
fromList []

But when I try to use it from other module, it fails. File Main.hs:

 {-# LANGUAGE TemplateHaskell #-}
 module Main where
 import Test

 main = do
   print $x

$ runhaskell Main.hs

Main.hs:5:9:
Not in scope: `Data.Map.empty'
In the result of the splice:
  $x
To see what the splice expanded to, use -ddump-splices
In the first argument of `print', namely `$x'
In the expression: print ($x)

--
All the best,
Alexey

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 where
 import A
 
 a = $x 

 empty =  -- No collision; the 'empty in A.hs becomes a fully qualified
-- name according to what's in scope in A.hs, so 'a' has type
-- Map k a

To avoid the import in A.hs too:

 module A where
 
 import Language.Haskell.TH
 import Language.Haskell.TH.Syntax(mkNameG_v)
 
 x = varE (mkNameG_v containers-0.4.0.0 Data.Map empty)
 
By the way, 'global' currently is a synonym for 'varE'; I guess it used to be 
something different and remains for backwards compatibility.

Cheers,
Daniel

On 2011-April-17 Sunday 18:42:15 Alexey Karakulov wrote:
 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 gchi it seems impossible.
 
 I have the file Test.hs:
  {-# LANGUAGE TemplateHaskell #-}
  module Test where
  import Language.Haskell.TH
  
  x :: ExpQ
  x = global $ mkName Data.Map.empty
 
 When I load it in ghci, all works:
 
 $ ghci -XTemplateHaskell Test.hs
 *Test $x
 Loading package pretty-1.0.1.2 ... linking ... done.
 Loading package array-0.3.0.2 ... linking ... done.
 Loading package containers-0.4.0.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 fromList []
 
 But when I try to use it from other module, it fails. File Main.hs:
  {-# LANGUAGE TemplateHaskell #-}
  module Main where
  import Test
  
  main = do
  
print $x
 
 $ runhaskell Main.hs
 
 Main.hs:5:9:
 Not in scope: `Data.Map.empty'
 In the result of the splice:
   $x
 To see what the splice expanded to, use -ddump-splices
 In the first argument of `print', namely `$x'
 In the expression: print ($x)
 
 --
 All the best,
 Alexey
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell tutorials?

2011-04-14 Thread Zoe Clifford
On Wed, Apr 13, 2011 at 10:43 PM, Kenneth Hoste kenneth.ho...@gmail.com 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?

 greetings,
 Kenneth

 If all else fails, it's still accessable via the wayback machine.

http://replay.waybackmachine.org/20090418034412/http://www.haskell.org/bz/thdoc.htm

and

http://replay.waybackmachine.org/20090421010040/http://www.haskell.org/bz/th3.htm

-Zoe
(hopefully I've figured out this mailing list thing right)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell tutorials?

2011-04-13 Thread Kenneth Hoste
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___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2011-01-18 Thread Ian Lynagh
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.
  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 the package lang or the
  module Generic comes from. Can someone enlighten me?
  
  The package 'syb' - 'scrap your boilerplate' looks quite similar.
 
 Yes, thanks. So the documentation should be updated
 to say package syb and module Data.Generics.
 
 @Ian, can you take care of this (without ticket)?

Done, ta.


Thanks
Ian


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2011-01-04 Thread Christian Maeder
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 compiler could be told to unfold an
 expression like
   parse text in a domain specific language
  at compile time.
 
 #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 the package lang or the
module Generic comes from. Can someone enlighten me?

I didn't find package lang on hackage.

Cheers Christian

7.16.1.  Using generics

To use generics you need to

*

  Use the flags -fglasgow-exts (to enable the extra syntax),
-XGenerics (to generate extra per-data-type code), and -package lang (to
make the Generics library available.
*

  Import the module Generics from the lang package. This import
brings into scope the data types Unit, :*:, and :+:. (You don't need
this import if you don't mention these types explicitly; for example, if
you are simply giving instance declarations.)




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2011-01-04 Thread Dominique Devriese
All,

2010/12/27 Jonathan Geddes geddes.jonat...@gmail.com:
 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 sometimes used in its generality: as a
general compile time meta-programming facility. For example, in my
experimental grammar-combinators parsing library [1], I am using it to
perform grammar transformations at compile time by simply generating
the definition for the transformed grammar using TH. This could be
extended in the future to provide a low-cost parser generator that
works from within TH, which can reuse the library's infrastructure.

Dominique

[1] http://projects.haskell.org/grammar-combinators/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2011-01-04 Thread 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-classes.html
 
 I see the text below and have no idea where the package lang or the
 module Generic comes from. Can someone enlighten me?

The package 'syb' - 'scrap your boilerplate' looks quite similar.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2011-01-04 Thread Christian Maeder
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-classes.html

 I see the text below and have no idea where the package lang or the
 module Generic comes from. Can someone enlighten me?
 
 The package 'syb' - 'scrap your boilerplate' looks quite similar.

Yes, thanks. So the documentation should be updated
to say package syb and module Data.Generics.

@Ian, can you take care of this (without ticket)?

Christian

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-28 Thread Tillmann Rendel

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
}
|]


causes the function json to be called at compile time with a string
argument of{\name\ : \Jonathan\\n   , \favorite language\:
\Haskell\\n   }. The whole expression being then replaced with the
result of the function application. What I like about this is that
defining quasiquoters is trivial. They're just functions of the form
String -  a. Many such quasiquoters already exist and would be ready
for use! I imagine certain rules would apply, ie a quasiquoter must be
defined prior to use and in a separate module, etc.


First note that this is just quotation, not yet quasiquotation. For 
quasiquotation, you would also need to support antiquotation (i.e., the 
use of Haskell identifiers or even expressions in the middle of quoted 
syntax). And to reach something similar to the current support for 
quasiquotation, you would need to support patterns etc., too.



Secondly, I was going to propose to use generic programming to convert 
from a parser like (String - JsonObject) to a quasiquoter for Json. But 
after half a day of experiments, I figured out that this idea is already 
developed in


  Geoffrey B. Mainland.
  Why It's Nice to be Quoted: Quasiquoting for Haskell.
  Haskell Workshop 2007

  Available at:

http://www.eecs.harvard.edu/~mainland/publications/mainland07quasiquoting.pdf

In that paper, Geoffrey Mainland explains how a parser can be 
generically upgraded to a quoter, reaching an intermediate conclusion on 
page 6:

By using generic programming, we can take a parser and create
expression and pattern quasiquoters for the language it parses with
only four lines of code, including type signatures! This holds not
just for our simple object language, but for any object language.


He goes on to explain how to add support for antiquotation [...] with 
only slightly more than four lines of code.



The functions dataToExpQ and dataToPatQ from that paper are available in 
the TH library in Language.Haskell.TH.Quote. A simple helper function


  quasiQuoter :: Data a = (String - Either String a) - QuasiQuoter
  quasiQuoter parser = QuasiQuoter
{ quoteExp = either fail (dataToExpQ (const Nothing)) . parse
, quotePat = either fail (dataToPatQ (const Nothing)) . parse
}

should allow you to write your JSON example as follows:

  parse :: String - Either String JsonObject
  parse = ...

  json = quasiQuoter parse

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.


  Tillmann

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-28 Thread Jonathan Geddes
On Tue, Dec 28, 2010 at 8:17 AM, Tillmann Rendel
ren...@mathematik.uni-marburg.de 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.

In the original post I said, It may very well be that I am simply not
experienced enough with TH to fully appreciate and embrace it. More
and more I am thinking this is the case. I'll have to give TH a more
thorough look.

BTW, in addition to the resources already given, can anyone suggest
materials for my aforementioned more thorough look?

Thanks again for the responses.

--Jonathan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Stephen Tetley
On 27 December 2010 07:35, Jonathan Geddes geddes.jonat...@gmail.com 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 Glasgow Haskell, taking it out of the domain of Template
Haskell?

How would the first example look like with Template Haskell and is
current quasiquoting syntax? I'm suspecting the differences are pretty
small.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Jonas Almström Duregård
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 approach is to have language support (through extensions)
for primitive operations like splicing, and to have libraries that combine
these operations into more complex systems (like automatic derivation of
type classes).

 Again, TH is very powerful, and fills in a number of holes in
 Haskell's feature set. But it leaves me wondering if these holes
 should not be filled in by other, more specialized features, leaving
 TH to continue to find other holes to fill.

Shouldn't specialized features be defined in terms of general features?

 json :: String - JsonObject
 json = ...

 data = [ json |
{ name : Jonathan
, favorite language: Haskell
}
|]

How does this differ from the current QuasiQuotes extension? From what I can
tell, all you need to achieve this with TH is to automatically derive a
Language.Haskell.TH.Lift instance for JsonObject, i.e. a  function lift ::
JsonObject - Q Exp such that the expression will evaluate to the original
JsonObject. A QuasiQuoter like the one you describe can then be created by
QuasiQuoter { parseExp = lift . json }. Should both approaches be supported
directly, or should we sacrifice the generality of the current quoters for
the simplicity of the ones you suggest?


The second part (deriving instances for general type classes) is a lot more
complicated. I would say that the most general way of showing that a class
can be derived is to provide a function that produces a set of declarations
given the name of the datatype. Here's a very simple suggestion for
incorporating this into the Haskell deriving syntax. Suppose we have these
two classes and TH functions for deriving them:

class Class1 ...
class Class2 ...

class1 :: Name - Q [Dec]
class2 :: Name - Q [Dec]

data D = D deriving (Show,class1,class2)

The last declaration could expand to:

data D = D deriving Show
class1 'D
class2 'D

If you don't want to write class1 and class2 by operating directly on
Haskell declarations, but rather use some DSL for specifying instances, then
all you need is a function deriv :: DerivationDSL - (Name - Q [Dec]).

/J

On 27 December 2010 08:35, Jonathan Geddes geddes.jonat...@gmail.com
wrote:
 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 and built-in
 syntax (via an extension) which feels strange to me. Finally, It's
 very complicated to do some simple things.

 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.

 I would propose that more specialized features be implemented to
 accomplish these tasks. To start, I'll throw out some ideas that
 provide these capabilities.

 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
}
|]

 causes the function json to be called at compile time with a string
 argument of{\name\ : \Jonathan\\n   , \favorite language\:
 \Haskell\\n   }. The whole expression being then replaced with the
 result of the function application. What I like about this is that
 defining quasiquoters is trivial. They're just functions of the form
 String - a. Many such quasiquoters already exist and would be ready
 for use! I imagine certain rules would apply, ie a quasiquoter must be
 defined prior to use and in a separate module, etc.

 For TH use #2, automatic instances, I would propose a way of declaring
 that a class can be automatically derived, and therefore added to the
 set [Eq, Ord, Show, Read, ... , etc]. This is the set of classes that
 can be put in the deriving clause of a type declaration. I don't
 know exactly what the syntax for this would look like, but I imagine
 it would look a bit like the various current implementations of
 automatic instances in TH.

 Again, TH is very powerful, and fills in a number of holes in
 Haskell's feature set. But it leaves me wondering if these holes
 should not be filled in by other, more specialized features, leaving
 TH to continue to find other holes to fill.

 I'm wondering if others see TH as a permanent solution, or if you
 agree with me that some of TH's most common usages should have more
 specialized features dedicated to them. It may very well be that I am
 simply not experienced 

Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Jonas Almström Duregård
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 TH without a reason.

/J

On 27 December 2010 08:44, Henning Thielemann lemm...@henning-thielemann.de
 wrote:


 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 a domain specific language
  at compile time.

  #2 Provide instances automatically.



 http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/generic-classes.html


 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. For the cases where Template Haskell is really needed, I'd prefer a
 solution that allows to generate the code before compilation, such that
 packages with automatically generated code can be run also on compilers that
 do not support Template Haskell.


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Henning Thielemann


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 just 
curious as to why you
would venture into the realm of TH without a reason.


E.g. refer to the recent discussion of storable-endian.

http://www.haskell.org/pipermail/haskell-cafe/2010-December/087551.html

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 parsed content is unfolded at 
compile time. It could even be computed at runtime, since it is only 
computed once because of laziness.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Ivan Lazar Miljenovic
2010/12/27 Henning Thielemann lemm...@henning-thielemann.de:
 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 parsed content is unfolded at compile
 time. It could even be computed at runtime, since it is only computed once
 because of laziness.

http://hackage.haskell.org/package/zeroth ?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Jonathan Geddes
On Mon, Dec 27, 2010 at 12:44 AM, Henning Thielemann
lemm...@henning-thielemann.de 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 string should be parsed at compile time is only half of the
equation in my mind. The other half is the clean syntax for multi-line
strings.

Haskell already has great syntax for specifying data in a declarative
manner. Especially in contrast with ie Java/C++. Even as good as the
dynamic languages ie JavaScript/Python/Ruby. When you add the ability
to specify data in ANY syntax you can parse, Haskell is clearly the
best. But the complexity of TH detracts from the elegance of this
greatly in my opinion. And wrapping your data in string syntax,
multi-line or otherwise, detracts from the elegance as well. A syntax
has to be less painful or more convenient or more
readable/maintainable than literal list/record syntax before it is
useful.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Jonathan Geddes
On Mon, Dec 27, 2010 at 1:14 AM, Stephen Tetley
stephen.tet...@gmail.com 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 things could coexist with TH. I just can't see TH
becoming standard. I think something much simpler that accomplishes
the common uses of TH is more likely to make it into Haskell'
20[1-2]x.

--Jonathan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-27 Thread Jonathan Geddes
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 defined in terms of general features?

Absolutely, but usually don't you use the specialized features over
general ones where you can? For example, I don't often (if ever) use
the general feature of the goto statement in C. Instead I use
conditionals, loops, and functions. I don't often write explicitly
recursive functions in Haskell, rather I use map, filter, fold, etc.
whenever the structure of the recursion allows.

 How does this differ from the current QuasiQuotes extension? From what I can
 tell, all you need to achieve this with TH is to automatically derive a
 Language.Haskell.TH.Lift instance for JsonObject, i.e. a  function lift ::
 JsonObject - Q Exp such that the expression will evaluate to the original
 JsonObject. A QuasiQuoter like the one you describe can then be created by
 QuasiQuoter { parseExp = lift . json }.

Right, it's not a lot of extra work. But it's enough that in most
cases, I stick with constructing records or using other built-in
syntax.

 Should both approaches be supported
 directly, or should we sacrifice the generality of the current quoters for
 the simplicity of the ones you suggest?

No, I don't think TH should be sacrificed. I just think more specific
(and more simple) features might be nice in place of some of TH's
specific uses.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell a Permanent solution?

2010-12-26 Thread Jonathan Geddes
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 and built-in
syntax (via an extension) which feels strange to me. Finally, It's
very complicated to do some simple things.

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.

I would propose that more specialized features be implemented to
accomplish these tasks. To start, I'll throw out some ideas that
provide these capabilities.

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
}
|]

causes the function json to be called at compile time with a string
argument of{\name\ : \Jonathan\\n   , \favorite language\:
\Haskell\\n   }. The whole expression being then replaced with the
result of the function application. What I like about this is that
defining quasiquoters is trivial. They're just functions of the form
String - a. Many such quasiquoters already exist and would be ready
for use! I imagine certain rules would apply, ie a quasiquoter must be
defined prior to use and in a separate module, etc.

For TH use #2, automatic instances, I would propose a way of declaring
that a class can be automatically derived, and therefore added to the
set [Eq, Ord, Show, Read, ... , etc]. This is the set of classes that
can be put in the deriving clause of a type declaration. I don't
know exactly what the syntax for this would look like, but I imagine
it would look a bit like the various current implementations of
automatic instances in TH.

Again, TH is very powerful, and fills in a number of holes in
Haskell's feature set. But it leaves me wondering if these holes
should not be filled in by other, more specialized features, leaving
TH to continue to find other holes to fill.

I'm wondering if others see TH as a permanent solution, or if you
agree with me that some of TH's most common usages should have more
specialized features dedicated to them. It may very well be that I am
simply not experienced enough with TH to fully appreciate and embrace
it.

By the way, did I miss any uses of TH as common as the ones I mentioned?

--Jonathan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-26 Thread 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 compiler could be told to unfold an 
expression like

  parse text in a domain specific language
 at compile time.


#2 Provide instances automatically.


http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/generic-classes.html


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. For the cases where Template Haskell is really needed, I'd prefer a 
solution that allows to generate the code before compilation, such that 
packages with automatically generated code can be run also on compilers 
that do not support Template Haskell.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell: exchanging information between 'splicers'

2010-11-26 Thread jean-christophe mincke
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-02 Thread Paolino
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 Latter aslat...@gmail.com

 2010/11/1 Paolino paolo.verone...@gmail.com:
  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 is printing some strange type variables but it
  compiles
 

 Template Haskell might be overkill for this. In the past, I've done:

  class (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b
  instance (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b

 I think this requires a couple of GHC extensions, but TemplateHaskell
 is an extension as well. Maybe there are pitfalls with this approach.

 Antoine

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-02 Thread Gábor Lehel
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 generate nontrivial instances of some class for
user-provided types, Template Haskell is frequently what you need to
use.

2010/11/2 Paolino paolo.verone...@gmail.com:
 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 Latter aslat...@gmail.com

 2010/11/1 Paolino paolo.verone...@gmail.com:
  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 is printing some strange type variables but it
  compiles
 

 Template Haskell might be overkill for this. In the past, I've done:

  class (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b
  instance (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b

 I think this requires a couple of GHC extensions, but TemplateHaskell
 is an extension as well. Maybe there are pitfalls with this approach.

 Antoine





-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
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 some hints on how to arrive there.

Thanks

paolino
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Christopher Done
On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com 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 code around, I
 ask here for the code, or some hints on how to arrive there.

I took Justin Bailey's haskelldb-th library as a TH example to work
from and rewrote one TH function to try my hand at it, it's quite easy
to follow with a simple example:

http://hpaste.org/paste/41035/demo

Maybe this is enough example to get you going. The rest you can find
syntax parts from the TH Haddock documentation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Gábor Lehel
On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done
chrisd...@googlemail.com wrote:
 On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com 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 code around, I
 ask here for the code, or some hints on how to arrive there.

 I took Justin Bailey's haskelldb-th library as a TH example to work
 from and rewrote one TH function to try my hand at it, it's quite easy
 to follow with a simple example:

 http://hpaste.org/paste/41035/demo

 Maybe this is enough example to get you going. The rest you can find
 syntax parts from the TH Haddock documentation.

A useful FYI: the API docs are (almost) completely devoid of comments,
but if you click to see the source, it does have some additional
information in comments there, just not Haddock-formatted.


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
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 illiss...@gmail.com

 On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done
 chrisd...@googlemail.com wrote:
  On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com 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 code
 around, I
  ask here for the code, or some hints on how to arrive there.
 
  I took Justin Bailey's haskelldb-th library as a TH example to work
  from and rewrote one TH function to try my hand at it, it's quite easy
  to follow with a simple example:
 
  http://hpaste.org/paste/41035/demo
 
  Maybe this is enough example to get you going. The rest you can find
  syntax parts from the TH Haddock documentation.

 A useful FYI: the API docs are (almost) completely devoid of comments,
 but if you click to see the source, it does have some additional
 information in comments there, just not Haddock-formatted.


  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Work is punishment for failing to procrastinate effectively.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread 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

$(classSynonym ''SClass)

ghci :i SClass command is printing some strange type variables but it
compiles

paolino

2010/11/1 Gábor Lehel illiss...@gmail.com

 On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done
 chrisd...@googlemail.com wrote:
  On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com 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 code
 around, I
  ask here for the code, or some hints on how to arrive there.
 
  I took Justin Bailey's haskelldb-th library as a TH example to work
  from and rewrote one TH function to try my hand at it, it's quite easy
  to follow with a simple example:
 
  http://hpaste.org/paste/41035/demo
 
  Maybe this is enough example to get you going. The rest you can find
  syntax parts from the TH Haddock documentation.

 A useful FYI: the API docs are (almost) completely devoid of comments,
 but if you click to see the source, it does have some additional
 information in comments there, just not Haddock-formatted.


  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Work is punishment for failing to procrastinate effectively.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Antoine Latter
2010/11/1 Paolino paolo.verone...@gmail.com:
 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 is printing some strange type variables but it
 compiles


Template Haskell might be overkill for this. In the past, I've done:

 class (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b
 instance (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b

I think this requires a couple of GHC extensions, but TemplateHaskell
is an extension as well. Maybe there are pitfalls with this approach.

Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: onward and upward

2010-10-19 Thread Brandon Moore
From: Simon Peyton-Jones simo...@microsoft.com
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/Template%20Haskell%20Proposal
 
Do let me know what you think.  Discussion by email is fine (cc me if it’s on 
Haskell-cafe), or comments direct on the Trac.  

A and B are both excellent ideas.

Less typechecking makes it easier to provide sugar for operations that
cannot be expressed nicely in the current type system, and also to
experiment with syntax. One example is

$(tmap 'Con [| [a, b, c, d] |]) = [Con a, Con b, Con c, Con d]

Another would be experimenting with monadic-case syntax
by making a macro that rewrites top-level case statements in
a quoted do block.

Case B starts to provide the sorts of static guarantees that
begin to justify (by using the result) the restrictions imposed
by typechecking splices ahead of time.

In D, adding a parseHaskell quasiquoter is an excellent idea.

This should be the proper fixpoint including all the current quasiquoters.
That might be easier to implement if the Haskell parser is passed as an argument
to the quasiquoters, rather than exposed as a binding in a module.

Brandon




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell: onward and upward

2010-10-18 Thread Simon Peyton-Jones
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 email is fine (cc me if it's on 
Haskell-cafe), or comments direct on the Trac.

(None of this will be in GHC 7.0; it's a proposed plan for post-release 
improvements.)

Thanks

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: onward and upward

2010-10-18 Thread Gregory Crosswhite
 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 identifier with a computed name I have to build up the AST 
manually rather than by using quoters since there is no way to splice an 
identifier name into a quoter.  Does this mean that it will not be 
possible to construct a TExp with a computed identifier name, since one 
can only use the quoter syntax and not manual construction?


Thanks,
Greg

On 10/18/10 3:02 PM, Simon Peyton-Jones wrote:


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 email is fine (cc me if 
it's on Haskell-cafe), or comments direct on the Trac.


(None of this will be in GHC 7.0; it's a proposed plan for 
post-release improvements.)


Thanks

Simon


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell: hiding declarations

2010-10-04 Thread 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 into the module header (i.e. into the export
list), I cant think of a good way to hide the internal declarations.
One way would be to put all the declarations into one or several
where-clauses, but this doesn't work very well when several functions
share the hidden declarations. Also I might want to hide a few data
types.

Does anyone have a clever solution? Has anyone had a similar problem
(maybe TH needs to be extended with support for hidden declarations)?

/J
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: hiding declarations

2010-10-04 Thread Vo Minh Thu
2010/10/4 Jonas Almström Duregård jonas.dureg...@chalmers.se:
 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), I cant think of a good way to hide the internal declarations.
 One way would be to put all the declarations into one or several
 where-clauses, but this doesn't work very well when several functions
 share the hidden declarations. Also I might want to hide a few data
 types.

 Does anyone have a clever solution? Has anyone had a similar problem
 (maybe TH needs to be extended with support for hidden declarations)?

Maybe this, although I guess this is what you mean by doesn't work very well:

(a,b,c,d,...) = (a,b,c,d,...) -- those areyour top-level declarations
  where
  a = ...
  b = ...
  c = ...
  d = ...
  ...
  all you other code

Cheers,
Thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell: hiding declarations

2010-10-04 Thread Liam O'Connor
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 not...@gmail.com:
 2010/10/4 Jonas Almström Duregård jonas.dureg...@chalmers.se:
 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), I cant think of a good way to hide the internal declarations.
 One way would be to put all the declarations into one or several
 where-clauses, but this doesn't work very well when several functions
 share the hidden declarations. Also I might want to hide a few data
 types.

 Does anyone have a clever solution? Has anyone had a similar problem
 (maybe TH needs to be extended with support for hidden declarations)?

 Maybe this, although I guess this is what you mean by doesn't work very 
 well:

 (a,b,c,d,...) = (a,b,c,d,...) -- those areyour top-level declarations
  where
  a = ...
  b = ...
  c = ...
  d = ...
  ...
  all you other code

 Cheers,
 Thu
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread 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 it. The generated code is then type
checked in this module. If constructors that are not exported are used
in the generated code, I believe you will get an error.

This could still be an issue because your TH code won't know if the
constructors are exported or not, but i doubt you can actually do
things with TH that you can't do with plain H.

 At least, it looks like I can, I didn't tried, actually.

Neither have I.

/J

On 4 July 2010 01:10, Serguey Zefirov sergu...@gmail.com wrote:
 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
 |   sizeOf = Map.size
 `

 Those are trivial. They are not interesting.

 I cannot write classes that see into internal structure. For example,
 I cannot write my own (de)serialization without using from/toAscList.

 This is somewhat strange situation.
 Was it a design decision?
 The reason that they are exported abstractly is so that you don't see
 the internals of the data structure, because 1) you don't need to, and
 2) to stop you from doing anything stupid with them.

 I was talking about successful reification of abstract data types.

 That way I can do anything stupid with them.

 At least, it looks like I can, I didn't tried, actually.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread Serguey Zefirov
2010/7/28 Jonas Almström Duregård jonas.dureg...@gmail.com:
 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 this module. If constructors that are not exported are used
 in the generated code, I believe you will get an error.

 This could still be an issue because your TH code won't know if the
 constructors are exported or not, but i doubt you can actually do
 things with TH that you can't do with plain H.

I doubt that doubt first. ;)

 At least, it looks like I can, I didn't tried, actually.
 Neither have I.

So I did. And succeed: TH sees into data types.

(ghc 6.12.1)

Module A.hs, contains definition of abstract data type A, class Class
and some primitive instance generator for that Class. Instance
generator takes a data declaration name, takes first constructor
(which should be argumentless) and makes it a value for definition of
c function.
--
{-# LANGUAGE TemplateHaskell #-}

module A(A,Class(..),mkSimpleClass) where

import Language.Haskell.TH

data A = A1 | A2
deriving Show

class Class a where
c :: a

mkSimpleClass :: Name - Q [Dec]
mkSimpleClass name = do
TyConI (DataD [] dname [] cs _) - reify name
((NormalC conname []):_) - return cs
ClassI (ClassD [] cname [_] [] [SigD mname _]) - reify ''Class
return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
[Clause [] (NormalB (ConE conname)) [
--

Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
--
{-# LANGUAGE TemplateHaskell #-}

module B where

import A

$(mkSimpleClass ''A)
--

I successfully loaded B.hs into ghci, Expression c :: A successfully
evaluates to A1.

My view on that problem is that we can add TyConIAbs for incompletely
exported and abstract data types.

When someone get TyConIAbs after reification, he will know that he
doesn't know everything about that type.

So, empty data declaration like data Z will return TyConI with empty
list of constructors, TyConIAbs will have empty list of constructors
for abstract data type.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread Gábor Lehel
2010/7/28 Serguey Zefirov sergu...@gmail.com:
 2010/7/28 Jonas Almström Duregård jonas.dureg...@gmail.com:
 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 this module. If constructors that are not exported are used
 in the generated code, I believe you will get an error.

 This could still be an issue because your TH code won't know if the
 constructors are exported or not, but i doubt you can actually do
 things with TH that you can't do with plain H.

 I doubt that doubt first. ;)

 At least, it looks like I can, I didn't tried, actually.
 Neither have I.

 So I did. And succeed: TH sees into data types.

 (ghc 6.12.1)

 Module A.hs, contains definition of abstract data type A, class Class
 and some primitive instance generator for that Class. Instance
 generator takes a data declaration name, takes first constructor
 (which should be argumentless) and makes it a value for definition of
 c function.
 --
 {-# LANGUAGE TemplateHaskell #-}

 module A(A,Class(..),mkSimpleClass) where

 import Language.Haskell.TH

 data A = A1 | A2
        deriving Show

 class Class a where
        c :: a

 mkSimpleClass :: Name - Q [Dec]
 mkSimpleClass name = do
        TyConI (DataD [] dname [] cs _) - reify name
        ((NormalC conname []):_) - return cs
        ClassI (ClassD [] cname [_] [] [SigD mname _]) - reify ''Class
        return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
 [Clause [] (NormalB (ConE conname)) [
 --

 Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
 --
 {-# LANGUAGE TemplateHaskell #-}

 module B where

 import A

 $(mkSimpleClass ''A)
 --

 I successfully loaded B.hs into ghci, Expression c :: A successfully
 evaluates to A1.

 My view on that problem is that we can add TyConIAbs for incompletely
 exported and abstract data types.

 When someone get TyConIAbs after reification, he will know that he
 doesn't know everything about that type.

 So, empty data declaration like data Z will return TyConI with empty
 list of constructors, TyConIAbs will have empty list of constructors
 for abstract data type.

You can also export just *some* constructors, though. This would
distinguish between  module Foo (A(..)) where data A and module Foo
(A) where data A = A, but what about module Bar (B(..)) where data B
= B and module Bar (B(B)) where data B = B | C | D?



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread Gábor Lehel
On Wed, Jul 28, 2010 at 12:55 PM, Gábor Lehel illiss...@gmail.com wrote:
 2010/7/28 Serguey Zefirov sergu...@gmail.com:
 2010/7/28 Jonas Almström Duregård jonas.dureg...@gmail.com:
 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 this module. If constructors that are not exported are used
 in the generated code, I believe you will get an error.

 This could still be an issue because your TH code won't know if the
 constructors are exported or not, but i doubt you can actually do
 things with TH that you can't do with plain H.

 I doubt that doubt first. ;)

 At least, it looks like I can, I didn't tried, actually.
 Neither have I.

 So I did. And succeed: TH sees into data types.

 (ghc 6.12.1)

 Module A.hs, contains definition of abstract data type A, class Class
 and some primitive instance generator for that Class. Instance
 generator takes a data declaration name, takes first constructor
 (which should be argumentless) and makes it a value for definition of
 c function.
 --
 {-# LANGUAGE TemplateHaskell #-}

 module A(A,Class(..),mkSimpleClass) where

 import Language.Haskell.TH

 data A = A1 | A2
        deriving Show

 class Class a where
        c :: a

 mkSimpleClass :: Name - Q [Dec]
 mkSimpleClass name = do
        TyConI (DataD [] dname [] cs _) - reify name
        ((NormalC conname []):_) - return cs
        ClassI (ClassD [] cname [_] [] [SigD mname _]) - reify ''Class
        return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
 [Clause [] (NormalB (ConE conname)) [
 --

 Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
 --
 {-# LANGUAGE TemplateHaskell #-}

 module B where

 import A

 $(mkSimpleClass ''A)
 --

 I successfully loaded B.hs into ghci, Expression c :: A successfully
 evaluates to A1.

 My view on that problem is that we can add TyConIAbs for incompletely
 exported and abstract data types.

 When someone get TyConIAbs after reification, he will know that he
 doesn't know everything about that type.

 So, empty data declaration like data Z will return TyConI with empty
 list of constructors, TyConIAbs will have empty list of constructors
 for abstract data type.

 You can also export just *some* constructors, though. This would
 distinguish between  module Foo (A(..)) where data A and module Foo
 (A) where data A = A, but what about module Bar (B(..)) where data B
 = B and module Bar (B(B)) where data B = B | C | D?

Never mind -- I see you mentioned incompletely exported already.

You could also just add a Bool parameter to TyConI signifying whether
some constructors are hidden. (Also, I imagine this doesn't just apply
to data types, but also say type classes.)





 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




 --
 Work is punishment for failing to procrastinate effectively.




-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread Simon Peyton-Jones
I assume you've seen http://hackage.haskell.org/trac/ghc/ticket/4222
There are non-obvious design choices here

Simon

| -Original Message-
| From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On
| Behalf Of Serguey Zefirov
| Sent: 28 July 2010 11:07
| 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 jonas.dureg...@gmail.com:
|  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 this module. If constructors that are not exported are used
|  in the generated code, I believe you will get an error.
| 
|  This could still be an issue because your TH code won't know if the
|  constructors are exported or not, but i doubt you can actually do
|  things with TH that you can't do with plain H.
| 
| I doubt that doubt first. ;)
| 
|  At least, it looks like I can, I didn't tried, actually.
|  Neither have I.
| 
| So I did. And succeed: TH sees into data types.
| 
| (ghc 6.12.1)
| 
| Module A.hs, contains definition of abstract data type A, class Class
| and some primitive instance generator for that Class. Instance
| generator takes a data declaration name, takes first constructor
| (which should be argumentless) and makes it a value for definition of
| c function.
| --
| {-# LANGUAGE TemplateHaskell #-}
| 
| module A(A,Class(..),mkSimpleClass) where
| 
| import Language.Haskell.TH
| 
| data A = A1 | A2
|   deriving Show
| 
| class Class a where
|   c :: a
| 
| mkSimpleClass :: Name - Q [Dec]
| mkSimpleClass name = do
|   TyConI (DataD [] dname [] cs _) - reify name
|   ((NormalC conname []):_) - return cs
|   ClassI (ClassD [] cname [_] [] [SigD mname _]) - reify ''Class
|   return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
| [Clause [] (NormalB (ConE conname)) [
| --
| 
| Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
| --
| {-# LANGUAGE TemplateHaskell #-}
| 
| module B where
| 
| import A
| 
| $(mkSimpleClass ''A)
| --
| 
| I successfully loaded B.hs into ghci, Expression c :: A successfully
| evaluates to A1.
| 
| My view on that problem is that we can add TyConIAbs for incompletely
| exported and abstract data types.
| 
| When someone get TyConIAbs after reification, he will know that he
| doesn't know everything about that type.
| 
| So, empty data declaration like data Z will return TyConI with empty
| list of constructors, TyConIAbs will have empty list of constructors
| for abstract data type.
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-28 Thread Serguey Zefirov
2010/7/28 Simon Peyton-Jones simo...@microsoft.com:
 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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-26 Thread Simon Peyton-Jones
|  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 fine.

I've created a ticket for this http://hackage.haskell.org/trac/ghc/ticket/4222. 
 

In writing it down I identify several design questions that need to be 
addressed before we can fix this bug.  Help welcome.

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Serguey Zefirov
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 fine.

This is somewhat strange situation.

Was it a design decision?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Ivan Lazar Miljenovic
Serguey Zefirov sergu...@gmail.com 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 - those data types could be reified just fine.

Huh?  Sure you can write class instances for them.

,
| 
| import qualified Data.Map as Map
| import Data.Map(Map)
| import qualified Data.Set as Set
| import Data.Set(Set)
| 
| class SizeOf x where
|   sizeOf :: x - Int
| 
| instance SizeOf [a] where
|   sizeOf = length
| 
| instance SizeOf (Set a) where
|   sizeOf = Set.size
| 
| instance SizeOf (Map k v) where
|   sizeOf = Map.size
`

 This is somewhat strange situation.

 Was it a design decision?

The reason that they are exported abstractly is so that you don't see
the internals of the data structure, because 1) you don't need to, and
2) to stop you from doing anything stupid with them.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Serguey Zefirov
 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
 |   sizeOf = Map.size
 `

Those are trivial. They are not interesting.

I cannot write classes that see into internal structure. For example,
I cannot write my own (de)serialization without using from/toAscList.

 This is somewhat strange situation.
 Was it a design decision?
 The reason that they are exported abstractly is so that you don't see
 the internals of the data structure, because 1) you don't need to, and
 2) to stop you from doing anything stupid with them.

I was talking about successful reification of abstract data types.

That way I can do anything stupid with them.

At least, it looks like I can, I didn't tried, actually.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Ivan Lazar Miljenovic
Serguey Zefirov sergu...@gmail.com 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.
 ,
 | instance SizeOf (Map k v) where
 |   sizeOf = Map.size
 `

 Those are trivial. They are not interesting.

You said you couldn't write any, and of course I wrote a trivial one
because I didn't want to write a whole library in an email.

 I cannot write classes that see into internal structure. For example,
 I cannot write my own (de)serialization without using from/toAscList.

So?  What's wrong with using {from,to}AscList ?

You could also try using GHC's stand-alone deriving mechanism to derive
binary or something:

http://www.haskell.org/haskellwiki/GHC/Stand-alone_deriving_declarations

 This is somewhat strange situation.  Was it a design decision?
 The reason that they are exported abstractly is so that you don't see
 the internals of the data structure, because 1) you don't need to, and
 2) to stop you from doing anything stupid with them.

 I was talking about successful reification of abstract data types.

 That way I can do anything stupid with them.

Why do you want to?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread David Menendez
On Sat, Jul 3, 2010 at 7:20 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Serguey Zefirov sergu...@gmail.com 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.
snip
 This is somewhat strange situation.  Was it a design decision?
 The reason that they are exported abstractly is so that you don't see
 the internals of the data structure, because 1) you don't need to, and
 2) to stop you from doing anything stupid with them.

 I was talking about successful reification of abstract data types.

 That way I can do anything stupid with them.

 Why do you want to?

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.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Ivan Lazar Miljenovic
David Menendez d...@zednenem.com 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 constructors, etc. was intentional...

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/4/10 00:29 , Ivan Lazar Miljenovic wrote:
 David Menendez d...@zednenem.com 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 constructors, etc. was intentional...

No, he knew that (abstract types from the original message).  The question
was whether TH is supposed to be able to violate the abstraction barrier.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkwwEdIACgkQIn7hlCsL25W+9gCgmUI5P5wdCDXoHjqJkx5lH5U2
ZFsAnjAeCfVAsFjHBpozp1D5BFG3kCKW
=c51E
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell

2010-03-19 Thread Rafael Almeida
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
dynamic generated string for the format, but that's not a practical
drawback (I can't think of a practical reason for using anything other
than a string literal for format anyway).

Anyhow, what is gained by the template programming in that case is
really the flexibility in the type system. You can generate the function
with the correct type on the fly, during compiling. That's nice enough,
but the article keeps saying that templates are nice for implementing
your own custom compiler optimizations. I can see that you really can do
so, but I fail to think of a good practical example where templates
would be hands down the best approach. Perhaps haskellers with more
experience have real life examples they've bumped into. So, please,
share your experience with us.

[1] 
http://research.microsoft.com/en-us/um/people/simonpj/papers/meta-haskell/meta-haskell.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell

2010-03-19 Thread Brandon S. Allbery KF8NH

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 for using anything other
than a string literal for format anyway).


Localization via message files.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell

2010-03-19 Thread Stephen Tetley
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


Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-04 Thread Bulat Ziganshin
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-04 Thread Gregory Crosswhite
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 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
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread 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) (SimpleM _ d2 _) - (SimpleM d1 d2 d3)
and so on.

Ultimately I want to generalize this to more variables.

I can't seem to get anything to substitute for the pattern variables in 
a lambda.  Is there a straightforward way of doing this?


Below is what I've been playing with to try to make this work.

Thanks,
Patrick.


---
module THTest where

import Language.Haskell.TH
import qualified Data.Bits

type Policy = Int

data Management = SimpleM Policy Policy Policy
   deriving Show

-- Compiles - but no substitution for the aX and bX variables
buildCP :: Int - ExpQ
buildCP k =
   [|\(SimpleM a1 a2 a3) (SimpleM b1 b2 b3) - (SimpleM $e1 $e2 $e3) |]
   where (e1,a1,b1) = bitToExprs 0 k
 (e2,a2,b2) = bitToExprs 1 k
 (e3,a3,b3) = bitToExprs 2 k


-- Won't compile:

buildCP2 :: Int - ExpQ
buildCP2 k =
   [|\(SimpleM $a1 $a2 $a3) (SimpleM $b1 $b2 $b3) - (SimpleM $e1 $e2 
$e3) |]

   where (e1,a1,b1) = bitToExprs 0 k
 (e2,a2,b2) = bitToExprs 1 k
 (e3,a3,b3) = bitToExprs 2 k

cp1 0 = \(SimpleM d1 d2 d3) (SimpleM _ _ _) - (SimpleM d1 d2 d3)

{-
-- idea is to use in calls like this:

cp0 0 = $(buildCP 0) -- should be \(SimpleM d1 d2 d3) (SimpleM _ _ _) - 
(SimpleM d1 d2 d3)

cp0 1 = $(buildCP 1)
-}

-- There is also a template haskell [p| ... |] syntax, but not yet 
implemented ...

bitToExprs:: Int - Int - (ExpQ,PatQ,PatQ)
bitToExprs n k =
   if Data.Bits.testBit (k::Int) (n::Int)
   then (e,v1,v2)
   else (e,v2,v1)
   where v1 =  return WildP
 v2 =  return $ VarP (mkName name)
 e = return $ VarE (mkName name)
 name = d ++ (show $ n + 1)

{-

-- ulitmate goal is something like this with 10ish d variables:
--

cp0 0 (SimpleM d1 d2 d3 m1) (SimpleM _ _ _ m2) = (SimpleM d1 d2 d3 (me1 
m1 m2))
cp0 1 (SimpleM d1 d2 _ m1) (SimpleM _ _ d3 m2) = (SimpleM d1 d2 d3 (me2 
m1 m2))
cp0 2 (SimpleM d1 _ d3 m1) (SimpleM _ d2 _ m2) = (SimpleM d1 d2 d3 (me1 
m1 m2))
cp0 3 (SimpleM d1 _ _ m1) (SimpleM _ d2 d3 m2) = (SimpleM d1 d2 d3 (me2 
m1 m2))
cp0 4 (SimpleM _ d2 d3 m1) (SimpleM d1 _ _ m2) = (SimpleM d1 d2 d3 (me1 
m1 m2))
cp0 5 (SimpleM _ d2 _ m1) (SimpleM d1 _ d3 m2) = (SimpleM d1 d2 d3 (me2 
m1 m2))
cp0 6 (SimpleM _ _ d3 m1) (SimpleM d1 d2 _ m2) = (SimpleM d1 d2 d3 (me1 
m1 m2))
cp0 7 (SimpleM _ _ _ m1) (SimpleM d1 d2 d3 m2) = (SimpleM d1 d2 d3 (me2 
m1 m2))

cp0 _ _ _ = (trace cp0 error undefined)

-}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Antoine Latter
On Sun, Jan 3, 2010 at 8:30 PM, Patrick Caldon p...@pessce.net 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)  into \(SimpleM d1 _ d3) (SimpleM _ d2 _) - (SimpleM d1 d2 d3)
 and so on.

 Ultimately I want to generalize this to more variables.

 I can't seem to get anything to substitute for the pattern variables in a
 lambda.  Is there a straightforward way of doing this?


Hello,

It looks like you want to construct expressions with the LamE
constructor, which is declared like so:

LamE [Pat] Exp

For the Pat, you would use eiter VarP or WildP for variable binding
patterns or wild-card patterns.

Or am I missing something?

Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Patrick Caldon

Antoine Latter wrote:

On Sun, Jan 3, 2010 at 8:30 PM, Patrick Caldon p...@pessce.net 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)  into \(SimpleM d1 _ d3) (SimpleM _ d2 _) - (SimpleM d1 d2 d3)
and so on.

Ultimately I want to generalize this to more variables.

I can't seem to get anything to substitute for the pattern variables in a
lambda.  Is there a straightforward way of doing this?




Hello,

It looks like you want to construct expressions with the LamE
constructor, which is declared like so:

LamE [Pat] Exp

  


Thanks - I see how that could work, I'll try it.

But really I was wondering if there was something like:

buildCP2 :: Int - ExpQ
buildCP2 k =
   [|\(SimpleM ~a1 ~a2 ~a3) (SimpleM ~b1 ~b2 ~b3) - (SimpleM $e1 $e2 
$e3) |]

   where (e1,a1,b1) = bitToExprs 0 k
 (e2,a2,b2) = bitToExprs 1 k
 (e3,a3,b3) = bitToExprs 2 k

bitToExprs:: Int - Int - (ExpQ,PatQ,PatQ)

Where ~a1 would mean look for something called a1 returning a pattern, 
and slot it into the pattern part of the lambda in the appropriate spot.


I'm guessing no such syntax exists?

Thanks again,

Patrick.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Tuomas Tynkkynen
2010/1/4 Patrick Caldon p...@pessce.net

 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)
 and so on.

 Ultimately I want to generalize this to more variables.

 I can't seem to get anything to substitute for the pattern variables in a 
 lambda.  Is there a straightforward way of doing this?

 Below is what I've been playing with to try to make this work.

 Thanks,
 Patrick.


Here's something pretty generic that gets the patterns right:

module THTest where

import Language.Haskell.TH
import Data.List
import Control.Monad

type Policy = Int

data Management = SimpleM Policy Policy Policy
  deriving Show

buildCP :: Name - Int - Int - ExpQ
buildCP ctor nVars nth = do names - replicateM nVars $ newName pat
            let p1 = replaceAt nth WildP $ map VarP names
                p2 = replaceAt nth (VarP $ names!!nth) $ replicate
nVars WildP
                return $ LamE [ConP ctor p1, ConP ctor p2] (ListE $
map VarE names)

replaceAt :: Int - a - [a] - [a]
replaceAt pos x xs = let (first,_:rest) = splitAt pos xs
            in first ++ [x] ++ rest
-- for example:
doFst = $(buildCP 'SimpleM 3 0)

doFst  (SimpleM 1 2 3) (SimpleM 4 5 6) == [4,2,3]

(returns a list because it's easier to do. Modifying it to return
SimpleM left as an exercise :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell - substitution in pattern in a lambda

2010-01-03 Thread Patrick Caldon

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.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types

2009-05-28 Thread Simon Peyton-Jones
You already have splicing for top level decls. Splicing for local decls is a 
whole different ball game because it brings new *binders* into scope.  For 
example

f = ...g...
g = let $(foo) in ...f...

Is the 'f' inside 'g' the same 'f' as the one bound at top level?  Not 
necessarily, because $(foo) might bind f.  So I can't even do dependency 
analysis to figure out whether f and g are mutually recursive!   It gets harder 
if $(foo) mentions 'f'; and if the definition of 'f' has a declaration splice 
too.

So splicing local decls introduces a new raft of questions whose answers are 
not obvious, and that might require some substantial structural rearrangement 
of GHC.  In particular to the rename and then typecheck strategy.   It's very 
similar to reason that we don't allow splices in patterns.

Bottom line: 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 Types

Spectacular!

How difficult would it be to implement splicing in decls? I'm interested in 
having a go at it, and it seems like a perfect time since I can cheat off the 
fresh diff. In particular I'd love to be able to do stuff like this (without 
the current vicious hackery i'm using) (and granted, where i'm splicing is 
somewhat willy-nilly, but some approximation of this):

-

{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module DecTest where
import HsDec
import Data.List
import DecTestBoot
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax
import Language.Haskell.Meta.Utils

bootQ :: Q [Dec]
bootQ = bootQFunct
  primQStruct

primQStruct = (''[]
  ,(conT ''[] `appT`)
  ,[|[]|]
  ,[|null|]
  ,[|undefined|]
  ,[|union|]
  ,[|undefined|]
  ,[|undefined|])

bootQFunct
  (primN  :: Name
  ,primQ  :: TypeQ
  - TypeQ  -- exists q. forall a. a - q a
  ,emptyQ :: ExpQ   -- Q a
  ,isEmptyQ   :: ExpQ   -- q a - Bool
  ,insertQ:: ExpQ   -- Int - a - q a - q a
  ,mergeQ :: ExpQ   -- q a - q a - q a
  ,findMinQ   :: ExpQ   -- q a - Maybe (Int, a)
  ,deleteMinQ :: ExpQ)  -- q a - q a

  = do  n - newName a
let primT = varT primN
a = varT n

[$dec|
  data BootQ $(a)
= Nil
| Node {-# UNPACK #-} !Int $(a) ($(primT) (BootQ $(a)))
deriving(Eq,Ord)

  empty :: BootQ $(a)
  isEmpty   :: BootQ $(a) - Bool
  insert:: Int - $(a) - BootQ $(a) - BootQ $(a)
  merge :: BootQ $(a) - BootQ $(a) - BootQ $(a)
  findMin   :: BootQ $(a) - Maybe (Int, $(a))
  deleteMin :: BootQ $(a) - BootQ $(a)

  empty = Nil
  isEmpty Nil = True
  isEmpty   _ = False
  findMin  Nil = Nothing
  findMin (Node n x _) = Just (n, x)
  insert n x q = merge (Node n x $(emptyQ)) q
  merge (Node n1 x1 q1)
(Node n2 x2 q2)
| n1 = n2  = Node n1 x1 ($(insertQ) n2 (Node n2 x2 q2) q1)
| otherwise = Node n2 x2 ($(insertQ) n1 (Node n1 x1 q1) q2)
  merge Nil q  = q
  merge q  Nil = q
  deleteMin  Nil = Nil
  deleteMin (Node _ _ q)
= case $(findMinQ) q of
Nothing - Nil
Just (_, Node m y q1)
  - let q2 = $(deleteMinQ) q
  in Node m y ($(mergeQ) q1 q2)
|]


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   >