-- | CTemplate is the template system that Google uses for many of their sites, -- including the search results from the main www.google.com web search. It's -- simple templating system, but has easy to use escaping functions. -- -- See for -- documentation (esp see the Tips link at the end of that) module Text.CTemplate ( Dictionary(..) , Variable(..) , Option(..) , expand , setTemplateRootDirectory ) where import Foreign import Foreign.C import qualified Data.ByteString as B import qualified Data.ByteString.Unsafe as B -- | This is a dictionary. Relative filenames are resolved in the current -- directory data Dictionary = Dictionary FilePath [(String, Variable)] deriving (Show, Eq) data Variable = StringV String -- ^ a string value (note - no char encoding performed) | BSV B.ByteString -- ^ a string value from a ByteString | SectionV [[(String, Variable)]] -- ^ a (possibly repeated) section | IncludedV Dictionary -- ^ an included dictionary deriving (Show, Eq) data Option = DontStrip | StripBlankLines | StripWhitespace deriving (Show, Eq, Enum) -- | This is the type of the C-side dictionary object data Dictionary_ -- | Likewise, this is the type of the C-side template data Template_ foreign import ccall unsafe "ct_load_template" _load_template :: CString -> CInt -> IO (Ptr Template_) foreign import ccall unsafe "ct_new_dict" _new_dict :: IO (Ptr Dictionary_) foreign import ccall unsafe "ct_set_string" _set_string :: Ptr Dictionary_ -> CString -> CString -> IO () foreign import ccall unsafe "ct_set_bytes" _set_bytes :: Ptr Dictionary_ -> CString -> Ptr CChar -> CInt -> IO () foreign import ccall unsafe "ct_new_section" _new_section :: Ptr Dictionary_ -> CString -> IO (Ptr Dictionary_) foreign import ccall unsafe "ct_new_included" _new_included :: Ptr Dictionary_ -> CString -> IO (Ptr Dictionary_) foreign import ccall unsafe "ct_set_filename" _set_filename :: Ptr Dictionary_ -> CString -> IO () foreign import ccall unsafe "ct_expand" _expand :: Ptr Template_ -> Ptr Dictionary_ -> IO (Ptr CChar) translateVariable :: Ptr Dictionary_ -> (String, Variable) -> IO () translateVariable dict (v, StringV s) = withCString v $ \v -> withCString s $ \s -> _set_string dict v s translateVariable dict (v, BSV bs) = withCString v $ \v -> B.unsafeUseAsCStringLen bs $ \(ptr, len) -> _set_bytes dict v ptr $ fromIntegral len translateVariable dict (v, SectionV varses) = withCString v $ \v -> flip mapM_ varses $ \vars -> _new_section dict v >>= \dict -> mapM_ (translateVariable dict) vars translateVariable dict (v, IncludedV (Dictionary filename vars)) = withCString v $ \v -> _new_included dict v >>= \dict -> withCString filename $ \ptr -> _set_filename dict ptr >> mapM_ (translateVariable dict) vars -- | Expand a template given the values to fill it expand :: Option -> Dictionary -> IO (Maybe B.ByteString) expand option (Dictionary filename vars) = do template <- withCString filename $ \ptr -> _load_template ptr $ fromIntegral $ fromEnum option if template == nullPtr then return Nothing else do dict <- _new_dict mapM_ (translateVariable dict) vars str <- _expand template dict bs <- B.packCString str free str return $ Just bs foreign import ccall unsafe "ct_set_root" _set_root :: Ptr CChar -> IO () -- | Set the directory where templates with non-absolute filenames will be -- loaded from setTemplateRootDirectory :: FilePath -> IO () setTemplateRootDirectory filename = withCString filename $ \ptr -> _set_root ptr