File: WebFrame.chs

package info (click to toggle)
haskell-webkit 0.11.0-2
  • links: PTS, VCS
  • area: main
  • in suites: squeeze
  • size: 328 kB
  • ctags: 2
  • sloc: haskell: 386; ansic: 5; makefile: 2
file content (284 lines) | stat: -rw-r--r-- 9,915 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
-----------------------------------------------------------------------------
--  Module      :  Graphics.UI.Gtk.WebKit.WebFrame
--  Author      :  Cjacker Huang
--  Copyright   :  (c) 2009 Cjacker Huang <jzhuang@redflag-linux.com>
--  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)
--
-- The content of a 'WebView'
--
-- Note:
-- Functon `webkit_web_frame_get_global_context` can't binding now, 
-- Because it need `JSGlobalContextRef` exist in JavaScriptCore.
--
-- Function `webkit_web_frame_print_full` can't binding now,
-- Because library `GtkPrintOperation` haven't binding.
--
-----------------------------------------------------------------------------

module Graphics.UI.Gtk.WebKit.WebFrame (
-- * Types
  WebFrame,

-- * Constructors
  webFrameNew,

-- * Methods
  webFrameGetWebView,
  webFrameGetName,
  webFrameGetTitle,
  webFrameGetUri,
  webFrameGetParent,
  webFrameGetLoadStatus,
  webFrameLoadUri,
  webFrameLoadString,
  webFrameLoadAlternateString,
  webFrameLoadRequest,
  webFrameStopLoading,
  webFrameReload,
  webFrameFindFrame,
  webFrameGetDataSource,
  webFrameGetHorizontalScrollbarPolicy,
  webFrameGetVerticalScrollbarPolicy,
  webFrameGetProvisionalDataSource,
  webFrameGetSecurityOrigin,
  webFramePrint,
) 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.General.Enums

