{-# LANGUAGE FlexibleInstances #-} module Text.HTML.Moe.Backend.DList where import qualified Data.ByteString.Char8 as B import Data.ByteString.UTF8 (fromString) import qualified Data.DList as D import qualified Data.List as L type Internal = D.DList Char instance Show (D.DList Char) where show = D.toList pack :: String -> Internal pack = D.fromList unpack :: Internal -> String unpack = D.toList none :: Internal none = D.empty concat :: [Internal] -> Internal concat = D.concat append :: Internal -> Internal -> Internal append = D.append intercalate :: Internal -> [Internal] -> Internal intercalate x = D.concat . L.intersperse x to_bs :: Internal -> B.ByteString to_bs = fromString . D.toList