Jonathan Cast <[EMAIL PROTECTED]> wrote:
> Albert Lai <[EMAIL PROTECTED]> wrote:
> <snip>
> > The best of both worlds may  be something like the notation in the HOL
> > theorem prover:
> > 
> > ``^q ^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i``
> > 
> > Do you agree that this is much better?
> > 
> > Could someone implement something like this in GHC please? :)

The attached code  has been tested and works;  call as $(interpolate "^q
^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i").

Still confident someone can do better (e.g., formatting parameters),

Jon Cast

module Language.Haskell.Interpolate where

import Char
import Control.Monad.Fix
import Language.Haskell.TH

lexToken :: String -> alpha -> (String -> String -> alpha) -> alpha
lexToken (c:s) x f
  | isAlpha c || c == '_'
  = flip fix ([c], s) $ \ loop (s1, s2) -> case s2 of
      (c:s2') | isAlphaNum c || c == '_' || c == '\''
            -> loop (c:s1, s2')
      _ -> f (reverse s1) s2
lexToken _ x f = x

interpolate :: String -> Q Exp
interpolate [] = listE []
interpolate ('^':s)
  = lexToken s (fail "Expected valid Haskell identifier") $ \ s1 s2 ->
      infixE (Just (varE 'show `appE` varE (mkName s1)))
             (varE '(++))
             (Just (interpolate s2))
interpolate ('\\':c:s) = infixE (Just (litE $ StringL [c]))
                                (varE '(++))
                                (Just (interpolate s))
interpolate s = let
     (s1, s2) = break (\c -> c =='^' || c == '\\') s
  in infixE (Just (litE $ StringL s1))
            (varE '(++))
            (Just (interpolate s2))
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to