[Haskell-cafe] some ideas for Haskell', from Python

George Pollard porges at porg.es
Tue Jan 20 21:44:37 EST 2009


On Wed, 2009-01-14 at 15:59 +0100, Manlio Perillo wrote:
> 1) In a Python string it is available the \U{name} escape, where name is
>     a character name in the Unicode database.
> 
>     As an example:
>         foo = u"abc\N{VULGAR FRACTION ONE HALF}"

This is possible via QuasiQuotation, you can write a parser that will
let you do it like this:

	foo = [$s|abc\N{VULGAR FRACTION ONE HALF}|]

I started to write one but got stuck :P By working from the wiki page
[1] I ended up with some code that will let you do:

	let e = 3 in [$s|h\V{e}llo\U{32}world|] == "h3llo world"

I got stuck on a few things:
- how best to allow arbitrary expressions (requires additional parsing
to allow braces inside strings and so on, e.g. [$s|hello \E{"}"}
world|])
- can't figure out how to write the quoting function for the patterns...
this would be awesome if it worked:

	everythingAfterFirstK [$s|\V{before}k\V{after}|] = after

- there's no library for looking up characters by name. 'unicode-names'
has getCharacterName but not the inverse.

Code follows:

StringSplicer.hs
> {-# LANGUAGE DeriveDataTypeable #-}
> 
> module StringSplicer 
> where
> 
> import Data.Generics
> import Text.ParserCombinators.Parsec
> import Control.Monad
> 
> data Exp = StringLit String
>           | Unicode Int
>           | Variable String
>           | Backslash
>           deriving (Show, Typeable, Data)
> 
> interp = do
> 	char '\\'
> 	c <- choice [char 'U', char 'V', char '\\']
> 	case c of
> 		'U' -> do
> 			char '{'
> 			n <- many1 digit
> 			char '}'
> 			return $ Unicode (read n)
> 		'V' -> do
> 			char '{'
> 			s <- manyTill anyChar (try $ char '}')
> 			return $ Variable s
> 		'\\' -> return Backslash
> 
> str = do
> 	s <- many1 $ noneOf ['\\']
> 	return $ StringLit s
> 
> expr = many $ interp <|> str
> 
> parseString :: Monad m => (String, Int, Int) -> String -> m [Exp]
> parseString (file, line, col) s =
> 	case runParser p () "" s of
> 		Left err -> fail $ show err
> 		Right e -> return e
> 	where
> 		p = do
> 			pos <- getPosition
> 			setPosition $
> 				(flip setSourceName) file $
> 				(flip setSourceLine) line $
> 				(flip setSourceColumn) col $
> 				pos
> 			e <- expr
> 			eof
> 			return e

StringSplicer.Quote.hs
> module StringSplicer.Quote
> where
> 
> import Data.Generics
> import qualified Language.Haskell.TH as TH
> import Language.Haskell.TH.Quote
> import Data.Char (chr)
> import StringSplicer
> 
> quoteExprExp :: String -> TH.ExpQ
> quoteExprPat :: String -> TH.PatQ
> 
> s :: QuasiQuoter
> s = QuasiQuoter quoteExprExp quoteExprPat
> 
> parseIt x = do
> 	loc <- TH.location
> 	let pos =
> 		(TH.loc_filename loc,
> 		fst (TH.loc_start loc),
> 		snd (TH.loc_start loc))
> 	parseString pos x
> 
> quoteExprExp x = do
> 	expr <- parseIt x
> 	it <- dataToExpQ (const Nothing `extQ` antiExprExp) expr
> 	return $ TH.AppE (TH.VarE (TH.mkName "concat")) it
> 
> quoteExprPat x = do
> 	expr <- parseIt x
> 	it <- dataToPatQ (const Nothing `extQ` antiExprPat) expr
> 	error "help!"
> 
> antiExprExp :: Exp -> Maybe (TH.Q TH.Exp)
> antiExprExp (StringLit s) = Just $ TH.litE (TH.stringL s)
> antiExprExp (Backslash) = Just $ TH.litE (TH.stringL "\\")
> antiExprExp (Unicode n) = Just $ TH.litE (TH.stringL [chr n])
> antiExprExp (Variable v) = Just $ TH.appE
> 	(TH.varE (TH.mkName "show"))
> 	(TH.varE (TH.mkName v))
> 
> antiExprPat :: Exp -> Maybe (TH.Q TH.Pat)
> antiExprPat (Unicode n) = Just $ TH.litP (TH.stringL [chr n])
> antiExprPat (Backslash) = Just $ TH.litP (TH.stringL "\\")
> antiExprPat (StringLit s) = Just $ TH.litP (TH.stringL s)
> antiExprPat (Variable v) = Just $ TH.varP (TH.mkName v)

[1]: http://haskell.org/haskellwiki/Quasiquotation

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 197 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20090121/93a5a3f8/attachment.bin


More information about the Haskell-Cafe mailing list