{-# LANGUAGE OverloadedStrings #-} {- | Convert the view hierarchy to OPML -} module OPML( opml ) where import Prelude hiding (head, id, div) import qualified Data.ByteString.Lazy as L import Data.Tree import Text.OPML.Syntax import Text.OPML.Writer import Types import Text.XML.Light.Types -- | Convert the view hierarchy into a textural description using the OPML format opml :: Tree (String,View) -> String opml = serializeOPML . genOpml genOpml :: Tree (String,View) -> OPML genOpml t = nullOPML { opmlBody = [htmlTree t]} htmlTree :: Tree (String,View) -> Outline htmlTree (Node a []) = node a [] htmlTree (Node a children) = node a (map htmlTree children) node :: (String,View) -> [Outline] -> Outline node (name,v) childen = let attr s k = Attr (blank_name {qName = s}) k attrs = [attr "Width" (show $ width v),attr "Height" (show $ height v), attr "Layer" (layerType v)] in (nullOutline name) {opmlOutlineChildren = childen, opmlOutlineAttrs = reverse attrs}