{-# LINE 2 "./Graphics/UI/Gtk/WebKit/WebDatabase.chs" #-}
-- -*-haskell-*-
-----------------------------------------------------------------------------
-- Module : Graphics.UI.Gtk.WebKit.WebDatabase
-- Author : Andy Stewart
-- Copyright : (c) 2010 Andy Stewart <lazycat.manatee@gmail.com>
--
-- 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 2.1 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.
--
-- |
-- Maintainer : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
-- Access to the WebKit Web Database
-----------------------------------------------------------------------------

module Graphics.UI.Gtk.WebKit.WebDatabase (
-- * Description
-- | WebKitWebDatabase is a representation of a Web Database database. The proposed Web Database standard
-- introduces support for SQL databases that web sites can create and access on a local computer
-- through JavaScript.
--
-- To get access to all databases defined by a security origin, use
-- 'securityOriginGetDatabases' Each database has a canonical name, as well as a user-friendly
-- display name.
--
-- WebKit uses SQLite to create and access the local SQL databases. The location of a WebKitWebDatabase
-- can be accessed wth 'webDatabaseGetFilename' You can configure the location of all
-- databases with 'setDatabaseDirectoryPath'.
--
-- For each database the web site can define an estimated size which can be accessed with
-- 'webDatabaseGetExpectedSize' The current size of the database in bytes is returned by
-- 'webDatabaseGetSize'.
--
-- For more information refer to the Web Database specification proposal at
-- http:

-- * Types
  WebDatabase,
  WebDatabaseClass,

-- * Methods
  webDatabaseGetDisplayName,
  webDatabaseGetExpectedSize,
  webDatabaseGetFilename,
  webDatabaseGetName,
  webDatabaseGetSecurityOrigin,
  webDatabaseGetSize,
  webDatabaseRemove,
) where

import Control.Monad (liftM)

import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.GError
import Graphics.UI.Gtk.Gdk.Events

import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.WebKit.Types
{-# LINE 71 "./Graphics/UI/Gtk/WebKit/WebDatabase.chs" #-}
import System.Glib.GObject
{-# LINE 72 "./Graphics/UI/Gtk/WebKit/WebDatabase.chs" #-}


{-# LINE 74 "./Graphics/UI/Gtk/WebKit/WebDatabase.chs" #-}

-- | Returns the name of the 'WebDatabase' as seen by the user.
webDatabaseGetDisplayName ::
   WebDatabaseClass self => self
 -> IO String
webDatabaseGetDisplayName wd =
  (\(WebDatabase arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_database_get_display_name argPtr1) (toWebDatabase wd) >>= peekCString

-- | Returns the expected size of the Database in bytes as defined by the web author. The Web Database standard allows web authors to
-- specify an expected size of the database to optimize the user experience.
webDatabaseGetExpectedSize ::
   WebDatabaseClass self => self
 -> IO Int
webDatabaseGetExpectedSize wd =
    liftM fromIntegral $ (\(WebDatabase arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_database_get_expected_size argPtr1) (toWebDatabase wd)

-- | Returns the absolute filename to the WebKitWebDatabase file on disk.
webDatabaseGetFilename ::
   WebDatabaseClass self => self
 -> IO String
webDatabaseGetFilename wd =
  (\(WebDatabase arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_database_get_filename argPtr1) (toWebDatabase wd) >>= peekCString

-- | Returns the canonical name of the 'WebDatabase'.
webDatabaseGetName ::
   WebDatabaseClass self => self
 -> IO String
webDatabaseGetName wd =
  (\(WebDatabase arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_database_get_name argPtr1) (toWebDatabase wd) >>= peekCString

-- | Returns the security origin of the WebKitWebDatabase.
webDatabaseGetSecurityOrigin ::
   WebDatabaseClass self => self
 -> IO SecurityOrigin
webDatabaseGetSecurityOrigin wd =
  makeNewGObject mkSecurityOrigin $ (\(WebDatabase arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_database_get_security_origin argPtr1) (toWebDatabase wd)

-- | Returns the actual size of the 'WebDatabase' space on disk in bytes.
webDatabaseGetSize ::
   WebDatabaseClass self => self
 -> IO Int
webDatabaseGetSize wd =
    liftM fromIntegral $ (\(WebDatabase arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_database_get_size argPtr1) (toWebDatabase wd)

-- | Removes the 'WebDatabase' from its security origin and destroys all data stored in the database.
webDatabaseRemove ::
   WebDatabaseClass self => self
 -> IO ()
webDatabaseRemove wd =
  (\(WebDatabase arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_database_remove argPtr1) (toWebDatabase wd)

foreign import ccall safe "webkit_web_database_get_display_name"
  webkit_web_database_get_display_name :: ((Ptr WebDatabase) -> (IO (Ptr CChar)))

foreign import ccall safe "webkit_web_database_get_expected_size"
  webkit_web_database_get_expected_size :: ((Ptr WebDatabase) -> (IO CULLong))

foreign import ccall safe "webkit_web_database_get_filename"
  webkit_web_database_get_filename :: ((Ptr WebDatabase) -> (IO (Ptr CChar)))

foreign import ccall safe "webkit_web_database_get_name"
  webkit_web_database_get_name :: ((Ptr WebDatabase) -> (IO (Ptr CChar)))

foreign import ccall safe "webkit_web_database_get_security_origin"
  webkit_web_database_get_security_origin :: ((Ptr WebDatabase) -> (IO (Ptr SecurityOrigin)))

foreign import ccall safe "webkit_web_database_get_size"
  webkit_web_database_get_size :: ((Ptr WebDatabase) -> (IO CULLong))

foreign import ccall safe "webkit_web_database_remove"
  webkit_web_database_remove :: ((Ptr WebDatabase) -> (IO ()))