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


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

2009-05-27 Thread Simon Peyton-Jones
Folks

Quite a few people have asked for splices in Template Haskell *types*, and I 
have finally gotten around to implementing them.  So now you can write things 
like

instance Binary $(blah blah) where ...
or  f :: $(wubble bubble) - Int

as requested, for example, in the message below.  Give it a whirl.  You need 
the HEAD; in a day or two you should find binary snapshots if you don't want to 
build from source.

Simon

PS: Note that you (still) cannot write a splice in a *binding* position. Thus 
you can't write
f $(blah blah) = e
or
data T $(blah blah) = MkT Int

I don't intend to change this; see the commentary at 
http://hackage.haskell.org/trac/ghc/ticket/1476

| -Original Message-
| From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On
| Behalf Of Ross Mellgren
| Sent: 25 January 2009 19:55
| To: Haskell Cafe
| Subject: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types
|
| Hi all,
|
| I'm writing a small module that exposes a template haskell splice that
| takes a (very simplified) C struct definition and builds:
|
|   - A data type definition,
|   - an instance for Data.Binary.Binary,
|   - and optionally a pretty print function for it
|
| However, it seems to do this I have to write a bunch of really ugly
| code that builds up the TH data structures by hand because quoting
| only works with splices for expressions, or so it seems.
|
| For example, to generate the binary instance I have this code:
|
| import qualified Language.Haskell.TH as TH
|
| -- tyname is the name of the data type I've already created, as a
| TH.Name
| -- tempnames is a list of temporary variable names that are used in
| lambda patterns
| -- fields is a list of tuples describing each field
| -- makeGetExp recursively builds a monadic computation consisting
| mostly of Binary.getWord32be = \ tempvar - ...
|
|  binaryInstDec - liftM (TH.InstanceD [] (TH.AppT (TH.ConT $
| TH.mkName Data.Binary.Binary) (TH.ConT tyname)))
| [d| get = $(makeGetExp (reverse $ zip
| fields tempnames) returnExp)
| put = undefined |]
|
| I'd really rather write:
|
|  binaryInstDec - [d|
|  instance Binary.Binary $(tyname) where
|  get = $(makeGetExp (reverse $ zip fields tempnames)
| returnExp)
|  put = undefined |]
|
| But GHC gives me a syntax error on the tyname splice. The docs seem to
| indicate this is the way it is -- that splices in type locations is
| plain not implemented.
|
| My question is whether or not this is just the way it is, and people
| writing TH declaration splices tend to have to start manually
| assembling a bunch of it, or is there some trick I've missed? Perhaps
| even better are there some tricks that people tend to use to make this
| less painful?
|
| I did try using some of the lowercased monadic constructors in
| Language.Haskell.TH.Lib but I didn't seem to get anything more succint
| out of it.
___
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-27 Thread Miguel Mitrofanov


On 27 May 2009, at 23:38, Simon Peyton-Jones wrote:


Folks

Quite a few people have asked for splices in Template Haskell  
*types*, and I have finally gotten around to implementing them.  So  
now you can write things like


   instance Binary $(blah blah) where ...
or  f :: $(wubble bubble) - Int


Great! Just what I was looking for a couple of days ago.

PS: Note that you (still) cannot write a splice in a *binding*  
position.


I think, I can live without it.
___
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-27 Thread Matt Morrow
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)
|]

{-
-- FORGOT TO PUT AN (Eq a) CXT, but oh well
ghci ppDoc `fmap` bootQ
data BootQ a_0_0 = Nil | Node !Int a_0_0 ([] (BootQ a_0_0))
deriving (Eq, Ord)
empty :: forall a_0_1 . BootQ a_0_1
isEmpty :: forall a_0_2 . BootQ a_0_2 - Bool
insert :: forall a_0_3 . Int - a_0_3 - BootQ a_0_3 - BootQ a_0_3
merge :: forall a_0_4 . BootQ a_0_4 - BootQ a_0_4 - BootQ a_0_4
findMin :: forall a_0_5 . BootQ a_0_5 - Maybe ((Int, a_0_5))
deleteMin :: forall a_0_6 . BootQ a_0_6 - BootQ a_0_6
empty = Nil
isEmpty (Nil) = True
isEmpty _ = False
findMin (Nil) = Nothing
findMin (Node n_7 x_8 _) = Just (n_7, x_8)
insert n_9 x_10 q_11 = merge (Node n_9 x_10 []) q_11
merge (Node n1_12 x1_13 q1_14) (Node n2_15
 x2_16
 q2_17) | n1_12 = n2_15 = Node n1_12
x1_13 (undefined n2_15 (Node n2_15 x2_16 q2_17) q1_14)
| otherwise = Node n2_15 x2_16
(undefined n1_12 (Node n1_12 x1_13 q1_14) q2_17)
merge (Nil) q_18 = q_18
merge q_19 (Nil) = q_19
deleteMin (Nil) = Nil
deleteMin (Node _ _ q_20) = case undefined q_20 of
Nothing - Nil
Just (_, Node m_21 y_22 q1_23) - let q2_24
= undefined q_20
   in Node
m_21 y_22 (union q1_23 q2_24)
ghci
-}

-

Thanks,
Matt



On Wed, May 27, 2009 at 2:38 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

 Folks

 Quite a few people have asked for splices in Template Haskell *types*, and
 I have finally gotten around to implementing them.  So now you can write
 things like

instance Binary $(blah blah) where ...
 or  f :: $(wubble bubble) - Int

 as requested, for example, in the message below.  Give it a whirl.  You
 need the HEAD; in a day or two you should find binary snapshots if you don't
 want to build from source.

Simon

 PS: Note that you (still) cannot write a splice in a *binding* position.
 Thus you can't write
f $(blah blah) = e
 or
data T $(blah blah) = MkT Int

 I don't intend to change this; see the commentary at
 http://hackage.haskell.org/trac/ghc/ticket/1476

 | -Original Message-
 | From: haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] On
 | Behalf Of Ross Mellgren
 |