-- file: System/Augeas.hs

-- Haskell bindings for the Augeas library
-- Copyright (c) 2009-2010, Jude Nagurney
--
-- This program is free software; you can redistribute it and/or modify it 
-- under the terms of the GNU General Public License as published by the Free 
-- Software Foundation; either version 2 of the License, or (at your option) 
-- any later version.
--
-- This program 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 General Public License for more details.
--
-- You should have received a copy of the GNU General Public License along with this program; 
-- 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 #-}

#ifndef _config_h
#include "../Config.h"
#define _config_h
#endif

{-|
  This module provides FFI bindings for the Augeas API (<http://augeas.net/docs/api.html>).
  
  /Note aug_close is not surfaced in the API because because the ForeignPtr returned by/
  /aug_init uses aug_close as its finializer./
-}
module System.Augeas
    (
    -- * Types
    Augeas
    , AugFlag(..)
    , none, save_backup, save_newfile, type_check, no_stdinc, save_noop, no_load, no_modl_autoload
    , AugMatch
    , exactly_one, no_match, invalid_match
    , AugRet(..)
    , success, one, System.Augeas.error
    , AugBefore(..)
    , just_before, just_after
    , AugErrCode(..)
    , no_error,  err_no_memory, err_internal, err_bad_path, err_no_match, err_multi_matches, err_syntax, err_no_lens, err_multi_xfm
               
    -- * Functions
    , aug_init
    , aug_defvar
    , aug_defnode
    , aug_get
    , aug_set
    , aug_insert
    , aug_rm
    , aug_mv
    , aug_match
    , aug_save
    , aug_load
    , aug_print
    , aug_error    
    , aug_error_message        
    , aug_error_minor_message
    , aug_error_details
    , aug_setm
    ) where

import System.IO
import System.Posix.IO
import System.Posix.Types
import Foreign
import Foreign.C.Types
import Foreign.C.String
import GHC.IO.Handle
import Data.ByteString.Char8

import System.AugeasHsc

-- --------------
-- Augeas pointer
-- --------------
{-|
   A pointer to the Augeas tree structure
   Not using a typed pointer (as per RWH p416) because of the compiler warning
-}
--newtype Augeas = Augeas (Ptr Augeas)
--        deriving (Eq, Show)
type Augeas = ()

-- ---------
-- aug_match
-- ---------

{-|
  The possible 'aug_get' return values.
-}
newtype AugMatch = AugMatch CInt
        deriving (Eq, Show)

{-|
  Exactly one match was found.
-}
exactly_one  :: AugMatch
exactly_one  = AugMatch 1

{-|
  No matches were found
-}
no_match  :: AugMatch
no_match  = AugMatch 0

{-|
 Either an invalid paths, or multiple matches were found.
-}
invalid_match  :: AugMatch
invalid_match  = AugMatch (-1)

-- -------
-- aug_ret
-- -------
{-|
  The possible return values for the 'aug_set', 'aug_insert', 'aug_mv', 'aug_save', and 'aug_print' functions
-}
newtype AugRet = AugRet CInt
        deriving (Eq, Show)

{-|
   The function worked as expected
-}
success  :: AugRet
success  = AugRet 0

{-|
   The function failed
-}
error  :: AugRet
error  = AugRet (-1)

one :: AugRet
one = AugRet 1

-- ----------
-- aug_before
-- ----------
{-|
  The possible BEFORE values fro the aug_insert function
-}
newtype AugBefore = AugBefore CInt
        deriving (Eq, Show)

{-|
   Insert the LABEL just before the PATH
-}
just_before  :: AugBefore
just_before  = AugBefore 1

{-|
   Insert the LABEL just after the PATH
-}
just_after  :: AugBefore
just_after  = AugBefore 0

-- utility functions

combineFlags :: [AugFlag] -> AugFlag
combineFlags = AugFlag . Prelude.foldr ((.|.) . unAugFlag) 0

-- --------
-- aug_init
-- --------

-- TODO:  Replace loadpath string with a dedicated loadpath type ?
foreign import ccall safe "augeas.h aug_init"
   c_aug_init :: CString -> CString -> AugFlag -> IO (Ptr Augeas)            

{-|
 Initialize the library.
 
 Use ROOT as the filesystem root. If ROOT is NULL, use the value of the
 environment variable AUGEAS_ROOT. If that doesn't exist either, use \"\/\".

 LOADPATH is a colon-spearated list of directories that modules should be
 searched in. This is in addition to the standard load path and the
 directories in AUGEAS_LENS_LIB

 FLAGS is a list of AugFlags

 Return a ForeignPtr to the Augeas tree upon success. If initialization
 fails, returns Nothing.

 /Note that the ForeignPtr returned by the function is using aug_close  as a finializer,/
 /so aug_close is called automatically when the Augeas pointer goes out of scope./

 /Therefore, there is no need to surface aug_close in the library./
 
-}

aug_init :: ByteString            -- ^ ROOT
          -> ByteString           -- ^ LOADPATH
          -> [AugFlag]            -- ^ FLAGS
          -> IO (Maybe (ForeignPtr Augeas)) -- ^ Augeas pointer
aug_init bstr1 bstr2 flags  =
     useAsCString bstr1 $ \root -> do
       useAsCString bstr2 $ \loadpath -> do
         aug_ptr <- c_aug_init root loadpath (combineFlags flags)
         if (aug_ptr == nullPtr)
            then do
              return Nothing
            else do
              ret_ptr <- newForeignPtr c_aug_close aug_ptr  -- release with aug_close
              return (Just ret_ptr)

-- ---------
-- aug_close
-- ---------

foreign import ccall safe "augeas.h &aug_close"
        c_aug_close :: FinalizerPtr Augeas

--{-|
-- from augeas.h:
--    Close this Augeas instance and free any storage associated with
--    it. After running AUG_CLOSE, AUG is invalid and can not be used for any
--    more operations.
---}
--aug_close :: FinalizerPtr Augeas
--aug_close =  c_aug_close 

-- ----------
-- aug_defvar
-- ----------
#ifdef HAS_AUGEAS_DEFVAR
foreign import ccall safe "augeas.h aug_defvar"
        c_aug_defvar :: Ptr Augeas                  -- aug
                     -> CString                     -- name
                     -> CString                     -- expr
                     -> IO (AugRet)                 -- return_value
#endif

{-|  
  Function: aug_defvar
  
   Define a variable NAME whose value is the result of evaluating EXPR. If
   a variable NAME already exists, its name will be replaced with the
   result of evaluating EXPR.
  
   If EXPR is Nothing, the variable NAME will be removed if it is defined.
  
   Path variables can be used in path expressions later on by prefixing
   them with '$'.
  
   Returns -1 on error; on success, returns 0 if EXPR evaluates to anything
   other than a nodeset, and the number of nodes if EXPR evaluates to a
   nodeset
-}
aug_defvar :: Ptr Augeas  -- ^ Augeas pointer
           -> ByteString  -- ^ NAME
           -> (Maybe ByteString)  -- ^ Maybe EXPR
           -> IO (AugRet) -- ^ AugRet

aug_defvar aug_ptr bstr1 maybe_bstr2 = 
#ifndef HAS_AUGEAS_DEFVAR
               Prelude.error "aug_defvar requires at least augeas version 0.5.0"
#else
               useAsCString bstr1 $ \name -> do
                 ret <- (case maybe_bstr2 of
                           (Just bstr2) ->  useAsCString bstr2 $ \expr -> do c_aug_defvar aug_ptr name expr
                           (Nothing) ->     c_aug_defvar aug_ptr name nullPtr)                   
                 return ret
#endif

-- -----------
-- aug_defnode
-- -----------
#ifdef HAS_AUGEAS_DEFNODE
foreign import ccall safe "augeas.h aug_defnode"
        c_aug_defnode :: Ptr Augeas                  -- aug
                      -> CString                     -- name
                      -> CString                     -- expr
                      -> CString                     -- value
                      -> Ptr CInt                    -- created
                      -> IO (CInt)               -- return_value
#endif

{-|  
 Function: aug_defnode

 Define a variable NAME whose value is the result of evaluating EXPR,
 which must be non-NULL and evaluate to a nodeset. If a variable NAME
 already exists, its name will be replaced with the result of evaluating
 EXPR.
 
 If EXPR evaluates to an empty nodeset, a node is created, equivalent to
 calling AUG_SET(AUG, EXPR, VALUE) and NAME will be the nodeset containing
 that single node.
 
 If CREATED is non-NULL, it is set to 1 if a node was created, and 0 if
 it already existed.
 
 Returns -1 on error; on success, returns the number of nodes in the
 nodeset 
-}



aug_defnode :: Ptr Augeas  -- ^ Augeas pointer
            -> ByteString  -- ^ NAME
            -> ByteString  -- ^ EXPR
            -> ByteString  -- ^ VALUE
            -> IO (AugRet,Maybe Bool) -- ^ (AugMatch,b_NodeCreated)
aug_defnode aug_ptr bstr1 bstr2 bstr3 = 
#ifndef HAS_AUGEAS_DEFNODE
        Prelude.error "aug_defnode requires at least augeas version 0.5.0"
#else
        useAsCString bstr1 $ \name -> do
          useAsCString bstr2 $ \expr -> do
            useAsCString bstr3 $ \value -> do
              alloca $ \created -> do
                ret <- c_aug_defnode aug_ptr name expr value created
                if ret /= -1 
                  then do
                    i_created <- peek created
                    if i_created == 0 
                      then do
                        return ((AugRet ret), Just False)
                      else do
                        return ((AugRet ret), Just True)
                  else do
                    return ((AugRet ret), Nothing)
#endif

-- -------
-- aug_get 
-- -------
#ifdef HAS_AUGEAS_GET
foreign import ccall safe "augeas.h aug_get"
        c_aug_get :: Ptr Augeas     -- aug
                  -> CString        -- path
                  -> Ptr CString    -- value
                  -> IO (CInt)      -- return_value
#endif

{-|  
  Lookup the value associated with PATH. VALUE can be NULL, in which case
  it is ignored. If VALUE is not NULL, it is used to return a pointer to
  the value associated with PATH if PATH matches exactly one node. If PATH
  matches no nodes or more than one node, *VALUE is set to NULL. Note that
  it is perfectly legal for nodes to have a NULL value, and that that by 
  itself does not indicate an error.

  Return AugMatch.exactly_one if there is exactly one node matching PATH, AugMatch.no_match if there is none,
  and AugMatch.invalid_match if there is more than one node matching PATH, or if
  PATH is not a legal path expression.
-}

aug_get :: Ptr Augeas  -- ^ Augeas pointer
        -> ByteString  -- ^ PATH
        -> IO (Either AugMatch (Maybe String)) -- ^ Either AugMatch or VALUE
aug_get aug_ptr bstr1 = 
#ifndef HAS_AUGEAS_GET
    Prelude.error "aug_get requires at least augeas version 0.0.1"
#else
    useAsCString bstr1 $ \path -> do
      alloca $ \value -> do
        ret <- c_aug_get aug_ptr path value
        if ret == 1
           then do 
             if value == nullPtr 
                then do
                  return (Left (AugMatch ret))
                else do
                  peeked <- peek value
                  if peeked == nullPtr
                     then do
                         return (Right Nothing)
                     else do
                         str_peeked <- peekCString peeked
                         return (Right (Just str_peeked))
           else do                   
             return (Left (AugMatch ret))

#endif

-- -------
-- aug_set
-- -------
#ifdef HAS_AUGEAS_SET
foreign import ccall safe "augeas.h aug_set"
        c_aug_set :: Ptr Augeas                  -- aug
                  -> CString                     -- path
                  -> CString                     -- value
                  -> IO (AugRet)                   -- return value
#endif

{-|

 Set the value associated with PATH to VALUE. VALUE is copied into the
 internal data structure. Intermediate entries are created if they don't
 exist. 

 Return AugRet.success on success, AugRet.error on error. It is an error if more than one
 node matches PATH.

-}
aug_set :: Ptr Augeas  -- ^ Augeas pointer
        -> ByteString  -- ^ PATH
        -> ByteString  -- ^ VALUE
        -> IO (AugRet) -- ^ return value
aug_set aug_ptr bs1 bs2 = 
#ifndef HAS_AUGEAS_SET
    Prelude.error "aug_insert requires at least augeas version 0.0.1"
#else
    useAsCString bs1 $ \path -> do
      useAsCString bs2 $ \value -> do
         ret <- c_aug_set aug_ptr path value
         return ret
#endif

-- ----------
-- aug_insert
-- ----------
#ifdef HAS_AUGEAS_INSERT
foreign import ccall safe "augeas.h aug_insert"
        c_aug_insert :: Ptr Augeas               -- aug
                     -> CString                  -- path
                     -> CString                  -- label
                     -> AugBefore                -- before
                     -> IO (AugRet)              -- return value
#endif

{-|

 Create a new sibling LABEL for PATH by inserting into the tree just
 before PATH if BEFORE == just_before or just after PATH if BEFORE == just_after.

 PATH must match exactly one existing node in the tree, and LABEL must be
 a label, i.e. not contain a '/', '*' or end with a bracketed index
 '[N]'.

 Return AugRet.success on success, and AugRet.error if the insertion fails.

-}
aug_insert :: Ptr Augeas   -- ^ Augeas pointer
           -> ByteString   -- ^ PTH
           -> ByteString   -- ^ LABEL
           -> AugBefore    -- ^ BEFORE
           -> IO (AugRet)  -- ^ return value
aug_insert aug_ptr bs1 bs2 before = 
#ifndef HAS_AUGEAS_INSERT
    Prelude.error "aug_insert requires at least augeas version 0.0.1"
#else
    useAsCString bs1 $ \path -> do
      useAsCString bs2 $ \label -> do
         ret <- c_aug_insert aug_ptr path label before
         return ret
#endif

-- ------
-- aug_rm
-- ------
#ifdef HAS_AUGEAS_RM
foreign import ccall safe "augeas.h aug_rm"
        c_aug_rm :: Ptr Augeas                   -- aug
                 -> CString                      -- path
                 -> IO (CInt)                    -- return value
#endif

{-|

 Remove path and all its children. Returns the number of entries removed.
 All nodes that match PATH, and their descendants, are removed.

-}
aug_rm :: Ptr Augeas  -- ^ Augeas pointer
       -> ByteString  -- ^ PATH
       -> IO (CInt)   -- ^ number of entries removed
aug_rm aug_ptr bs_path = 
#ifndef HAS_AUGEAS_RM
    Prelude.error "aug_mv requires at least augeas version 0.0.1"
#else
    useAsCString bs_path $ \path -> do    
      ret <- c_aug_rm aug_ptr path
      return ret
#endif

-- ------
-- aug_mv
-- ------
#ifdef HAS_AUGEAS_MV
foreign import ccall safe "augeas.h aug_mv"
        c_aug_mv :: Ptr Augeas                   -- aug
                 -> CString                      -- src
                 -> CString                      -- dst
                 -> IO (AugRet)                    -- return value
#endif

{- |
 Move the node SRC to DST. SRC must match exactly one node in the
 tree. DST must either match exactly one node in the tree, or may not
 exist yet. If DST exists already, it and all its descendants are
 deleted. If DST does not exist yet, it and all its missing ancestors are
 created.

 Note that the node SRC always becomes the node DST: when you move \/a\/b
 to \/x, the node \/a\/b is now called \/x, no matter whether \/x existed
 initially or not.

 Return AugRet.success on success and AugRet.error on failure.
-}
aug_mv :: Ptr Augeas  -- ^ Augeas pointer
       -> ByteString  -- ^ SRC
       -> ByteString  -- ^ DEST
       -> IO (AugRet) -- ^ return value
aug_mv aug_ptr bs_src bs_dst = 
#ifndef HAS_AUGEAS_MV
        Prelude.error "aug_mv requires at least augeas version 0.3.0"
#else
        useAsCString bs_src $ \src -> do
          useAsCString bs_dst $ \dst -> do
             ret <- c_aug_mv aug_ptr src dst
             return ret
#endif

-- ---------
-- aug_match
-- ---------
#ifdef HAS_AUGEAS_MATCH
foreign import ccall safe "augeas.h aug_match"
        c_aug_match :: Ptr Augeas                -- aug
                    -> CString                   -- path
                    -> Ptr (Ptr CString)         -- matches
                    -> IO (CInt)                 -- return value
#endif

{-|
 Return the number of matches of the path expression PATH in AUG. If
 MATCHES is non-NULL, an array with the returned number of elements will
 be allocated and filled with the paths of the matches. The caller must
 free both the array and the entries in it. The returned paths are
 sufficiently qualified to make sure that they match exactly one node in
 the current tree.

 If MATCHES is NULL, nothing is allocated and only the number
 of matches is returned.

 Returns -1 on error, or the total number of matches (which might be 0).

 Path expressions use a very simple subset of XPath: the path PATH
 consists of a number of segments, separated by '/'; each segment can
 either be a '*', matching any tree node, or a string, optionally
 followed by an index in brackets, matching tree nodes labelled with
 exactly that string. If no index is specified, the expression matches
 all nodes with that label; the index can be a positive number N, which
 matches exactly the Nth node with that label (counting from 1), or the
 special expression 'last()' which matches the last node with the given
 label. All matches are done in fixed positions in the tree, and nothing
 matches more than one path segment.

-}

aug_match :: Ptr Augeas    -- ^ Augeas pointer
          -> ByteString    -- ^ PATH
          -> IO (Int, Maybe [String]) -- ^ (match count, MATCHES)
aug_match aug_ptr bs_path = 
#ifndef HAS_AUGEAS_MATCH
   Prelude.error "aug_match requires at least augeas version 0.0.1"  
#else
    useAsCString bs_path $ \path -> do
      alloca $ \matches -> do
        ret <- c_aug_match aug_ptr path matches
        if ret == -1 
           then do
             return (-1, Nothing)
           else do
             matches_cstrs <- peekArray (fromIntegral ret) =<< peek matches

             -- There's got to be a better way to map (IO [CString]) to (IO [String]) ...
             matches_strs <- Prelude.foldr (\t io_l -> do s <- peekCString t; l <- io_l; return (s:l)) (return []) matches_cstrs

             return (fromIntegral ret, Just matches_strs)
#endif

-- --------
-- aug_save
-- --------
#ifdef HAS_AUGEAS_SAVE
foreign import ccall safe "augeas.h aug_save"
        c_aug_save :: Ptr Augeas                 -- aug
                   -> IO (AugRet)                  -- return value
#endif

{-|

 Write all pending changes to disk. 

 Return AugRet.error if an error is encountered, AugRet.success on success. 
 Only files that had any changes made to them are written.

 If AUG_SAVE_NEWFILE is set in the FLAGS passed to AUG_INIT, create
 changed files as new files with the extension ".augnew", and leave the
 original file unmodified.

 Otherwise, if AUG_SAVE_BACKUP is set in the FLAGS passed to AUG_INIT,
 move the original file to a new file with extension ".augsave".

 If neither of these flags is set, overwrite the original file.

-}
aug_save :: Ptr Augeas    -- ^ Augeas pointer
         -> IO (AugRet)   -- ^ return value
aug_save aug_ptr = 
#ifndef HAS_AUGEAS_SAVE
    Prelude.error "aug_save requires at least augeas version 0.0.1"
#else
    do 
      ret <- c_aug_save aug_ptr
      return ret
#endif

-- --------
-- aug_load
-- --------
#ifdef HAS_AUGEAS_LOAD
foreign import ccall safe "augeas.h aug_load"
        c_aug_load :: Ptr Augeas                -- aug
                    -> IO (CInt)                 -- return value
#endif

{-|
 Function: aug_load
 
 Load files into the tree. Which files to load and what lenses to use on
 them is specified under /augeas/load in the tree; each entry
 /augeas/load/NAME specifies a 'transform', by having itself exactly one
 child 'lens' and any number of children labelled 'incl' and 'excl'. The
 value of NAME has no meaning.
 
 The 'lens' grandchild of /augeas/load specifies which lens to use, and
 can either be the fully qualified name of a lens 'Module.lens' or
 '@Module'. The latter form means that the lens from the transform marked
 for autoloading in MODULE should be used.
 
 The 'incl' and 'excl' grandchildren of /augeas/load indicate which files
 to transform. Their value are used as glob patterns. Any file that
 matches at least one 'incl' pattern and no 'excl' pattern is
 transformed. The order of 'incl' and 'excl' entries is irrelevant.
 
 When AUG_INIT is first called, it populates /augeas/load with the
 transforms marked for autoloading in all the modules it finds.
 
 Before loading any files, AUG_LOAD will remove everything underneath
 /augeas/files and /files, regardless of whether any entries have been
 modified or not.
 
 Returns -1 on error, 0 on success. Note that success includes the case
 where some files could not be loaded. Details of such files can be found
 as '/augeas//error'.

-}
aug_load :: Ptr Augeas    -- ^ Augeas pointer
         -> IO (AugRet)   -- ^ return value
aug_load aug_ptr = 
#ifndef HAS_AUGEAS_LOAD
    Prelude.error "aug_load requires at least augeas version 0.5.0"
#else
    do
      ret <- c_aug_load aug_ptr
      return (AugRet ret)
#endif

-- ---------
-- aug_print
-- ---------
-- FILE *fdopen(int fildes, const char *mode);
foreign import ccall "" fdopen :: Fd -> CString -> IO (Ptr CFile)

foreign import ccall "" fflush :: (Ptr CFile) -> IO (Int)

foreign import ccall "" fclose :: (Ptr CFile) -> IO (Int)
 
handleToCFile :: Handle -> String -> IO (Ptr CFile)
handleToCFile h m =
 do iomode <- newCString m

    -- Duplicate the handle, so the original stays open after the handleToFd call closes the duplicate
    dup_h <- hDuplicate h      
    fd <- handleToFd dup_h
    fdopen fd iomode

-- surface aug_print
#ifdef HAS_AUGEAS_PRINT
foreign import ccall safe "augeas.h aug_print"
        c_aug_print :: Ptr Augeas               -- aug
                    -> Ptr CFile                -- out
                    -> CString                  -- path
                    -> IO (AugRet)              -- return value
#endif

{-|
 Print each node matching PATH and its descendants to OUT.
 Return AugRet.success on success, or AugRet.error on failure

-}

aug_print :: Ptr Augeas  -- ^ Augeas pointer
          -> Handle      -- ^ Already opened file handle
          -> ByteString  -- ^ PATH
          -> IO (AugRet) -- ^ return value
aug_print aug_ptr fptr_out bs_path = 
#ifndef HAS_AUGEAS_PRINT
   Prelude.error "aug_print requires at least augeas version 0.0.1"
#else
   useAsCString bs_path $ \path -> do
     out <- handleToCFile fptr_out "w"
     ret <- c_aug_print aug_ptr out path
     _ <- fflush out
     _ <- fclose out
     return(ret)
#endif


-- ---------
-- aug_error
-- ---------
#ifdef HAS_AUGEAS_ERROR
foreign import ccall safe "augeas.h aug_error"
        c_aug_error :: Ptr Augeas               -- aug
                    -> IO (AugErrCode)          -- error code
#endif

{-|
 Return a human-readable message for the error code */
-}

aug_error :: Ptr Augeas  -- ^ Augeas pointer
           -> IO (AugErrCode) -- ^ return value
aug_error aug_ptr = 
#ifndef HAS_AUGEAS_ERROR
        Prelude.error "aug_error requires at least augeas version 0.6.0"
#else
        do 
          ret <- c_aug_error aug_ptr
          return(ret)
#endif

-- -----------------
-- aug_error_message
-- -----------------
#ifdef HAS_AUGEAS_ERROR_MESSAGE
foreign import ccall safe "augeas.h aug_error_message"
        c_aug_error_message :: Ptr Augeas               -- aug
                            -> IO (CString)             -- return value
#endif

{-|
 Return a human-readable message for the error code */
-}
aug_error_message :: Ptr Augeas  -- ^ Augeas pointer
                  -> IO (ByteString) -- ^ return value
aug_error_message aug_ptr = 
#ifndef HAS_AUGEAS_ERROR_MESSAGE
    Prelude.error "aug_error_message requires at least augeas version 0.6.0"
#else
    do
      cstr <- c_aug_error_message aug_ptr
      ret <- packCString cstr
      return(ret)
#endif

-- -----------------------
-- aug_error_minor_message
-- -----------------------
#ifdef HAS_AUGEAS_ERROR_MINOR_MESSAGE
foreign import ccall safe "augeas.h aug_error_minor_message"
        c_aug_error_minor_message :: Ptr Augeas               -- aug
                                  -> IO (CString)             -- return value
#endif

{-|
 Return a human-readable message elaborating the error code; might be
 NULL. For example, when the error code is AUG_EPATHX, this will explain
 how the path expression is invalid */
-}
aug_error_minor_message :: Ptr Augeas      -- ^ Augeas pointer
                        -> IO (ByteString) -- ^ return value
aug_error_minor_message aug_ptr = 
#ifndef HAS_AUGEAS_ERROR_MINOR_MESSAGE
    Prelude.error "aug_error_minor_message requires at least augeas version 0.6.0"
#else
    do
      cstr <- c_aug_error_minor_message aug_ptr
      ret <- packCString cstr
      return(ret)
#endif

-- -----------------
-- aug_error_details
-- -----------------
#ifdef HAS_AUGEAS_ERROR_DETAILS
foreign import ccall safe "augeas.h aug_error_details"
        c_aug_error_details :: Ptr Augeas               -- aug
                           -> IO (CString)             -- return value
#endif

{-|
 Return details about the error, which might be NULL. For example, for
 AUG_EPATHX, indicates where in the path expression the error
 occurred. The returned value can only be used until the next API call
-}
aug_error_details :: Ptr Augeas  -- ^ Augeas pointer
                  -> IO (ByteString) -- ^ return value
aug_error_details aug_ptr = 
#ifndef HAS_AUGEAS_ERROR_DETAILS
    Prelude.error "aug_error_details requires at least augeas version 0.6.0"
#else
    do 
      cstr <- c_aug_error_details aug_ptr
      ret <- packCString cstr
      return(ret)
#endif

-- --------
-- aug_setm
-- --------
#ifdef HAS_AUGEAS_SETM
foreign import ccall safe "augeas.h aug_setm"
        c_aug_setm :: Ptr Augeas  -- aug
                      -> CString -- base
                      -> CString -- sub
                      -> CString -- value
                      -> IO (AugRet) --return value
#endif 

{-|
 Set the value of multiple nodes in one operation. Find or create a node
 matching SUB by interpreting SUB as a path expression relative to each
 node matching BASE. SUB may be NULL, in which case all the nodes
 matching BASE will be modified.

 Returns:
 number of modified nodes on success, -1 on error
-}
aug_setm :: Ptr Augeas          -- ^Augeas pointer
         -> ByteString          -- base
         -> (Maybe ByteString)  -- sub
         -> ByteString          -- value
         -> IO (AugRet)         -- retval
aug_setm aug_ptr bstr1 maybe_bstr2 bstr3  =
#ifndef HAS_AUGEAS_SETM
    Prelude.error "aug_setm requires at least augeas version 0.7.2"
#else
    useAsCString bstr1 $ \base -> do
      useAsCString bstr3 $ \value -> do
         ret <- (case maybe_bstr2 of
                   (Just bstr2) -> useAsCString bstr2 $ \sub -> do c_aug_setm aug_ptr base sub value
                   (Nothing) ->  c_aug_setm aug_ptr base nullPtr value
                ) 
         return ret

#endif