{- Copyright 2013,2014 Marcelo Millani This file is part of boomange. boomange is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. boomange is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with boomange. If not, see -} module Data.Builder where import Data.Tree import Data.Entities splitSet _ [] = ([],[]) splitSet f (h:r) = let (true,false) = splitSet f r in if f h then (h:true,false) else (true,h:false) makeError msg fname = let file = Node{rootLabel = "file://" ++ fname, subForest = []} link = Node{rootLabel = fname, subForest = [file]} in Node{rootLabel = "Error: " ++ msg, subForest = [link] } -- | builds the bookmark tree buildBookmarks fname Node{rootLabel = rl, subForest = sForest} = case sForest of [] -> buildBookmarks fname (makeError ("empty tree (" ++ rl ++ ")") fname) [Node{rootLabel = l, subForest = []} ] -> Url{name = rl, url = l} _ -> Folder{name = rl, children = map (buildBookmarks fname ) sForest} -- | generates html for the given bookmarks htmlBookmarks bookmark = concat $ map (htmlBookmarks' 0) bookmark htmlBookmarks' depth bookmark = case bookmark of Folder{name = n, children = c} -> ident ++ "
\n" ++ ident ++ "

" ++ n ++ "

\n" ++ (concat $ map (htmlBookmarks' (depth+1)) c ) ++ ident ++ "
\n" Url{name = n, url = u} -> ident ++ "" ++ n ++ "
\n" where ident = take depth $ repeat '\t'