-- file: Augeas.hsc -- Haskell bindings for the Augeas library -- Copyright (c) 2009-2012, Jude Nagurney -- This library is free software; you can redistribute it and/or modify it -- under the terms of the GNU Lesser General Public License as published by -- the Free Software Foundation; either version 3 of the License, or -- (at your option) any later version. -- This library 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 Lesser General Public -- License for more details. -- You should have received a copy of the GNU Lesser General Public License -- along with this library; if not, write to the Free Software Foundation, -- Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -- -- Contact the author at -- jude@pwan.org {-# LANGUAGE CPP, ForeignFunctionInterface, EmptyDataDecls, StandaloneDeriving #-} #ifndef _config_h #include "Config.h" #define _config_h #endif module System.AugeasHsc where import Foreign.C.Types import Foreign.Storable #include "augeas.h" -- ---------------------------------- -- Maps to aug_flags enum in augeas.h -- ---------------------------------- newtype AugFlag = AugFlag { unAugFlag :: CInt } deriving (Eq, Show) #{enum AugFlag, AugFlag , none = AUG_NONE , save_backup = AUG_SAVE_BACKUP , save_newfile = AUG_SAVE_NEWFILE , type_check = AUG_TYPE_CHECK , no_stdinc = AUG_NO_STDINC , save_noop = AUG_SAVE_NOOP , no_load = AUG_NO_LOAD , no_modl_autoload = AUG_NO_MODL_AUTOLOAD #ifdef HAS_AUGEAS_SPAN , enable_span = AUG_ENABLE_SPAN #endif } -- --------------------------------- -- Maps to auf_errcode_t in augeas.h -- --------------------------------- newtype AugErrCode = AugErrCode { unAugErrCode :: CInt } deriving (Eq, Show) #{enum AugErrCode, AugErrCode , no_error = AUG_NOERROR , err_no_memory = AUG_ENOMEM , err_internal = AUG_EINTERNAL , err_bad_path = AUG_EPATHX , err_no_match = AUG_ENOMATCH , err_multi_matches = AUG_EMMATCH , err_syntax = AUG_ESYNTAX , err_no_lens = AUG_ENOLENS , err_multi_xfm = AUG_EMXFM #ifdef HAS_AUGEAS_SPAN , err_no_span = AUG_ENOSPAN #endif #ifdef HAS_AUGEAS_SRUN , err_mv_desc = AUG_EMVDESC , err_cmd_run = AUG_ECMDRUN #endif #ifdef HAS_AUGEAS_TO_XML , err_bad_arg = AUG_EBADARG #endif } #ifdef HAS_AUGEAS_TO_XML #include #let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__) --data xmlNode data AugeasXmlNode -- deriving (Eq, Show) data AugeasXmlNodeHandle = Ptr AugeasXmlNode instance Storable AugeasXmlNode where alignment _ = #{alignment xmlNode} sizeOf _ = #{size xmlNode} -- peek ptr = do -- _type <- #{peek xmlNode, type} ptr -- name <- #{peek xmlNode, name} ptr -- children <- #{peek xmlNode, children} ptr -- last <- #{peek xmlNode, last} ptr -- parent <- #{peek xmlNode, parent} ptr -- next <- #{peek xmlNode, next} ptr -- prev <- #{peek xmlNode, prev} ptr -- doc <- #{peek xmlNode, doc} ptr -- return (XmlNode _type name children last parent next prev doc) -- return (XmlNode _type name ) -- poke ptr (XmlNode _type name children last parent next prev doc) = do -- poke ptr (XmlNode _type name) = do -- #{poke xmlNode, type} ptr _type -- #{poke xmlNode, name} ptr name #endif