module Graphics.UI.Gtk.WebKit.Download (
Download,
DownloadClass,
DownloadError(..),
DownloadStatus(..),
downloadNew,
downloadStart,
downloadCancel,
downloadGetUri,
downloadGetNetworkRequest,
downloadGetNetworkResponse,
downloadGetSuggestedFilename,
downloadGetDestinationUri,
downloadGetProgress,
downloadGetElapsedTime,
downloadGetTotalSize,
downloadGetCurrentSize,
downloadGetStatus,
downloadSetDestinationUri,
currentSize,
destinationUri,
networkRequest,
networkResponse,
progress,
status,
suggestedFilename,
totalSize,
downloadError,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.GError
import System.Glib.Attributes as G
import System.Glib.Properties
import Graphics.UI.Gtk.Gdk.Events
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.Signals
import System.Glib.GObject
data DownloadError = DownloadErrorCancelledByUser
| DownloadErrorDestination
| DownloadErrorNetwork
deriving (Enum)
data DownloadStatus = DownloadStatusError
| DownloadStatusCreated
| DownloadStatusStarted
| DownloadStatusCancelled
| DownloadStatusFinished
instance Enum DownloadStatus where
fromEnum DownloadStatusError = (1)
fromEnum DownloadStatusCreated = 0
fromEnum DownloadStatusStarted = 1
fromEnum DownloadStatusCancelled = 2
fromEnum DownloadStatusFinished = 3
toEnum (1) = DownloadStatusError
toEnum 0 = DownloadStatusCreated
toEnum 1 = DownloadStatusStarted
toEnum 2 = DownloadStatusCancelled
toEnum 3 = DownloadStatusFinished
toEnum unmatched = error ("DownloadStatus.toEnum: Cannot match " ++ show unmatched)
succ DownloadStatusError = DownloadStatusCreated
succ DownloadStatusCreated = DownloadStatusStarted
succ DownloadStatusStarted = DownloadStatusCancelled
succ DownloadStatusCancelled = DownloadStatusFinished
succ _ = undefined
pred DownloadStatusCreated = DownloadStatusError
pred DownloadStatusStarted = DownloadStatusCreated
pred DownloadStatusCancelled = DownloadStatusStarted
pred DownloadStatusFinished = DownloadStatusCancelled
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x DownloadStatusFinished
enumFromThen _ _ = error "Enum DownloadStatus: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum DownloadStatus: enumFromThenTo not implemented"
downloadNew :: NetworkRequestClass request => request -> IO Download
downloadNew nr =
wrapNewGObject mkDownload $ (\(NetworkRequest arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_new argPtr1) (toNetworkRequest nr)
downloadStart::
DownloadClass self => self
-> IO()
downloadStart dl =
(\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_start argPtr1) (toDownload dl)
downloadCancel::
DownloadClass self => self
-> IO()
downloadCancel dl =
(\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_cancel argPtr1) (toDownload dl)
downloadGetUri::
(DownloadClass self, GlibString string) => self
-> IO (Maybe string)
downloadGetUri dl =
(\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_uri argPtr1) (toDownload dl)
>>= maybePeek peekUTFString
downloadGetNetworkRequest ::
DownloadClass self => self
-> IO NetworkRequest
downloadGetNetworkRequest dl =
makeNewGObject mkNetworkRequest $ (\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_network_request argPtr1) (toDownload dl)
downloadGetNetworkResponse ::
DownloadClass self => self
-> IO NetworkResponse
downloadGetNetworkResponse dl =
makeNewGObject mkNetworkResponse $ (\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_network_response argPtr1) (toDownload dl)
downloadGetSuggestedFilename ::
(DownloadClass self, GlibString string) => self
-> IO (Maybe string)
downloadGetSuggestedFilename dl =
(\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_suggested_filename argPtr1) (toDownload dl) >>= maybePeek peekUTFString
downloadGetDestinationUri ::
(DownloadClass self, GlibString string) => self
-> IO (Maybe string)
downloadGetDestinationUri dl =
(\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_destination_uri argPtr1) (toDownload dl) >>= maybePeek peekUTFString
downloadSetDestinationUri ::
(DownloadClass self, GlibString string) => self
-> string
-> IO()
downloadSetDestinationUri dl dest =
withUTFString dest $ \destPtr ->
(\(Download arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_set_destination_uri argPtr1 arg2) (toDownload dl) destPtr
downloadGetProgress ::
DownloadClass self => self
-> IO Double
downloadGetProgress dl =
liftM realToFrac $ (\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_progress argPtr1) (toDownload dl)
downloadGetElapsedTime ::
DownloadClass self => self
-> IO Double
downloadGetElapsedTime dl =
liftM realToFrac $ (\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_elapsed_time argPtr1) (toDownload dl)
downloadGetTotalSize ::
DownloadClass self => self
-> IO Int
downloadGetTotalSize dl =
liftM fromIntegral $ (\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_total_size argPtr1) (toDownload dl)
downloadGetCurrentSize ::
DownloadClass self => self
-> IO Int
downloadGetCurrentSize dl =
liftM fromIntegral $ (\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_current_size argPtr1) (toDownload dl)
downloadGetStatus ::
DownloadClass self => self
-> IO DownloadStatus
downloadGetStatus dl =
liftM (toEnum . fromIntegral) $ (\(Download arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_download_get_status argPtr1) (toDownload dl)
currentSize :: DownloadClass self => ReadAttr self Int
currentSize = readAttr downloadGetCurrentSize
destinationUri :: (DownloadClass self, GlibString string) => G.Attr self (Maybe string)
destinationUri = newAttrFromMaybeStringProperty "destination-uri"
networkRequest :: DownloadClass self => G.Attr self NetworkRequest
networkRequest =
newAttrFromObjectProperty "network-request"
webkit_network_request_get_type
networkResponse :: DownloadClass self => G.Attr self NetworkResponse
networkResponse =
newAttrFromObjectProperty "network-response"
webkit_network_response_get_type
progress :: DownloadClass self => ReadAttr self Double
progress = readAttr downloadGetProgress
status :: DownloadClass self => ReadAttr self DownloadStatus
status = readAttr downloadGetStatus
suggestedFilename :: (DownloadClass self, GlibString string) => ReadAttr self (Maybe string)
suggestedFilename = readAttr downloadGetSuggestedFilename
totalSize :: DownloadClass self => ReadAttr self Int
totalSize = readAttr downloadGetTotalSize
downloadError :: (DownloadClass self, GlibString string) => Signal self (Int -> Int -> string -> IO Bool)
downloadError = Signal (connect_INT_INT_GLIBSTRING__BOOL "error")
foreign import ccall safe "webkit_download_new"
webkit_download_new :: ((Ptr NetworkRequest) -> (IO (Ptr Download)))
foreign import ccall safe "webkit_download_start"
webkit_download_start :: ((Ptr Download) -> (IO ()))
foreign import ccall safe "webkit_download_cancel"
webkit_download_cancel :: ((Ptr Download) -> (IO ()))
foreign import ccall safe "webkit_download_get_uri"
webkit_download_get_uri :: ((Ptr Download) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_download_get_network_request"
webkit_download_get_network_request :: ((Ptr Download) -> (IO (Ptr NetworkRequest)))
foreign import ccall safe "webkit_download_get_network_response"
webkit_download_get_network_response :: ((Ptr Download) -> (IO (Ptr NetworkResponse)))
foreign import ccall safe "webkit_download_get_suggested_filename"
webkit_download_get_suggested_filename :: ((Ptr Download) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_download_get_destination_uri"
webkit_download_get_destination_uri :: ((Ptr Download) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_download_set_destination_uri"
webkit_download_set_destination_uri :: ((Ptr Download) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_download_get_progress"
webkit_download_get_progress :: ((Ptr Download) -> (IO CDouble))
foreign import ccall safe "webkit_download_get_elapsed_time"
webkit_download_get_elapsed_time :: ((Ptr Download) -> (IO CDouble))
foreign import ccall safe "webkit_download_get_total_size"
webkit_download_get_total_size :: ((Ptr Download) -> (IO CULong))
foreign import ccall safe "webkit_download_get_current_size"
webkit_download_get_current_size :: ((Ptr Download) -> (IO CULong))
foreign import ccall safe "webkit_download_get_status"
webkit_download_get_status :: ((Ptr Download) -> (IO CInt))
foreign import ccall safe "webkit_network_request_get_type"
webkit_network_request_get_type :: CULong
foreign import ccall safe "webkit_network_response_get_type"
webkit_network_response_get_type :: CULong