module ProjectM36.Relation.Show.HTML where import ProjectM36.Base import ProjectM36.Relation import ProjectM36.Tuple import ProjectM36.Atom import qualified Data.List as L import ProjectM36.Attribute import Data.Text (append, Text, pack) import qualified Data.Text as T import qualified Data.Text.IO as TIO attributesAsHTML :: Attributes -> Text attributesAsHTML attrs = "" `append` (T.concat $ map oneAttrHTML attrNameList) `append` "" where oneAttrHTML attrName = "" `append` attrName `append` "" attrNameList = sortedAttributeNameList (attributeNameSet attrs) relationAsHTML :: Relation -> Text relationAsHTML rel@(Relation attrNameSet tupleSet) = "" `append` (attributesAsHTML attrNameSet) `append` (tupleSetAsHTML tupleSet) `append` "" `append` tablefooter `append` "
" where tablefooter = "" `append` (pack $ show (cardinality rel)) `append` " tuples" writeHTML :: Text -> IO () writeHTML = TIO.writeFile "/home/agentm/rel.html" writeRel :: Relation -> IO () writeRel = writeHTML . relationAsHTML tupleAsHTML :: RelationTuple -> Text tupleAsHTML tuple = "" `append` T.concat (L.map tupleFrag (tupleSortedAssocs tuple)) `append` "" where tupleFrag tup = "" `append` atomToText (snd tup) `append` "" tupleSetAsHTML :: RelationTupleSet -> Text tupleSetAsHTML tupSet = foldr folder "" (asList tupSet) where folder tuple acc = acc `append` tupleAsHTML tuple