Haskell Quiz/GEDCOM/Solution Anton

From HaskellWiki
< Haskell Quiz‎ | GEDCOM
Revision as of 00:10, 12 August 2011 by Apirogov (talk | contribs) (New page: GEDCOM Parser <haskell> -- RubyQuiz Nr.6 - GEDCOM to XML translator -- Copyright (C) 2011 Anton Pirogov -- Usage: runhaskell rubyquiz6.hs < gedcomfile....)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.


-- 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...