Haskell Quiz/GEDCOM/Solution Anton
< Haskell Quiz | GEDCOM
-- RubyQuiz Nr.6 - GEDCOM to XML translator
-- Copyright (C) 2011 Anton Pirogov
-- Usage: runhaskell rubyquiz6.hs < gedcomfile.ged
-- Yes, I know that the output is fugly and the code hackish.. but it does the job :P
module Main where
main = do dat <- fmap lines getContents
let (_,rest,result) = foldl transform (0,[],[]) dat
putStr $ unlines $ reverse (reverse rest ++ result)
transform :: (Int, [String], [String]) -> String -> (Int, [String], [String])
transform (lastd,rest,result) s
| lastd < depth = (depth, closer:rest,opener:result)
| lastd >= depth = (depth, if hasRest then closer : drop ddiff rest else [closer],
opener : (if hasRest then reverse $ take ddiff rest else [""]) ++ result)
where (d:t:v) = words s
depth = read d :: Int
val = unwords v
ddiff = (lastd - depth)+1
isID (x:xs) = x=='@'
clTag str = "</" ++ str ++ ">"
indent = replicate (depth*2) ' '
hasRest = not $ null rest
closer = (indent ++ if isID t then clTag val else clTag t)
opener = indent ++ "<" ++ if isID t
then val ++ " id=\"" ++ t ++ "\">"
else t ++ if val /= ""
then " value=\""++val++"\">"
else ">"
Its visible here that (easy) text processing is not neccessarily one of Haskells strengths...
Description: The approach taken here is quite simple.. for each line, check the depth number - if it did not increase, output the closing tags of the last tag (and its parents if neccessary) from the rest-stack, output the opening xml tag for the current line and put the closing tag onto the rest-stack. At the end, append the remaining closing tags. So the accumulator keeps track of: the last depth, the closing tag stack and the result.