module Text.Ascetic
where
import Data.String.Utils (join)
type Content = String
type Tag = String
type Attribute = String
type Value = String
data Ascetic =
C Content
| E Tag [Ascetic]
| A Tag [(Attribute, Value)] [Ascetic]
| L [Ascetic]
| D Tag [(Attribute, Value)] Ascetic
deriving (Eq)
class ToAscetic a where
ascetic :: a -> Ascetic
ascii x = to "" x where
showAVs avs = [a ++ "=\"" ++ v ++ "\"" | (a,v) <- avs]
to ind x = case x of
C c -> c
E t [] -> "<" ++ t ++ ">" ++ "</" ++ t ++ ">"
E t [C c] -> ind ++ "<" ++ t ++ ">" ++ c ++ "</" ++ t ++ ">"
E t xs ->
ind
++ "<" ++ t ++ ">\n"
++ join "\n" [to (ind ++ " ") x | x <- xs]
++ "\n" ++ ind ++ "</" ++ t ++ ">"
A t avs [] -> ind ++ "<" ++ t ++ " " ++ join " " (showAVs avs) ++ ">" ++ "</" ++ t ++ ">"
A t avs [C c] -> ind ++ "<" ++ t ++ " " ++ join " " (showAVs avs) ++ ">" ++ c ++ "</" ++ t ++ ">"
A t avs xs ->
ind
++ "<" ++ t ++ " " ++ join " " (showAVs avs) ++ ">\n"
++ join "\n" [to (ind ++ " ") x | x <- xs]
++ "\n" ++ ind ++ "</" ++ t ++ ">"
L xs -> join "\n" [to ind x | x <- xs]
D t avs x ->
ind
++ "<?" ++ t ++ " " ++ join " " (showAVs avs) ++ "?>\n"
++ (to ind x)
minified x = to x where
showAVs avs = [a ++ "=\"" ++ v ++ "\"" | (a,v) <- avs]
to x = case x of
C c -> c
E t [] -> "<" ++ t ++ ">" ++ "</" ++ t ++ ">"
E t [C c] -> "<" ++ t ++ ">" ++ c ++ "</" ++ t ++ ">"
E t xs ->
"<" ++ t ++ ">"
++ join "" [to x | x <- xs]
++ "" ++ "</" ++ t ++ ">"
A t avs [] -> "<" ++ t ++ " " ++ join " " (showAVs avs) ++ ">" ++ "</" ++ t ++ ">"
A t avs [C c] -> "<" ++ t ++ " " ++ join " " (showAVs avs) ++ ">" ++ c ++ "</" ++ t ++ ">"
A t avs xs ->
"<" ++ t ++ " " ++ join " " (showAVs avs) ++ ">"
++ join "" [to x | x <- xs]
++ "" ++ "</" ++ t ++ ">"
L xs -> join "" [to x | x <- xs]
D t avs x ->
"<?" ++ t ++ " " ++ join " " (showAVs avs) ++ "?>\n"
++ (to x)
instance Show Ascetic where
show = minified
--eof