{#import Graphics.UI.Gtk.Abstract.Object#}	(makeNewObject)
{#import Graphics.UI.Gtk.WebKit.Types#}
{#import System.Glib.GObject#}

{#context lib="webkit" prefix ="webkit"#}

-- * Enums

{#enum LoadStatus {underscoreToCase}#}

------------------
-- Constructors


-- | Create a new 'WebFrame' instance with the given @webview@.
--
-- A 'WebFrame' contains the content of one URI.
webFrameNew :: 
    WebViewClass webview => webview  -- ^ @webview@ - the given webview
 -> IO WebFrame
webFrameNew webview =  
    constructNewGObject mkWebFrame $ {#call web_frame_new#} (toWebView webview)

-- | Return the 'WebView' that manages the given 'WebFrame'.
webFrameGetWebView :: 
    WebFrameClass self => self
 -> IO WebView
webFrameGetWebView webframe = 
    makeNewObject mkWebView $ liftM castPtr $ {#call web_frame_get_web_view#} (toWebFrame webframe)

-- | Return the name of the given 'WebFrame'.
webFrameGetName :: 
    WebFrameClass self => self
 -> IO (Maybe String) -- ^ the name string or @Nothing@ in case failed.
webFrameGetName webframe = 
    {#call web_frame_get_name#} (toWebFrame webframe) >>= maybePeek peekCString

-- | Return the title of the given 'WebFrame'.
webFrameGetTitle :: 
    WebFrameClass self => self 
 -> IO (Maybe String) -- ^ the title string or @Nothing@ in case failed.
webFrameGetTitle webframe = 
    {#call web_frame_get_title#} (toWebFrame webframe) >>= maybePeek peekCString

-- | Return the URI of the given 'WebFrame'.	
webFrameGetUri :: 
    WebFrameClass self => self 
 -> IO (Maybe String) -- ^ the URI string or @Nothing@ in case failed.
webFrameGetUri webframe = 
    {#call web_frame_get_uri#} (toWebFrame webframe) >>= maybePeek peekCString

-- | Return the 'WebFrame''s parent frame if it has one,
-- Otherwise return Nothing.
webFrameGetParent :: 
    WebFrameClass self => self 
 -> IO (Maybe WebFrame) -- ^ a 'WebFrame' or @Nothing@ in case failed.
webFrameGetParent webframe = 
    maybeNull (makeNewGObject mkWebFrame) $ {#call web_frame_get_parent#} (toWebFrame webframe)

-- | Determines the current status of the load.
--
-- frameĀ :   a WebKitWebView 
--                          
-- * Since 1.1.7
webFrameGetLoadStatus ::
    WebFrameClass self => self
 -> IO LoadStatus    
webFrameGetLoadStatus ls =
    liftM (toEnum . fromIntegral) $ {#call web_frame_get_load_status#} (toWebFrame ls)

-- | Request loading of the specified URI string.
webFrameLoadUri :: 
    WebFrameClass self => self 
 -> String -- ^ @uri@ - an URI string. 
 -> IO ()
webFrameLoadUri webframe uri = 
    withCString uri $ \uriPtr -> {#call web_frame_load_uri#}
    (toWebFrame webframe)
    uriPtr

-- | Requests loading of the given @content@ 
-- with the specified @mime_type@, @encoding@ and @base_uri@.
-- 
-- If @mime_type@ is @Nothing@, \"text/html\" is assumed.
--
-- If @encoding@ is @Nothing@, \"UTF-8\" is assumed.
webFrameLoadString :: 
    WebFrameClass self => self 
 -> String -- ^ @content@ - the content string to be loaded.
 -> (Maybe String) -- ^ @mime_type@ - the MIME type or @Nothing@. 
 -> (Maybe String) -- ^ @encoding@ - the encoding or @Nothing@.
 -> String -- ^ @base_uri@ - the base URI for relative locations.
 -> IO()
webFrameLoadString webframe content mimetype encoding baseuri = 
    withCString content  $ \contentPtr ->
    maybeWith withCString mimetype $ \mimetypePtr ->
    maybeWith withCString encoding $ \encodingPtr ->
    withCString baseuri  $ \baseuriPtr ->
        {#call web_frame_load_string#} 
          (toWebFrame webframe) 
          contentPtr 
          mimetypePtr 
          encodingPtr 
          baseuriPtr

-- |Request loading of an alternate content for a URL that is unreachable.
--
-- Using this method will preserve the back-forward list.
-- The URI passed in @base_uri@ has to be an absolute URI.		
webFrameLoadAlternateString :: 
    WebFrameClass self => self 
 -> String  -- ^ @content@ - the alternate content to display 
            -- as the main page of the frame
 -> String  -- ^ @base_uri@ - the base URI for relative locations. 
 -> String  -- ^ @unreachable_url@ - the URL for the alternate page content.
 -> IO()
webFrameLoadAlternateString webframe content baseurl unreachableurl = 
    withCString content  $ \contentPtr ->
    withCString baseurl  $ \baseurlPtr ->
    withCString unreachableurl  $ \unreachableurlPtr ->
        {#call web_frame_load_alternate_string#}
          (toWebFrame webframe) 
          contentPtr
          baseurlPtr
          unreachableurlPtr

-- | Connects to a given URI by initiating an asynchronous client request.
--
-- Creates a provisional data source that will transition to a committed data source once any data has been received. 
-- Use 'webFrameStopLoading' to stop the load. 
-- This function is typically invoked on the main frame.
webFrameLoadRequest :: 
   (WebFrameClass self, NetworkRequestClass requ) => self -> requ
 -> IO ()
webFrameLoadRequest webframe request =
  {#call web_frame_load_request#} (toWebFrame webframe) (toNetworkRequest request) 

-- | Stops and pending loads on the given data source and those of its children.
webFrameStopLoading :: 
    WebFrameClass self => self
 -> IO()
webFrameStopLoading webframe = 
    {#call web_frame_stop_loading#} (toWebFrame webframe)

-- |Reloads the initial request.
webFrameReload :: 
    WebFrameClass self => self
 -> IO()
webFrameReload webframe = 
    {#call web_frame_reload#} (toWebFrame webframe)

-- |Return the 'WebFrame' associated with the given name 
-- or @Nothing@ in case none if found
-- 
-- For pre-defined names, return the given webframe if name is 
webFrameFindFrame:: 
    WebFrameClass self => self 
 -> String  -- ^ @name@ - the name of the frame to be found.
 -> IO (Maybe WebFrame)
webFrameFindFrame webframe name = 
    withCString name $ \namePtr ->
	maybeNull (makeNewGObject mkWebFrame) $ 
          {#call web_frame_find_frame#} (toWebFrame webframe) namePtr

-- | Returns the committed data source.
webFrameGetDataSource :: 
   WebFrameClass self => self
 -> IO WebDataSource
webFrameGetDataSource webframe =
  makeNewGObject mkWebDataSource $ {#call web_frame_get_data_source#} (toWebFrame webframe)

-- | Return the policy of horizontal scrollbar.
webFrameGetHorizontalScrollbarPolicy :: 
   WebFrameClass self => self
 -> IO PolicyType   
webFrameGetHorizontalScrollbarPolicy webframe = 
    liftM (toEnum.fromIntegral) $
    {#call web_frame_get_horizontal_scrollbar_policy#} (toWebFrame webframe)
  
-- | Return the policy of vertical scrollbar.
webFrameGetVerticalScrollbarPolicy :: 
   WebFrameClass self => self
 -> IO PolicyType   
webFrameGetVerticalScrollbarPolicy webframe = 
    liftM (toEnum.fromIntegral) $
    {#call web_frame_get_vertical_scrollbar_policy#} (toWebFrame webframe)

-- | You use the 'webFrameLoadRequest' method to initiate a request that creates a provisional data source. 
-- The provisional data source will transition to a committed data source once any data has been received. 
-- Use 'webFrameGetDataSource' to get the committed data source.
webFrameGetProvisionalDataSource :: 
   WebFrameClass self => self
 -> IO WebDataSource   
webFrameGetProvisionalDataSource webframe =
  makeNewGObject mkWebDataSource $ {#call web_frame_get_provisional_data_source#} (toWebFrame webframe)

-- | Returns the frame's security origin.
webFrameGetSecurityOrigin ::
   WebFrameClass self => self
 -> IO SecurityOrigin   
webFrameGetSecurityOrigin webframe = 
  makeNewGObject mkSecurityOrigin $ {#call web_frame_get_security_origin#} (toWebFrame webframe)

-- |Prints the given 'WebFrame'.
--
-- by presenting a print dialog to the user. 
webFramePrint:: 
    WebFrameClass self => self
 -> IO()
webFramePrint webframe = 
  {#call web_frame_print#} (toWebFrame webframe)