{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.WebKit2.Structs.UserScript
    ( 

-- * Exported types
    UserScript(..)                          ,
    noUserScript                            ,


 -- * Methods
-- ** userScriptNew
    userScriptNew                           ,


-- ** userScriptRef
    userScriptRef                           ,


-- ** userScriptUnref
    userScriptUnref                         ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.WebKit2.Types
import GI.WebKit2.Callbacks

newtype UserScript = UserScript (ForeignPtr UserScript)
foreign import ccall "webkit_user_script_get_type" c_webkit_user_script_get_type :: 
    IO GType

instance BoxedObject UserScript where
    boxedType _ = c_webkit_user_script_get_type

noUserScript :: Maybe UserScript
noUserScript = Nothing

-- method UserScript::new
-- method type : Constructor
-- Args : [Arg {argName = "source", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "injected_frames", argType = TInterface "WebKit2" "UserContentInjectedFrames", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "injection_time", argType = TInterface "WebKit2" "UserScriptInjectionTime", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "whitelist", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "blacklist", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "source", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "injected_frames", argType = TInterface "WebKit2" "UserContentInjectedFrames", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "injection_time", argType = TInterface "WebKit2" "UserScriptInjectionTime", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "whitelist", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "blacklist", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit2" "UserScript"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_user_script_new" webkit_user_script_new :: 
    CString ->                              -- source : TBasicType TUTF8
    CUInt ->                                -- injected_frames : TInterface "WebKit2" "UserContentInjectedFrames"
    CUInt ->                                -- injection_time : TInterface "WebKit2" "UserScriptInjectionTime"
    Ptr CString ->                          -- whitelist : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- blacklist : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO (Ptr UserScript)


userScriptNew ::
    (MonadIO m) =>
    T.Text ->                               -- source
    UserContentInjectedFrames ->            -- injected_frames
    UserScriptInjectionTime ->              -- injection_time
    Maybe ([T.Text]) ->                     -- whitelist
    Maybe ([T.Text]) ->                     -- blacklist
    m UserScript
userScriptNew source injected_frames injection_time whitelist blacklist = liftIO $ do
    source' <- textToCString source
    let injected_frames' = (fromIntegral . fromEnum) injected_frames
    let injection_time' = (fromIntegral . fromEnum) injection_time
    maybeWhitelist <- case whitelist of
        Nothing -> return nullPtr
        Just jWhitelist -> do
            jWhitelist' <- packZeroTerminatedUTF8CArray jWhitelist
            return jWhitelist'
    maybeBlacklist <- case blacklist of
        Nothing -> return nullPtr
        Just jBlacklist -> do
            jBlacklist' <- packZeroTerminatedUTF8CArray jBlacklist
            return jBlacklist'
    result <- webkit_user_script_new source' injected_frames' injection_time' maybeWhitelist maybeBlacklist
    checkUnexpectedReturnNULL "webkit_user_script_new" result
    result' <- (wrapBoxed UserScript) result
    freeMem source'
    mapZeroTerminatedCArray freeMem maybeWhitelist
    freeMem maybeWhitelist
    mapZeroTerminatedCArray freeMem maybeBlacklist
    freeMem maybeBlacklist
    return result'

-- method UserScript::ref
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit2" "UserScript", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit2" "UserScript", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit2" "UserScript"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_user_script_ref" webkit_user_script_ref :: 
    Ptr UserScript ->                       -- _obj : TInterface "WebKit2" "UserScript"
    IO (Ptr UserScript)


userScriptRef ::
    (MonadIO m) =>
    UserScript ->                           -- _obj
    m UserScript
userScriptRef _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- webkit_user_script_ref _obj'
    checkUnexpectedReturnNULL "webkit_user_script_ref" result
    result' <- (wrapBoxed UserScript) result
    touchManagedPtr _obj
    return result'

-- method UserScript::unref
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit2" "UserScript", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit2" "UserScript", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_user_script_unref" webkit_user_script_unref :: 
    Ptr UserScript ->                       -- _obj : TInterface "WebKit2" "UserScript"
    IO ()


userScriptUnref ::
    (MonadIO m) =>
    UserScript ->                           -- _obj
    m ()
userScriptUnref _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    webkit_user_script_unref _obj'
    touchManagedPtr _obj
    return ()