[Haskell-cafe] Re: Language Workbenches - First attempt

Yoel Jacobsen yoel at emet.co.il
Tue Sep 13 08:20:01 EDT 2005


source = "#123456789012345678901234567890123456789012345678901234567890\n\
\SVCLFOWLER         10101MS0120050313.........................\n\
\SVCLHOHPE          10201DX0320050315........................\n\
\SVCLTWO           x10301MRP220050329..............................\n\ 
            \USGE10301TWO 
x50214..7050329..............................."

type ConfigLine = (String, [(String, (Int, Int))])
type Configuration = [ConfigLine]
type KeyVal = (String, String)
type Header = String
type Entry = (Header, [KeyVal])

config :: Configuration
config = [("SVCL", [("CustomerName", (4, 18)),
                     ("CustomerID", (19, 23)),
                     ("CallTypeCode", (24, 27)),
                     ("DateOfCallString", (28, 35))]),

           ("USGE", [("CustomerID", (4, 8)),
                     ("CustomerName", (9, 22)),
                     ("Cycle", (30, 30)),
                     ("ReadDAte", (31, 36))])]

getRange :: Int -> Int -> [a] -> [a]
getRange a b l = take (b-a+1) $ drop a l

lineToFields :: String -> [(Int,Int)] -> [String]
lineToFields line points = map (fieldFromTo line) points
     where fieldFromTo line (x,y) = getRange x y line

lineType :: String -> String
lineType = getRange 0 3

applyConfig :: String -> ConfigLine -> [KeyVal]
applyConfig line (ckey, cval) =
     if lineType line == ckey
     then zip names $ lineToFields line points
     else []
     where part = unzip cval
           names = fst part
           points = snd part

parseLine :: Configuration -> String -> Entry
parseLine cnf line = (header, parsed)
     where rawData :: [[KeyVal]]
           rawData = map (applyConfig line) cnf
           parsed :: [KeyVal]
           parsed = head $ dropWhile null rawData
           header = lineType line

parse :: Configuration -> [String] -> [Entry]
parse cnf lines = map (parseLine cnf) lines

run = parse config $ filter noComment $ lines source
     where noComment = \x -> (head x) /= '#'


====== Output
*Main> run
[("SVCL",[("CustomerName","FOWLER 
"),("CustomerID","10101"),("CallTypeCode","MS01"),("DateOfCallString","20050313")]),("SVCL",[("CustomerName","HOHPE 
 
"),("CustomerID","10201"),("CallTypeCode","DX03"),("DateOfCallString","20050315")]),("SVCL",[("CustomerName","TWO 
 
x"),("CustomerID","10301"),("CallTypeCode","MRP2"),("DateOfCallString","20050329")]),("USGE",[("CustomerID","10301"),("CustomerName","TWO 
          x"),("Cycle","7"),("ReadDAte","050329")])]
*Main>



Yoel Jacobsen wrote:
> It seems that Martin Fowler's article "Language Workbenches: The 
> killer-App for Domain Specific Languages?" - 
> http://www.martinfowler.com/articles/languageWorkbench.html - has 
> generated some nice dynamic solution where a configuration file is 
> written in the same language as the program. Notable examples are lisp - 
> http://lispm.dyndns.org/news?ID=NEWS-2005-07-08-1 and python - 
> http://billionairebusinessman.blogspot.com/2005/09/drop-that-schema-and-put-your-hands-in.html 
> 
> 
> I'm trying to create an _elegant_ solution in Haskell. But I'm stuck. 
> Since the native record-like access in Haskell syntax is using labelled 
> fields in datatype decleration but the later are strictly compile-time. 
> Therefore, if I compile my program and add a field in the configuration 
> file (written in Haskell, using, for instance hs-plugins), I'll need to 
> recompile the data declaration as well.
> 
> Further, what is the type of the parser? Consider the following 
> implementation:
> 
> source = "#123456789012345678901234567890123456789012345678901234567890\n\
>  \SVCLFOWLER         10101MS0120050313.........................\n\
>  \SVCLHOHPE          10201DX0320050315........................\n\
>  \SVCLTWO           x10301MRP220050329..............................\n\ 
>         \USGE10301TWO x50214..7050329..............................."
> 
> data Configuration = Config String [(String, Int, Int)]
> 
> config = [
>           Config "SVCL" [("CustomerName", 4, 18),
>                          ("CustomerID", 19, 23),
>                          ("CallTypeCode", 24, 27),
>                          ("DateOfCallString", 28, 35)],
> 
>           Config "USGE" [("CustomerID", 4, 8),
>                          ("CustomerName", 9, 22),
>                          ("Cycle", 30, 30),
>                          ("ReadDAte", 31, 36)]]
> 
> -- parse takes the configuration, a line from the source string and 
> generate a record
> 
> parse :: Configuration -> String -> Record
> 
> 
> What is the type of Record?
> 
> Anyway, any elegant solution or a hint towards one are most welcome.
> 
> Thanks,
>   Yoel



More information about the Haskell-Cafe mailing list