-- 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/ItemInfo/Internal.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/>.
-- 
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE MultiParamTypeClasses #-}

{-# LINE 19 "./Gnome/Keyring/ItemInfo/Internal.chs" #-}

module Gnome.Keyring.ItemInfo.Internal where
import Data.Text.Lazy (Text)
import Control.Exception (bracket)
import Foreign
import Foreign.C
import Gnome.Keyring.FFI

newtype ItemID = ItemID Word32
	deriving (Show, Eq, Ord)

data RawType = ITEM_GENERIC_SECRET
             | ITEM_NETWORK_PASSWORD
             | ITEM_NOTE
             | ITEM_CHAINED_KEYRING_PASSWORD
             | ITEM_ENCRYPTION_KEY_PASSWORD
             | ITEM_PK_STORAGE
             | ITEM_LAST_TYPE
             deriving (Show)
instance Enum RawType where
  fromEnum ITEM_GENERIC_SECRET = 0
  fromEnum ITEM_NETWORK_PASSWORD = 1
  fromEnum ITEM_NOTE = 2
  fromEnum ITEM_CHAINED_KEYRING_PASSWORD = 3
  fromEnum ITEM_ENCRYPTION_KEY_PASSWORD = 4
  fromEnum ITEM_PK_STORAGE = 256
  fromEnum ITEM_LAST_TYPE = 257

  toEnum 0 = ITEM_GENERIC_SECRET
  toEnum 1 = ITEM_NETWORK_PASSWORD
  toEnum 2 = ITEM_NOTE
  toEnum 3 = ITEM_CHAINED_KEYRING_PASSWORD
  toEnum 4 = ITEM_ENCRYPTION_KEY_PASSWORD
  toEnum 256 = ITEM_PK_STORAGE
  toEnum 257 = ITEM_LAST_TYPE
  toEnum unmatched = error ("RawType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 31 "./Gnome/Keyring/ItemInfo/Internal.chs" #-}

data ItemType
	= ItemGenericSecret
	| ItemNetworkPassword
	| ItemNote
	| ItemChainedKeyringPassword
	| ItemEncryptionKeyPassword
	| ItemPublicKeyStorage
	deriving (Show, Eq)

fromItemType :: ItemType -> CInt
fromItemType = fromIntegral . fromEnum . toRaw where
	toRaw ItemGenericSecret = ITEM_GENERIC_SECRET
	toRaw ItemNetworkPassword = ITEM_NETWORK_PASSWORD
	toRaw ItemNote = ITEM_NOTE
	toRaw ItemChainedKeyringPassword = ITEM_CHAINED_KEYRING_PASSWORD
	toRaw ItemEncryptionKeyPassword = ITEM_ENCRYPTION_KEY_PASSWORD
	toRaw ItemPublicKeyStorage = ITEM_PK_STORAGE

toItemType :: RawType -> ItemType
toItemType ITEM_GENERIC_SECRET = ItemGenericSecret
toItemType ITEM_NETWORK_PASSWORD = ItemNetworkPassword
toItemType ITEM_NOTE = ItemNote
toItemType ITEM_CHAINED_KEYRING_PASSWORD = ItemChainedKeyringPassword
toItemType ITEM_ENCRYPTION_KEY_PASSWORD = ItemEncryptionKeyPassword
toItemType ITEM_PK_STORAGE = ItemPublicKeyStorage
toItemType x = error $ "Unknown item type: " ++ show x

-- | Note: setting mtime and ctime will not affect the keyring
data ItemInfo = ItemInfo
	{ itemType        :: ItemType
	, itemSecret      :: Maybe Text
	, itemDisplayName :: Maybe Text
	, itemMTime       :: Integer -- TODO: TimeOfDay
	, itemCTime       :: Integer -- TODO: TimeOfDay
	}
	deriving (Show, Eq)

peekItemInfo :: Ptr () -> IO ItemInfo
peekItemInfo info = do
	cType <- gnome_keyring_item_info_get_type info
	secret <- stealNullableText =<< gnome_keyring_item_info_get_secret info
	name <- stealNullableText =<< gnome_keyring_item_info_get_display_name info
	mtime <- toInteger `fmap` gnome_keyring_item_info_get_mtime info
	ctime <- toInteger `fmap` gnome_keyring_item_info_get_ctime info
	let type' = toItemType . toEnum . fromIntegral $ cType
	return $ ItemInfo type' secret name mtime ctime

stealItemInfo :: Ptr (Ptr ()) -> IO ItemInfo
stealItemInfo ptr = bracket (peek ptr) freeItemInfo peekItemInfo

freeItemInfo :: Ptr () -> IO ()
freeItemInfo = gnome_keyring_item_info_free
{-# LINE 84 "./Gnome/Keyring/ItemInfo/Internal.chs" #-}

foreign import ccall "gnome-keyring.h &gnome_keyring_item_info_free"
	finalizeItemInfo :: FunPtr (Ptr a -> IO ())

withItemInfo :: ItemInfo -> (Ptr () -> IO a) -> IO a
withItemInfo info io = do
	fptr <- newForeignPtr finalizeItemInfo =<< gnome_keyring_item_info_new
{-# LINE 91 "./Gnome/Keyring/ItemInfo/Internal.chs" #-}
	withForeignPtr fptr $ \ptr -> do
	gnome_keyring_item_info_set_type ptr . fromItemType . itemType $ info
	withNullableText (itemSecret info) $ gnome_keyring_item_info_set_secret ptr
	withNullableText (itemDisplayName info) $ gnome_keyring_item_info_set_display_name ptr
	io ptr

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_get_type"
  gnome_keyring_item_info_get_type :: ((Ptr ()) -> (IO CInt))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_get_secret"
  gnome_keyring_item_info_get_secret :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_get_display_name"
  gnome_keyring_item_info_get_display_name :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_get_mtime"
  gnome_keyring_item_info_get_mtime :: ((Ptr ()) -> (IO CLong))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_get_ctime"
  gnome_keyring_item_info_get_ctime :: ((Ptr ()) -> (IO CLong))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_free"
  gnome_keyring_item_info_free :: ((Ptr ()) -> (IO ()))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_new"
  gnome_keyring_item_info_new :: (IO (Ptr ()))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_set_type"
  gnome_keyring_item_info_set_type :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_set_secret"
  gnome_keyring_item_info_set_secret :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall unsafe "Gnome/Keyring/ItemInfo/Internal.chs.h gnome_keyring_item_info_set_display_name"
  gnome_keyring_item_info_set_display_name :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))