-- GENERATED by C->Haskell Compiler, version 0.16.0 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./Gnome/Keyring/Keyring.chs" #-}-- Copyright (C) 2009 John Millikin <jmillikin@gmail.com>
-- 
-- 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 3 of the License, or
-- 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, see <http://www.gnu.org/licenses/>.
-- 
-- |
-- Maintainer  : John Millikin <jmillikin@gmail.com>
-- Stability   : experimental
-- Portability : non-portable (FFI)
-- 
-- GNOME Keyring manages multiple keyrings. Each keyring can store one or
-- more items, containing secrets.
-- 
-- One of the keyrings is the default keyring, which can in many cases be
-- used by specifying 'Nothing' for a keyring names.
-- 
-- Each keyring can be in a locked or unlocked state. A password must be
-- specified, either by the user or the calling application, to unlock the
-- keyring.

{-# LANGUAGE ForeignFunctionInterface #-}

{-# LINE 33 "./Gnome/Keyring/Keyring.chs" #-}

module Gnome.Keyring.Keyring
	( KeyringName
	
	-- * Basic operations
	, getDefaultKeyring
	, setDefaultKeyring
	, listKeyringNames
	, create
	, delete
	, changePassword
	, listItemIDs
	
	-- * Locking and unlocking
	, lock
	, lockAll
	, unlock
	
	-- * Keyring information
	, KeyringInfo (..)
	, KeyringInfoToken
	, getInfo
	, setInfo
	) where

import Control.Exception (bracket)
import Data.Text.Lazy (Text)
import Gnome.Keyring.Item (findItems) -- for docs
import Gnome.Keyring.ItemInfo
import Gnome.Keyring.KeyringInfo
import Gnome.Keyring.Internal.FFI
import Gnome.Keyring.Internal.Operation
import Gnome.Keyring.Internal.Types

-- | Get the default keyring name. If no default keyring exists, then
-- 'Nothing' will be returned.
-- 
getDefaultKeyring :: Operation (Maybe KeyringName)
getDefaultKeyring = maybeTextOperation
	get_default_keyring
	get_default_keyring_sync

get_default_keyring :: GetStringCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
get_default_keyring a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  get_default_keyring'_ a1' a2' a3' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 80 "./Gnome/Keyring/Keyring.chs" #-}

get_default_keyring_sync :: IO (Result, Maybe Text)
get_default_keyring_sync =
  alloca $ \a1' -> 
  get_default_keyring_sync'_ a1' >>= \res ->
  stealNullableTextPtr a1'>>= \a1'' -> 
  let {res' = result res} in
  return (res', a1'')
{-# LINE 84 "./Gnome/Keyring/Keyring.chs" #-}

stealNullableTextPtr :: Ptr CString -> IO (Maybe Text)
stealNullableTextPtr ptr = bracket (peek ptr) free peekNullableText

-- | Change the default keyring.
-- 
setDefaultKeyring :: KeyringName -> Operation ()
setDefaultKeyring k = voidOperation
	(set_default_keyring k)
	(set_default_keyring_sync k)

set_default_keyring :: Text -> DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
set_default_keyring a1 a2 a3 a4 =
  withText a1 $ \a1' -> 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  set_default_keyring'_ a1' a2' a3' a4' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 101 "./Gnome/Keyring/Keyring.chs" #-}

set_default_keyring_sync :: Text -> IO ((Result, ()))
set_default_keyring_sync a1 =
  withText a1 $ \a1' -> 
  set_default_keyring_sync'_ a1' >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 105 "./Gnome/Keyring/Keyring.chs" #-}

-- | Get a list of keyring names. If no keyrings exist, an empty list
-- will be returned.
-- 
listKeyringNames :: Operation [KeyringName]
listKeyringNames = textListOperation
	list_keyring_names
	list_keyring_names_sync

list_keyring_names :: GetListCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
list_keyring_names a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  list_keyring_names'_ a1' a2' a3' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 119 "./Gnome/Keyring/Keyring.chs" #-}

list_keyring_names_sync :: IO (Result, [Text])
list_keyring_names_sync =
  alloca $ \a1' -> 
  list_keyring_names_sync'_ a1' >>= \res ->
  stealTextList a1'>>= \a1'' -> 
  let {res' = result res} in
  return (res', a1'')
{-# LINE 123 "./Gnome/Keyring/Keyring.chs" #-}

stealTextList :: Ptr (Ptr ()) -> IO [Text]
stealTextList ptr = bracket (peek ptr)
	gnome_keyring_string_list_free
{-# LINE 127 "./Gnome/Keyring/Keyring.chs" #-}
	(mapGList peekText)

-- | Create a new keyring with the specified name. In most cases, 'Nothing'
-- will be passed as the password, which will prompt the user to enter a
-- password of their choice.
-- 
create :: KeyringName -> Maybe Text -> Operation ()
create k p = voidOperation (c_create k p) (create_sync k p)

c_create :: Text -> Maybe Text -> DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
c_create a1 a2 a3 a4 a5 =
  withText a1 $ \a1' -> 
  withNullableText a2 $ \a2' -> 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  c_create'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 143 "./Gnome/Keyring/Keyring.chs" #-}

create_sync :: Text -> Maybe Text -> IO ((Result, ()))
create_sync a1 a2 =
  withText a1 $ \a1' -> 
  withNullableText a2 $ \a2' -> 
  create_sync'_ a1' a2' >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 148 "./Gnome/Keyring/Keyring.chs" #-}

-- | Delete a keyring. Once a keyring is deleted, there is no mechanism for
-- recovery of its contents.
-- 
delete :: KeyringName -> Operation ()
delete k = voidOperation (c_delete k) (delete_sync k)

c_delete :: Text -> DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
c_delete a1 a2 a3 a4 =
  withText a1 $ \a1' -> 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  c_delete'_ a1' a2' a3' a4' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 161 "./Gnome/Keyring/Keyring.chs" #-}

delete_sync :: Text -> IO ((Result, ()))
delete_sync a1 =
  withText a1 $ \a1' -> 
  delete_sync'_ a1' >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 165 "./Gnome/Keyring/Keyring.chs" #-}

-- | Lock a keyring, so that its contents may not be accessed without first
-- supplying a password.
-- 
-- Most keyring operations involving items require that the keyring first be
-- unlocked. One exception is 'findItems' and related computations.
-- 
lock :: Maybe KeyringName -> Operation ()
lock k = voidOperation (c_lock k) (lock_sync k)

c_lock :: Maybe Text -> DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
c_lock a1 a2 a3 a4 =
  withNullableText a1 $ \a1' -> 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  c_lock'_ a1' a2' a3' a4' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 181 "./Gnome/Keyring/Keyring.chs" #-}

lock_sync :: Maybe Text -> IO ((Result, ()))
lock_sync a1 =
  withNullableText a1 $ \a1' -> 
  lock_sync'_ a1' >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 185 "./Gnome/Keyring/Keyring.chs" #-}

-- | Lock all the keyrings, so that their contents may not be accessed
-- without first unlocking them with a password.
-- 
lockAll :: Operation ()
lockAll = voidOperation lock_all lock_all_sync

lock_all :: DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
lock_all a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  lock_all'_ a1' a2' a3' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 197 "./Gnome/Keyring/Keyring.chs" #-}

lock_all_sync :: IO ((Result, ()))
lock_all_sync =
  lock_all_sync'_ >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 200 "./Gnome/Keyring/Keyring.chs" #-}

-- | Unlock a keyring, so that its contents may be accessed. In most cases,
-- 'Nothing' will be specified as the password, which will prompt the user
-- to enter the correct password.
-- 
-- Most keyring operations involving items require that the keyring first be
-- unlocked. One exception is 'findItems' and related computations.
-- 
unlock :: Maybe KeyringName -> Maybe Text -> Operation ()
unlock k p = voidOperation (c_unlock k p) (unlock_sync k p)

c_unlock :: Maybe Text -> Maybe Text -> DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
c_unlock a1 a2 a3 a4 a5 =
  withNullableText a1 $ \a1' -> 
  withNullableText a2 $ \a2' -> 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  c_unlock'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 218 "./Gnome/Keyring/Keyring.chs" #-}

unlock_sync :: Maybe Text -> Maybe Text -> IO ((Result, ()))
unlock_sync a1 a2 =
  withNullableText a1 $ \a1' -> 
  withNullableText a2 $ \a2' -> 
  unlock_sync'_ a1' a2' >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 223 "./Gnome/Keyring/Keyring.chs" #-}

-- | Get information about the keyring.
-- 
getInfo :: Maybe KeyringName -> Operation KeyringInfo
getInfo k = keyringInfoOperation (get_info k) (get_info_sync k)

get_info :: Maybe Text -> GetKeyringInfoCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
get_info a1 a2 a3 a4 =
  withNullableText a1 $ \a1' -> 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  get_info'_ a1' a2' a3' a4' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 235 "./Gnome/Keyring/Keyring.chs" #-}

get_info_sync :: Maybe Text -> IO (Result, KeyringInfo)
get_info_sync a1 =
  withNullableText a1 $ \a1' -> 
  alloca $ \a2' -> 
  get_info_sync'_ a1' a2' >>= \res ->
  stealKeyringInfoPtr a2'>>= \a2'' -> 
  let {res' = result res} in
  return (res', a2'')
{-# LINE 240 "./Gnome/Keyring/Keyring.chs" #-}

-- | Set flags and info for the keyring. The only fields in the
-- 'KeyringInfo' which are used are 'keyringLockOnIdle' and
-- 'keyringLockTimeout'.
-- 
setInfo :: Maybe KeyringName -> KeyringInfo -> Operation ()
setInfo k info = voidOperation
	(set_info k info)
	(set_info_sync k info)

set_info :: Maybe Text -> KeyringInfo -> DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
set_info a1 a2 a3 a4 a5 =
  withNullableText a1 $ \a1' -> 
  withKeyringInfo a2 $ \a2' -> 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  set_info'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 257 "./Gnome/Keyring/Keyring.chs" #-}

set_info_sync :: Maybe Text -> KeyringInfo -> IO ((Result, ()))
set_info_sync a1 a2 =
  withNullableText a1 $ \a1' -> 
  withKeyringInfo a2 $ \a2' -> 
  set_info_sync'_ a1' a2' >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 262 "./Gnome/Keyring/Keyring.chs" #-}

-- | Change the password for a keyring. In most cases, 'Nothing' would
-- be specified for both the original and new passwords to allow the user
-- to type both.
-- 
changePassword :: KeyringName
               -> Maybe Text -- ^ Old password
               -> Maybe Text -- ^ New password
               -> Operation ()
changePassword k op np = voidOperation
	(change_password k op np)
	(change_password_sync k op np)

change_password :: Text -> Maybe Text -> Maybe Text -> DoneCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
change_password a1 a2 a3 a4 a5 a6 =
  withText a1 $ \a1' -> 
  withNullableText a2 $ \a2' -> 
  withNullableText a3 $ \a3' -> 
  let {a4' = id a4} in 
  let {a5' = id a5} in 
  let {a6' = id a6} in 
  change_password'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 283 "./Gnome/Keyring/Keyring.chs" #-}

change_password_sync :: Text -> Maybe Text -> Maybe Text -> IO ((Result, ()))
change_password_sync a1 a2 a3 =
  withText a1 $ \a1' -> 
  withNullableText a2 $ \a2' -> 
  withNullableText a3 $ \a3' -> 
  change_password_sync'_ a1' a2' a3' >>= \res ->
  let {res' = resultAndTuple res} in
  return (res')
{-# LINE 289 "./Gnome/Keyring/Keyring.chs" #-}

-- | Get a list of all the IDs for items in the keyring. All items which are
-- not flagged as 'ItemApplicationSecret' are included in the list. This
-- includes items that the calling application may not (yet) have access to.
listItemIDs :: Maybe KeyringName -> Operation [ItemID]
listItemIDs name = itemIDListOperation
	(list_item_ids name)
	(list_item_ids_sync name)

list_item_ids :: Maybe Text -> GetListCallbackPtr -> Ptr () -> DestroyNotifyPtr -> IO (CancellationKey)
list_item_ids a1 a2 a3 a4 =
  withNullableText a1 $ \a1' -> 
  let {a2' = id a2} in 
  let {a3' = id a3} in 
  let {a4' = id a4} in 
  list_item_ids'_ a1' a2' a3' a4' >>= \res ->
  let {res' = CancellationKey res} in
  return (res')
{-# LINE 304 "./Gnome/Keyring/Keyring.chs" #-}

list_item_ids_sync :: Maybe Text -> IO (Result, [ItemID])
list_item_ids_sync a1 =
  withNullableText a1 $ \a1' -> 
  alloca $ \a2' -> 
  list_item_ids_sync'_ a1' a2' >>= \res ->
  stealItemIDList a2'>>= \a2'' -> 
  let {res' = result res} in
  return (res', a2'')
{-# LINE 309 "./Gnome/Keyring/Keyring.chs" #-}

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_get_default_keyring"
  get_default_keyring'_ :: ((FunPtr (CInt -> ((Ptr CChar) -> ((Ptr ()) -> (IO ()))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ())))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_get_default_keyring_sync"
  get_default_keyring_sync'_ :: ((Ptr (Ptr CChar)) -> (IO CInt))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_set_default_keyring"
  set_default_keyring'_ :: ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ()))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_set_default_keyring_sync"
  set_default_keyring_sync'_ :: ((Ptr CChar) -> (IO CInt))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_list_keyring_names"
  list_keyring_names'_ :: ((FunPtr (CInt -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ())))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_list_keyring_names_sync"
  list_keyring_names_sync'_ :: ((Ptr (Ptr ())) -> (IO CInt))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_string_list_free"
  gnome_keyring_string_list_free :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_create"
  c_create'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ())))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_create_sync"
  create_sync'_ :: ((Ptr CChar) -> ((Ptr CChar) -> (IO CInt)))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_delete"
  c_delete'_ :: ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ()))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_delete_sync"
  delete_sync'_ :: ((Ptr CChar) -> (IO CInt))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_lock"
  c_lock'_ :: ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ()))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_lock_sync"
  lock_sync'_ :: ((Ptr CChar) -> (IO CInt))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_lock_all"
  lock_all'_ :: ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ())))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_lock_all_sync"
  lock_all_sync'_ :: (IO CInt)

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_unlock"
  c_unlock'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ())))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_unlock_sync"
  unlock_sync'_ :: ((Ptr CChar) -> ((Ptr CChar) -> (IO CInt)))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_get_info"
  get_info'_ :: ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ()))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_get_info_sync"
  get_info_sync'_ :: ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt)))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_set_info"
  set_info'_ :: ((Ptr CChar) -> ((Ptr ()) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ())))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_set_info_sync"
  set_info_sync'_ :: ((Ptr CChar) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_change_password"
  change_password'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ()))))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_change_password_sync"
  change_password_sync'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO CInt))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_list_item_ids"
  list_item_ids'_ :: ((Ptr CChar) -> ((FunPtr (CInt -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (Ptr ()))))))

foreign import ccall safe "Gnome/Keyring/Keyring.chs.h gnome_keyring_list_item_ids_sync"
  list_item_ids_sync'_ :: ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt)))