Fri Jan 18 06:55:03 PST 2008  [EMAIL PROTECTED]
  * Add quasi-quotation, courtesy of Geoffrey Mainland
  
  This patch adds quasi-quotation, as described in
    "Nice to be Quoted: Quasiquoting for Haskell"
        (Geoffrey Mainland, Haskell Workshop 2007)
  Implemented by Geoffrey and polished by Simon.
  
  Overview
  ~~~~~~~~
  The syntax for quasiquotation is very similar to the existing
  Template haskell syntax:
        [$q| stuff |]
  where 'q' is the "quoter".  This syntax differs from the paper, by using
  a '$' rather than ':', to avoid clashing with parallel array comprehensions.
   
  The "quoter" is a value of type Language.Haskell.TH.Quote.QuasiQuoter, which
  contains two functions for quoting expressions and patterns, respectively.
   
       quote = Language.Haskell.TH.Quote.QuasiQuoter quoteExp quotePat
   
       quoteExp :: String -> Language.Haskell.TH.ExpQ
       quotePat :: String -> Language.Haskell.TH.PatQ
  
  TEXT is passed unmodified to the quoter. The context of the
  quasiquotation statement determines which of the two quoters is
  called: if the quasiquotation occurs in an expression context,
  quoteExp is called, and if it occurs in a pattern context, quotePat
  is called.
  
  The result of running the quoter on its arguments is spliced into
  the program using Template Haskell's existing mechanisms for
  splicing in code. Note that although Template Haskell does not
  support pattern brackets, with this patch binding occurrences of
  variables in patterns are supported. Quoters must also obey the same
  stage restrictions as Template Haskell; in particular, in this
  example quote may not be defined in the module where it is used as a
  quasiquoter, but must be imported from another module.
  
  Points to notice
  ~~~~~~~~~~~~~~~~
  * The whole thing is enabled with the flag -XQuasiQuotes
  
  * There is an accompanying patch to the template-haskell library. This
    involves one interface change:
        currentModule :: Q String
    is replaced by
        location :: Q Loc
    where Loc is a data type defined in TH.Syntax thus:
        data Loc
          = Loc { loc_filename :: String
              , loc_package  :: String
              , loc_module   :: String
              , loc_start    :: CharPos
              , loc_end      :: CharPos }
  
        type CharPos = (Int, Int)       -- Line and character position
   
    So you get a lot more info from 'location' than from 'currentModule'.
    The location you get is the location of the splice.
    
    This works in Template Haskell too of course, and lets a TH program
    generate much better error messages.
  
  * There's also a new module in the template-haskell package called 
    Language.Haskell.TH.Quote, which contains support code for the
    quasi-quoting feature.
  
  * Quasi-quote splices are run *in the renamer* because they can build 
    *patterns* and hence the renamer needs to see the output of running the
    splice.  This involved a bit of rejigging in the renamer, especially
    concerning the reporting of duplicate or shadowed names.
  
    (In fact I found and removed a few calls to checkDupNames in RnSource 
    that are redundant, becuase top-level duplicate decls are handled in
    RnNames.)
  
  
  

    M ./compiler/basicTypes/RdrName.lhs -2 +5
    M ./compiler/basicTypes/SrcLoc.lhs +5
    M ./compiler/deSugar/DsMeta.hs -3 +17
    M ./compiler/hsSyn/Convert.lhs -1 +8
    M ./compiler/hsSyn/HsExpr.lhs +7
    M ./compiler/hsSyn/HsPat.hi-boot-6 +2
    M ./compiler/hsSyn/HsPat.lhs +19
    M ./compiler/hsSyn/HsPat.lhs-boot -1 +4
    M ./compiler/hsSyn/HsUtils.lhs +7
    M ./compiler/main/DynFlags.hs +2
    M ./compiler/parser/Lexer.x +43
    M ./compiler/parser/Parser.y.pp +6
    M ./compiler/parser/RdrHsSyn.lhs +1
    M ./compiler/rename/RnBinds.lhs -3 +2
    M ./compiler/rename/RnEnv.lhs -43 +47
    M ./compiler/rename/RnExpr.lhs -2 +16
    M ./compiler/rename/RnPat.lhs -13 +54
    M ./compiler/rename/RnSource.lhs -21 +36
    M ./compiler/typecheck/TcExpr.lhs +2
    M ./compiler/typecheck/TcPat.lhs +3
    M ./compiler/typecheck/TcRnMonad.lhs +3
    M ./compiler/typecheck/TcRnTypes.lhs -2 +2
    M ./compiler/typecheck/TcSplice.hi-boot-6 -1 +3
    M ./compiler/typecheck/TcSplice.lhs -8 +101
    M ./compiler/typecheck/TcSplice.lhs-boot -1 +5
    M ./docs/users_guide/flags.xml +6
    M ./docs/users_guide/glasgow_exts.xml +138

_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to