{-# LANGUAGE FlexibleInstances #-} module Data.Lighttpd ((.=>.) ,(.=.) ,(./.) ,showSettings) where import System.FilePath import Data.List import Utils ------------------------------------------------------------------------------ -- Lighttpd configuration -- | Class for generalising the properties. class LightyProperty a where toProp :: a -> Prop -- | Necessary instances. instance LightyProperty [[Char]] where toProp = List instance LightyProperty [Char] where toProp = String instance LightyProperty Int where toProp = Number instance LightyProperty [Prop] where toProp = Props instance LightyProperty [[Prop]] where toProp = Props . map Props -- | A property. data Prop = String String | Number Int | List [String] | Assign String Prop | Props [Prop] -- | A property "setting". data Set = Set String Prop instance Show Prop where show (String s) = show s show (Number n) = show n show (List xs) = "(" ++ commas xs ++ ")" where show (Assign p v) = show p ++ " => " ++ show v show (Props ps) = "(" ++ commas ps ++ ")" instance Show Set where show (Set s p) = s ++ " = " ++ show p -- | Print a list of settings in the lighttpd config format. showSettings :: [Set] -> String showSettings = unlines . map show commas :: Show a => [a] -> String commas = concat . intersperse "," . map show ------------------------------------------------------------------------------ -- Combinators -- | "Set" a property. (.=.) :: LightyProperty a => String -> a -> Set p .=. v = Set p (toProp v) infixr 0 .=. -- | "Assign" a value to something. (.=>.) :: LightyProperty a => String -> a -> Prop (.=>.) a b = Assign a (toProp b) infixr 0 .=>.