[Delete old web stuff which is no longer necessary
Neil Mitchell**20080820231111] {
hunk ./src/Web/HTML.hs 1
-{-# LINE 4 "HTML.hsx" #-}
-module Web.HTML
- (WebData(..), htmlFront, htmlError, htmlAnswers, innerNoResult)
- where
-{-# LINE 6 "HTML.hsx" #-}
-import Web.XML
-{-# LINE 7 "HTML.hsx" #-}
-import Hoogle.General
-{-# LINE 8 "HTML.hsx" #-}
-import General.CGI
-
-{-# LINE 11 "HTML.hsx" #-}
-data WebData = WebData{webSearch :: String, webPackage :: String,
- webLogo :: String}
-{-# LINE 16 "HTML.hsx" #-}
-doctype
- = ""
-{-# LINE 19 "HTML.hsx" #-}
-anyPage webData@WebData{webSearch = webSearch} body
- = doctype ++ "\n" ++ show html
- where {-# LINE 21 "HTML.hsx" #-}
- html
- = (genTag (Nothing, "html") []
- [toXMLs
- ((genTag (Nothing, "head") []
- [toXMLs
- ((genETag (Nothing, "meta")
- [toAttribute ("http-equiv" := "Content-Type"),
- toAttribute ("content" := "text/html; charset=iso-8859-1")])),
- toXMLs
- ((genTag (Nothing, "title") []
- [toXMLs (if null webSearch then "" else webSearch ++ " - "),
- toXMLs (pcdata "Hoogle")])),
- toXMLs
- ((genETag (Nothing, "link")
- [toAttribute ("type" := "text/css"),
- toAttribute ("rel" := "stylesheet"),
- toAttribute ("href" := "res/hoogle.css")])),
- toXMLs
- ((genTag (Nothing, "script")
- [toAttribute ("type" := "text/javascript"),
- toAttribute ("src" := "res/hoogle.js")]
- [toXMLs (pcdata " ")]))])),
- toXMLs
- ((genTag (Nothing, "body")
- [toAttribute ("onload" := "on_load()"),
- toAttribute
- ("id" := (if null webSearch then "front" else "answers"))]
- [toXMLs
- ((genTag (Nothing, "table") [toAttribute ("id" := "header")]
- [toXMLs
- ((genTag (Nothing, "tr") []
- [toXMLs
- ((genTag (Nothing, "td")
- [toAttribute ("style" := "text-align:left;")]
- [toXMLs
- ((genTag (Nothing, "a")
- [toAttribute
- ("href" := "http://www.haskell.org/")]
- [toXMLs (pcdata "haskell.org")]))])),
- toXMLs
- ((genTag (Nothing, "td")
- [toAttribute ("style" := "text-align:right;")]
- [toXMLs (rawXml ""),
- toXMLs
- ((genTag (Nothing, "a")
- [toAttribute
- ("href" := "javascript:addHoogle()")]
- [toXMLs (pcdata "Firefox plugin")])),
- toXMLs (pcdata " "),
- toXMLs (pcdata "|\n "),
- toXMLs (rawXml ""),
- toXMLs
- ((genTag (Nothing, "a")
- [toAttribute
- ("href" :=
- "http://www.haskell.org/haskellwiki/Hoogle/Tutorial")]
- [toXMLs (pcdata "Tutorial")])),
- toXMLs (pcdata " "),
- toXMLs (pcdata "|\n "),
- toXMLs
- ((genTag (Nothing, "a")
- [toAttribute
- ("href" :=
- "http://www.haskell.org/haskellwiki/Hoogle")]
- [toXMLs (pcdata "Manual")]))]))]))])),
- toXMLs (body),
- toXMLs
- ((genTag (Nothing, "p") [toAttribute ("id" := "footer")]
- [toXMLs (pcdata "© "),
- toXMLs
- ((genTag (Nothing, "a")
- [toAttribute ("href" := "http://www.cs.york.ac.uk/~ndm/")]
- [toXMLs (pcdata "Neil Mitchell")])),
- toXMLs (pcdata " "),
- toXMLs (pcdata "2004-2008\n ")]))]))])
-
-{-# LINE 60 "HTML.hsx" #-}
-searchPage :: (ToXMLs a) => WebData -> a -> String
-{-# LINE 61 "HTML.hsx" #-}
-searchPage
- webData@WebData{webPackage = webPackage, webLogo = webLogo} inner
- = anyPage webData
- (genTag (Nothing, "hsx") []
- [toXMLs
- ((genTag (Nothing, "div") [toAttribute ("id" := "logo")]
- [toXMLs
- (iff (not $ null webPackage) $
- (genETag (Nothing, "img")
- [toAttribute ("src" := ("res/" ++ webPackage ++ "_small.png")),
- toAttribute ("alt" := webPackage)])),
- toXMLs
- ((genTag (Nothing, "a") [toAttribute ("href" := ".")]
- [toXMLs
- ((genETag (Nothing, "img")
- [toAttribute ("src" := ("res/hoogle_" ++ webLogo ++ "_small.png")),
- toAttribute ("alt" := "Hoogle")]))]))])),
- toXMLs
- ((genTag (Nothing, "form")
- [toAttribute ("action" := "?"), toAttribute ("method" := "get")]
- [toXMLs
- ((genTag (Nothing, "div") []
- [toXMLs
- (iff (not $ null webPackage)
- (genETag (Nothing, "input")
- [toAttribute ("type" := "hidden"),
- toAttribute ("name" := "package"),
- toAttribute ("value" := webPackage)])),
- toXMLs
- (iff (webLogo /= "default")
- (genETag (Nothing, "input")
- [toAttribute ("name" := "q"), toAttribute ("type" := "hidden"),
- toAttribute ("value" := webLogo)])),
- toXMLs
- ((genETag (Nothing, "input")
- [toAttribute ("name" := "q"), toAttribute ("id" := "txt"),
- toAttribute ("type" := "text"),
- toAttribute ("style" := "width:300px;margin-right:5px;"),
- toAttribute ("value" := (escapeAttrib $ webSearch webData))])),
- toXMLs
- ((genETag (Nothing, "input")
- [toAttribute ("style" := "padding-left:15px;padding-right:15px;"),
- toAttribute ("type" := "submit"),
- toAttribute ("value" := "Search")]))]))])),
- toXMLs (inner)])
-
-{-# LINE 90 "HTML.hsx" #-}
-htmlError :: WebData -> String -> String
-{-# LINE 91 "HTML.hsx" #-}
-htmlError webData errmsg
- = searchPage webData $
- (genTag (Nothing, "hsx") []
- [toXMLs
- ((genTag (Nothing, "table") [toAttribute ("id" := "heading")]
- [toXMLs
- ((genTag (Nothing, "tr") []
- [toXMLs
- ((genTag (Nothing, "td") [] [toXMLs (pcdata "Invalid Search")])),
- toXMLs
- ((genTag (Nothing, "td") [toAttribute ("id" := "count")]
- [toXMLs (pcdata "No results found")]))]))])),
- toXMLs
- ((genTag (Nothing, "div") [toAttribute ("id" := "failure")]
- [toXMLs (pcdata "Error, your search was invalid:"),
- toXMLs ((genETag (Nothing, "br") [])), toXMLs (errmsg),
- toXMLs
- ((genTag (Nothing, "ul") []
- [toXMLs
- ((genTag (Nothing, "li") []
- [toXMLs
- (pcdata
- "This is probably a parse error, check for matching brackets etc.")]))]))]))])
-
-{-# LINE 111 "HTML.hsx" #-}
-innerNoResult :: String
-{-# LINE 112 "HTML.hsx" #-}
-innerNoResult
- = show $
- (genTag (Nothing, "div") [toAttribute ("id" := "failure")]
- [toXMLs (pcdata "Your search returned no results:\n "),
- toXMLs
- ((genTag (Nothing, "ul") []
- [toXMLs
- ((genTag (Nothing, "li") []
- [toXMLs
- (pcdata
- "Make sure you are using the search engine properly, it only searches for Haskell functions")])),
- toXMLs
- ((genTag (Nothing, "li") []
- [toXMLs
- (pcdata
- "Try a smaller substring, for example, if you searched for "),
- toXMLs ((genTag (Nothing, "tt") [] [toXMLs (pcdata "mapConcat")])),
- toXMLs (pcdata ", try searching for either "),
- toXMLs ((genTag (Nothing, "tt") [] [toXMLs (pcdata "map")])),
- toXMLs (pcdata " "), toXMLs (pcdata "or "),
- toXMLs ((genTag (Nothing, "tt") [] [toXMLs (pcdata "concat")])),
- toXMLs (pcdata " "), toXMLs (pcdata "individually.")]))]))])
-
-{-# LINE 123 "HTML.hsx" #-}
-htmlAnswers :: WebData -> String -> String
-{-# LINE 124 "HTML.hsx" #-}
-htmlAnswers webData inner = searchPage webData (rawXml inner)
-
-{-# LINE 131 "HTML.hsx" #-}
-htmlFront :: WebData -> String
-{-# LINE 132 "HTML.hsx" #-}
-htmlFront
- webData@WebData{webPackage = webPackage, webLogo = webLogo}
- = anyPage webData $
- (genTag (Nothing, "div")
- [toAttribute
- ("style" :=
- "width:100%;margin-top:30px;margin-bottom:30px;text-align:center;")]
- [toXMLs
- (iff (not $ null webPackage)
- (genETag (Nothing, "img")
- [toAttribute ("style" := "vertical-align:top;"),
- toAttribute ("src" := ("res/" ++ webPackage ++ "_large.png")),
- toAttribute ("alt" := webPackage)])),
- toXMLs
- ((genETag (Nothing, "img")
- [toAttribute ("style" := "vertical-align:top;"),
- toAttribute ("src" := ("res/hoogle_" ++ webLogo ++ "_large.png")),
- toAttribute ("alt" := "Hoogle")])),
- toXMLs
- ((genTag (Nothing, "sup")
- [toAttribute
- ("style" := "font-family:serif;font-weight:bold;font-size:16pt;")]
- [toXMLs (pcdata "3.1\n "),
- toXMLs
- ((genTag (Nothing, "span") [toAttribute ("style" := "color:#b00;")]
- [toXMLs (pcdata "[β]")]))])),
- toXMLs ((genETag (Nothing, "br") [])),
- toXMLs
- ((genTag (Nothing, "i") []
- [toXMLs (pcdata "The Haskell API Search Engine")])),
- toXMLs
- (iff (not $ null webPackage)
- (genTag (Nothing, "hsx") []
- [toXMLs (pcdata " "), toXMLs (pcdata "- "),
- toXMLs
- ((genTag (Nothing, "a")
- [toAttribute ("href" := "http://haskell.org/gtk2hs/")]
- [toXMLs (pcdata "Gtk2Hs")])),
- toXMLs (pcdata " "), toXMLs (pcdata "edition")])),
- toXMLs ((genETag (Nothing, "br") [])),
- toXMLs
- ((genTag (Nothing, "form")
- [toAttribute ("id" := "input"), toAttribute ("action" := ""),
- toAttribute ("method" := "get"),
- toAttribute
- ("style" := "text-align:center;padding-top:20px;display:block;")]
- [toXMLs
- ((genTag (Nothing, "div") []
- [toXMLs
- (iff (not $ null webPackage)
- (genETag (Nothing, "input")
- [toAttribute ("type" := "hidden"),
- toAttribute ("name" := "package"),
- toAttribute ("value" := webPackage)])),
- toXMLs
- (iff (webLogo /= "default")
- (genETag (Nothing, "input")
- [toAttribute ("name" := "q"), toAttribute ("type" := "hidden"),
- toAttribute ("value" := webLogo)])),
- toXMLs
- ((genETag (Nothing, "input")
- [toAttribute ("name" := "q"), toAttribute ("id" := "txt"),
- toAttribute ("type" := "text"),
- toAttribute ("style" := "width:300px;margin-right:5px;")])),
- toXMLs
- ((genETag (Nothing, "input")
- [toAttribute ("style" := "padding-left:15px;padding-right:15px;"),
- toAttribute ("type" := "submit"),
- toAttribute ("value" := "Search")]))]))])),
- toXMLs
- ((genTag (Nothing, "div")
- [toAttribute
- ("style" :=
- "margin:auto;margin-top:40px;padding:3px;width:300px;border:2px solid #cc0;background-color:#ffc;font-size:10pt;text-align:left;")]
- [toXMLs (pcdata "Example searches:"),
- toXMLs ((genETag (Nothing, "br") [])), toXMLs (pcdata " "),
- toXMLs
- ((genTag (Nothing, "a") [toAttribute ("href" := "?q=map")]
- [toXMLs (pcdata "map")])),
- toXMLs ((genETag (Nothing, "br") [])), toXMLs (pcdata " "),
- toXMLs
- ((genTag (Nothing, "a")
- [toAttribute
- ("href" := "?q=(a%20-%3E%20b)%20-%3E%20[a]%20-%3E%20[b]")]
- [toXMLs (pcdata "(a -> b) -> [a] -> [b]")])),
- toXMLs ((genETag (Nothing, "br") [])), toXMLs (pcdata " "),
- toXMLs
- ((genTag (Nothing, "a")
- [toAttribute ("href" := "?q=Ord%20a%20%3D%3E%20[a]%20-%3E%20[a]")]
- [toXMLs (pcdata "Ord a => [a] -> [a]")]))]))])
rmfile ./src/Web/HTML.hs
hunk ./src/Web/HTML.hsx 1
-
--- generate pages, using hsx preprocessor
--- http://www.cs.chalmers.se/~d00nibro/haskell-src-exts/
-module Web.HTML(WebData(..), htmlFront, htmlError, htmlAnswers, innerNoResult) where
-
-import Web.XML
-import Hoogle.General
-import General.CGI
-
-
-data WebData = WebData {webSearch :: String, webPackage :: String, webLogo :: String}
-
-
-
--- the individual elements that make up a web page:
-doctype = ""
-
--- null search means its the front page
-anyPage webData@WebData{webSearch=webSearch} body = doctype ++ "\n" ++ show html
- where
- html =
-
-
-
- <% if null webSearch then "" else webSearch ++ " - " %>Hoogle
-
-
-
-
-
-
-
-
- <% body %>
-
-
-
-
-
--- any page which is a search page
-searchPage :: ToXMLs a => WebData -> a -> String
-searchPage webData@WebData{webPackage=webPackage, webLogo=webLogo} inner = anyPage webData
-
-
- <% iff (not $ null webPackage) $
-
- %>
-
-
-
-
-
-
-
- <% inner %>
-
-
-
--- displayed if the user types an valid search, i.e. 3
-htmlError :: WebData -> String -> String
-htmlError webData errmsg = searchPage webData $
-
-
-
- Invalid Search
- No results found
-
-
-
-
- Error, your search was invalid:
- <% errmsg %>
-
- This is probably a parse error, check for matching brackets etc.
-
-
-
-
-
--- no results have been found, i.e. blah
-innerNoResult :: String
-innerNoResult = show $
-
- Your search returned no results:
-
- Make sure you are using the search engine properly, it only searches for Haskell functions
- Try a smaller substring, for example, if you searched for mapConcat , try searching for either map or concat individually.
-
-
-
-
-
-htmlAnswers :: WebData -> String -> String
-htmlAnswers webData inner = searchPage webData (rawXml inner)
-
-
-
-
-
--- displayed at the start, home page
-htmlFront :: WebData -> String
-htmlFront webData@WebData{webPackage=webPackage, webLogo=webLogo} = anyPage webData $
-
- <% iff (not $ null webPackage)
-
- %>
-
-
3.1
- [β]
-
-
The Haskell API Search Engine
- <% iff (not $ null webPackage)
-
- Gtk2Hs edition
- %>
-
-
-
-
-
rmfile ./src/Web/HTML.hsx
hunk ./src/Web/Lambdabot.hs 1
-
-module Web.Lambdabot(query) where
-
-import Data.List
-import Data.Char
-import System.Directory
-
-query :: String -> IO (Maybe String)
-query x = do d <- readDatabase
- return $ case filter ((==) (prepSearch x) . fst) d of
- (x:xs) -> Just $ formatRes (snd x)
- [] -> Nothing
-
-
-prepSearch = map toLower . reverse . dropWhile isSpace . reverse . dropWhile isSpace
-
-formatRes = unwords . map linky . words
-
-linky x | "http://" `isPrefixOf` x = "" ++ x ++ " "
- | otherwise = x
-
-
-readDatabase :: IO [(String, String)]
-readDatabase = do let lambdabotDatabase = "res/lambdabot.txt"
- b <- doesFileExist lambdabotDatabase
- if not b then return [] else do
- x <- readFile lambdabotDatabase
- return $ f (lines x)
- where
- f (key:val:xs) = (key,val) : f xs
- f _ = []
-
rmfile ./src/Web/Lambdabot.hs
hunk ./src/Web/Main.hs 1
-{- |
- The Web interface, expects to be run as a CGI script.
- This does not require Haskell CGI etc, it just dumps HTML to the console
--}
-
-module Web.Main where
-
-import Hoogle.Hoogle
-import Hoogle.TextUtil
-
-import General.CGI
-import Web.Lambdabot
-import Web.HTML
-
-import Data.Char
-import Data.List
-import Data.Maybe
-import System.Environment
-import System.Directory
-import System.Info
-import Control.Monad
-
-
-
----------------------------------------------------------------------
--- DEBUGGING SECTION
-
--- | Should the output be sent to the console and a file.
--- If true then both, the file is 'debugFile'.
--- Useful mainly for debugging.
---
-debugForce = False
-
--- | Defaults to True always in Hugs, since no one will
--- run the service for real via Hugs, but I debug it that way
-debugMode = debugForce || compilerName == "hugs"
-
--- | The file to output to if 'debugMode' is True
-debugFile = "../../web/temp.htm"
-
--- | Clear the debugging file
-debugBegin = when debugMode $ writeFile debugFile ""
-
--- | Write out a line, to console and optional to a debugging file
-putLine :: String -> IO ()
-putLine x = do putStrLn x
- when debugMode $ appendFile debugFile x
-
-
-
-
--- | The main function
-main :: IO ()
-main = do args <- cgiArgs
- putStr "Content-type: text/html\n\n"
- debugBegin
- appendFile "log.txt" (show args ++ "\n")
- let input = lookupDef "" "q" args
-
- let dat = WebData input
- (if ("package","gtk") `elem` args then "gtk" else "")
- (lookupDef "default" "logo" args)
-
- if null input then putLine $ htmlFront dat
- else do let p = hoogleParse input
- case hoogleParseError p of
- Just x -> putLine $ htmlError dat x
- Nothing -> showResults dat p args
-
-
-lookupDef :: Eq key => val -> key -> [(key, val)] -> val
-lookupDef def key list = case lookup key list of
- Nothing -> def
- Just x -> x
-
-lookupDefInt :: Eq key => Int -> key -> [(key, String)] -> Int
-lookupDefInt def key list = case lookup key list of
- Nothing -> def
- Just x -> case reads x of
- [(x,"")] -> x
- _ -> def
-
-
--- | Perform a search, dump the results using 'putLine'
-showResults :: WebData -> Search -> [(String, String)] -> IO ()
-showResults dat input args =
- do
- let useGtk = ("package","gtk") `elem` args
- res <- hoogleResults (if useGtk then "res/gtk.txt" else "res/hoogle.txt") input
- let lres = length res
- search = hoogleSearch input
- tSearch = showText search
- useres = take num $ drop start res
-
- let count =
- "" ++
- "Searched for " ++ showTags search ++
- " " ++
- (if lres == 0 then "No results found" else f lres) ++
- "
"
-
- let suggest = case hoogleSuggest True input of
- Nothing -> ""
- Just x -> "Hoogle says: " ++ showTags x ++ "
"
-
- lam <- Web.Lambdabot.query (lookupDef "" "q" args)
- let lambdabot = case lam of
- Nothing -> ""
- Just x -> "" ++
- "Lambdabot says: "
- ++ x ++ "
"
-
- let results = if null res then innerNoResult
- else "" ++ concatMap showResult useres ++ "
"
-
- let pageFlip = g lres
-
- let sher = if format == "sherlock" then sherlock useres else ""
-
- putLine $ htmlAnswers dat (count ++ suggest ++ lambdabot ++ results ++ pageFlip ++ sher)
- where
- start = lookupDefInt 0 "start" args
- num = lookupDefInt 25 "num" args
- format = lookupDef "" "format" args
- nostart = filter ((/=) "start" . fst) args
-
- showPrev len pos = if start <= 0 then "" else
- " "
-
- showNext len pos = if start+num >= len then "" else
- " "
-
-
- f len =
- showPrev len "top" ++
- "Results " ++ show (start+1) ++ " - " ++ show (min (start+num) len) ++ " of " ++ show len ++ " " ++
- showNext len "top"
-
- g len = if start == 0 && len <= num then "" else
- "" ++
- showPrev len "bot" ++
- concat (zipWith h [1..10] [0,num..len]) ++
- showNext len "bot" ++
- "
"
-
- h num start2 = " " ++ show num ++ " "
-
-
-
-sherlock :: [Result] -> String
-sherlock xs = "\n\n"
- where
- f res@(Result modu name typ _ _ _ _) =
- "- " ++ hoodoc res True ++
- "
" ++
- showTags name ++ " " ++
- "(" ++ showText modu ++ ") " ++
- " \n"
-
-
-
-showTags :: TagStr -> String
-showTags (Str x) = escapeHTML x
-showTags (Tag "b" x) = "" ++ showTags x ++ " "
-showTags (Tag "u" x) = "" ++ showTags x ++ " "
-showTags (Tag "a" x) = "" ++ showTags x ++ " "
- where
- url = if "http://" `isPrefixOf` txt then txt else "?q=" ++ escape txt
- txt = showText x
-
-showTags (Tag [n] x) | n >= '1' && n <= '6' =
- "" ++ showTags x ++ " "
-showTags (Tag n x) = showTags x
-showTags (Tags xs) = concatMap showTags xs
-
-
-showTagsLimit :: Int -> TagStr -> String
-showTagsLimit n x = if length s > n then take (n-2) s ++ ".." else s
- where
- s = showText x
-
-
-showResult :: Result -> String
-showResult res@(Result modu name typ _ _ _ _) =
- "" ++
- "" ++
- hoodoc res False ++ showTagsLimit 20 modu ++ "" ++
- (if null (showTags modu) then "" else ".") ++
- " "
- ++ openA ++ showTags name ++ "" ++
- " "
- ++ openA ++ ":: " ++ showTags typ ++ "" ++
- " " ++
- " \n"
- where
- openA = hoodoc res True
-
-
-hoodoc :: Result -> Bool -> String
-hoodoc res full = f $
- if not full
- then modu ++ "&mode=module"
- else if resultMode res == "module"
- then modu ++ (if null modu then "" else ".") ++ showText (resultName res) ++ "&mode=module"
- else showText (resultModule res) ++
- "&name=" ++ escape (showText (resultName res)) ++
- "&mode=" ++ resultMode res
- where
- modu = showText (resultModule res)
- f x = ""
-
-
-
--- | Read the hit count, increment it, return the new value.
--- Hit count is stored in hits.txt
-hitCount :: IO Integer
-hitCount = do x <- readHitCount
- -- HUGS SCREWS THIS UP WITHOUT `seq`
- -- this should not be needed, but it is
- -- (we think)
- x `seq` writeHitCount (x+1)
- return (x+1)
- where
- hitFile = "hits.txt"
-
- readHitCount :: IO Integer
- readHitCount =
- do exists <- doesFileExist hitFile
- if exists
- then do src <- readFile hitFile
- return (parseHitCount src)
- else return 0
-
- writeHitCount :: Integer -> IO ()
- writeHitCount x = writeFile hitFile (show x)
-
- parseHitCount = read . head . lines
rmfile ./src/Web/Main.hs
hunk ./src/Web/XML.hs 1
-{-# OPTIONS_GHC -fglasgow-exts #-}
-
-module Web.XML where
-
-import General.CGI
-
--- the data
-
-data XML = Tag String [Attribute] XML
- | PCData String
- | RawData String
- | XmlList [XML]
-
-data Pair a b = a := b
-
-data Attribute = Attribute String String
-
-
--- the generators
-
-a <+> b = XmlList [a,b]
-
-genTag :: (Maybe String, String) -> [Attribute] -> [XML] -> XML
-genTag (a,b) c d = Tag b c (XmlList d)
-
-toAttribute :: Pair String String -> Attribute
-toAttribute (a := b) = Attribute a b
-
-pcdata :: String -> XML
-pcdata x = PCData x
-
-genETag :: (Maybe String, String) -> [Attribute] -> XML
-genETag a b = genTag a b []
-
-rawXml x = RawData x
-
-class ToXMLs a where
- toXMLs :: a -> XML
-
-instance ToXMLs XML where
- toXMLs x = x
-
-instance ToXMLs String where
- toXMLs x = PCData $ escapeHTML x
-
-instance ToXMLs a => ToXMLs (Maybe a) where
- toXMLs Nothing = XmlList []
- toXMLs (Just x) = toXMLs x
-
-
--- the show
-
-instance Show XML where
- show (Tag "hsx" [] inner) = show inner
- show (Tag name attr inner) = "<" ++ name ++ concatMap ((' ':) . show) attr ++ ">" ++
- show inner ++
- "" ++ name ++ ">"
- show (PCData s) = s
- show (XmlList xs) = concatMap show xs
- show (RawData x) = x
-
-instance Show Attribute where
- -- should really be escapeAttrib, but this destroys
- -- the URL's from the results, should fix that!
- show (Attribute name value) = name ++ "=\"" ++ value ++ "\""
-
rmfile ./src/Web/XML.hs
hunk ./src/Web/res/error.inc 1
-
-
- Invalid Search
- No results found
-
-
-
-
- Error, your search was invalid:
- $
-
- This is probably a parse error, check for matching brackets etc.
-
-
rmfile ./src/Web/res/error.inc
hunk ./src/Web/res/front.inc 1
-
-
-
-
- Hoogle
-
-
-
-
-
-
-
-
-
-
-
-
3.1
- [β]
-
-
The Haskell API Search Engine
-
-
-
-
-
-
- "Roses are red. Violets are blue. Google rocks. Homage to you."
-
-
-
-
-
-
rmfile ./src/Web/res/front.inc
hunk ./src/Web/res/front_gtk.inc 1
-
-
-
-
- Hoogle
-
-
-
-
-
-
-
-
-
-
-
-
-
-
3
- [β]
-
-
-
The Haskell API Search Engine -
Gtk2Hs edition
-
-
-
-
-
-
- "Roses are red. Violets are blue. Google rocks. Homage to you."
-
-
-
-
-
-
rmfile ./src/Web/res/front_gtk.inc
hunk ./src/Web/res/gtk.txt 1
--- Hoogle documentation, generated by Haddock
--- See Hoogle, http://www.haskell.org/hoogle/
-
-module System.Glib.Types
-newtype GObject
-GObject :: ForeignPtr GObject -> GObject
-instance GObjectClass GObject
-class GObjectClass o
-instance GObjectClass AboutDialog
-instance GObjectClass AccelGroup
-instance GObjectClass AccelLabel
-instance GObjectClass AccelMap
-instance GObjectClass Action
-instance GObjectClass ActionGroup
-instance GObjectClass Adjustment
-instance GObjectClass Alignment
-instance GObjectClass Arrow
-instance GObjectClass AspectFrame
-instance GObjectClass Bin
-instance GObjectClass Box
-instance GObjectClass Button
-instance GObjectClass ButtonBox
-instance GObjectClass CList
-instance GObjectClass CTree
-instance GObjectClass Calendar
-instance GObjectClass CellRenderer
-instance GObjectClass CellRendererPixbuf
-instance GObjectClass CellRendererText
-instance GObjectClass CellRendererToggle
-instance GObjectClass CellView
-instance GObjectClass CheckButton
-instance GObjectClass CheckMenuItem
-instance GObjectClass Clipboard
-instance GObjectClass ColorButton
-instance GObjectClass ColorSelection
-instance GObjectClass ColorSelectionDialog
-instance GObjectClass Colormap
-instance GObjectClass Combo
-instance GObjectClass ComboBox
-instance GObjectClass ComboBoxEntry
-instance GObjectClass Container
-instance GObjectClass Curve
-instance GObjectClass Dialog
-instance GObjectClass Display
-instance GObjectClass DragContext
-instance GObjectClass DrawWindow
-instance GObjectClass Drawable
-instance GObjectClass DrawingArea
-instance GObjectClass Editable
-instance GObjectClass Entry
-instance GObjectClass EntryCompletion
-instance GObjectClass EventBox
-instance GObjectClass Expander
-instance GObjectClass FileChooser
-instance GObjectClass FileChooserButton
-instance GObjectClass FileChooserDialog
-instance GObjectClass FileChooserWidget
-instance GObjectClass FileFilter
-instance GObjectClass FileSelection
-instance GObjectClass Fixed
-instance GObjectClass Font
-instance GObjectClass FontButton
-instance GObjectClass FontFace
-instance GObjectClass FontFamily
-instance GObjectClass FontMap
-instance GObjectClass FontSelection
-instance GObjectClass FontSelectionDialog
-instance GObjectClass FontSet
-instance GObjectClass Frame
-instance GObjectClass GC
-instance GObjectClass GConf
-instance GObjectClass GObject
-instance GObjectClass GammaCurve
-instance GObjectClass GladeXML
-instance GObjectClass HBox
-instance GObjectClass HButtonBox
-instance GObjectClass HPaned
-instance GObjectClass HRuler
-instance GObjectClass HScale
-instance GObjectClass HScrollbar
-instance GObjectClass HSeparator
-instance GObjectClass HandleBox
-instance GObjectClass IMContext
-instance GObjectClass IMMulticontext
-instance GObjectClass IconFactory
-instance GObjectClass IconView
-instance GObjectClass Image
-instance GObjectClass ImageMenuItem
-instance GObjectClass InputDialog
-instance GObjectClass Invisible
-instance GObjectClass Item
-instance GObjectClass ItemFactory
-instance GObjectClass Label
-instance GObjectClass Layout
-instance GObjectClass List
-instance GObjectClass ListItem
-instance GObjectClass ListStore
-instance GObjectClass Menu
-instance GObjectClass MenuBar
-instance GObjectClass MenuItem
-instance GObjectClass MenuShell
-instance GObjectClass MenuToolButton
-instance GObjectClass MessageDialog
-instance GObjectClass Misc
-instance GObjectClass MozEmbed
-instance GObjectClass Notebook
-instance GObjectClass Object
-instance GObjectClass OptionMenu
-instance GObjectClass Paned
-instance GObjectClass PangoContext
-instance GObjectClass PangoLayoutRaw
-instance GObjectClass Pixbuf
-instance GObjectClass Pixmap
-instance GObjectClass Plug
-instance GObjectClass Preview
-instance GObjectClass ProgressBar
-instance GObjectClass RadioAction
-instance GObjectClass RadioButton
-instance GObjectClass RadioMenuItem
-instance GObjectClass RadioToolButton
-instance GObjectClass Range
-instance GObjectClass RcStyle
-instance GObjectClass Ruler
-instance GObjectClass Scale
-instance GObjectClass Screen
-instance GObjectClass Scrollbar
-instance GObjectClass ScrolledWindow
-instance GObjectClass Separator
-instance GObjectClass SeparatorMenuItem
-instance GObjectClass SeparatorToolItem
-instance GObjectClass Settings
-instance GObjectClass SizeGroup
-instance GObjectClass Socket
-instance GObjectClass SourceBuffer
-instance GObjectClass SourceLanguage
-instance GObjectClass SourceLanguagesManager
-instance GObjectClass SourceMarker
-instance GObjectClass SourceStyleScheme
-instance GObjectClass SourceTag
-instance GObjectClass SourceTagTable
-instance GObjectClass SourceView
-instance GObjectClass SpinButton
-instance GObjectClass Statusbar
-instance GObjectClass Style
-instance GObjectClass Table
-instance GObjectClass TearoffMenuItem
-instance GObjectClass TextBuffer
-instance GObjectClass TextChildAnchor
-instance GObjectClass TextMark
-instance GObjectClass TextTag
-instance GObjectClass TextTagTable
-instance GObjectClass TextView
-instance GObjectClass TipsQuery
-instance GObjectClass ToggleAction
-instance GObjectClass ToggleButton
-instance GObjectClass ToggleToolButton
-instance GObjectClass ToolButton
-instance GObjectClass ToolItem
-instance GObjectClass Toolbar
-instance GObjectClass Tooltips
-instance GObjectClass TreeModel
-instance GObjectClass TreeModelSort
-instance GObjectClass TreeSelection
-instance GObjectClass TreeStore
-instance GObjectClass TreeView
-instance GObjectClass TreeViewColumn
-instance GObjectClass UIManager
-instance GObjectClass VBox
-instance GObjectClass VButtonBox
-instance GObjectClass VPaned
-instance GObjectClass VRuler
-instance GObjectClass VScale
-instance GObjectClass VScrollbar
-instance GObjectClass VSeparator
-instance GObjectClass Viewport
-instance GObjectClass Widget
-instance GObjectClass Window
-instance GObjectClass WindowGroup
-toGObject :: GObjectClass o => o -> GObject
-fromGObject :: GObjectClass o => GObject -> o
-castToGObject :: GObjectClass obj => obj -> obj
-
-module System.Glib.GList
-type GList = Ptr ()
-readGList :: GList -> IO [Ptr a]
-fromGList :: GList -> IO [Ptr a]
-toGList :: [Ptr a] -> IO GList
-type GSList = Ptr ()
-readGSList :: GSList -> IO [Ptr a]
-fromGSList :: GSList -> IO [Ptr a]
-fromGSListRev :: GSList -> IO [Ptr a]
-toGSList :: [Ptr a] -> IO GSList
-
-module System.Glib.Flags
-class (Enum a, Bounded a) => Flags a
-instance Flags AccelFlags
-instance Flags AttachOptions
-instance Flags CalendarDisplayOptions
-instance Flags EventMask
-instance Flags ExtensionMode
-instance Flags FileFilterFlags
-instance Flags FontMask
-instance Flags IOCondition
-instance Flags InputCondition
-instance Flags Modifier
-instance Flags SourceSearchFlags
-instance Flags TextSearchFlags
-instance Flags TreeModelFlags
-instance Flags UIManagerItemType
-instance Flags WindowState
-fromFlags :: Flags a => [a] -> Int
-toFlags :: Flags a => Int -> [a]
-
-module System.Glib.FFI
-with :: Storable a => a -> (Ptr a -> IO b) -> IO b
-nullForeignPtr :: ForeignPtr a
-maybeNull :: (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
-withForeignPtrs :: [ForeignPtr a] -> ([Ptr a] -> IO b) -> IO b
-withArrayLen :: Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
-
-module System.Glib.GType
-type GType = CULong
-typeInstanceIsA :: Ptr () -> GType -> Bool
-
-module System.Glib.GTypeConstants
-invalid :: GType
-uint :: GType
-int :: GType
-uchar :: GType
-char :: GType
-bool :: GType
-enum :: GType
-flags :: GType
-pointer :: GType
-float :: GType
-double :: GType
-string :: GType
-object :: GType
-boxed :: GType
-
-module System.Glib.GValue
-newtype GValue
-GValue :: Ptr GValue -> GValue
-valueInit :: GValue -> GType -> IO ()
-valueUnset :: GValue -> IO ()
-valueGetType :: GValue -> IO GType
-allocaGValue :: (GValue -> IO b) -> IO b
-
-module System.Glib.GParameter
-newtype GParameter
-GParameter :: (String, GValue) -> GParameter
-instance Storable GParameter
-
-module System.Glib.GObject
-objectNew :: GType -> [(String, GValue)] -> IO (Ptr GObject)
-objectRef :: GObjectClass obj => Ptr obj -> IO ()
-objectUnref :: Ptr a -> FinalizerPtr a
-makeNewGObject :: GObjectClass obj => (ForeignPtr obj -> obj) -> IO (Ptr obj) -> IO obj
-type DestroyNotify = FunPtr (Ptr () -> IO ())
-mkFunPtrDestroyNotify :: FunPtr a -> IO DestroyNotify
-type GWeakNotify = FunPtr (Ptr () -> Ptr GObject -> IO ())
-objectWeakref :: GObjectClass o => o -> IO () -> IO GWeakNotify
-objectWeakunref :: GObjectClass o => o -> GWeakNotify -> IO ()
-
-module System.Glib.MainLoop
-type HandlerId = CUInt
-timeoutAdd :: IO Bool -> Int -> IO HandlerId
-timeoutAddFull :: IO Bool -> Priority -> Int -> IO HandlerId
-timeoutRemove :: HandlerId -> IO ()
-idleAdd :: IO Bool -> Priority -> IO HandlerId
-idleRemove :: HandlerId -> IO ()
-data IOCondition
-instance Bounded IOCondition
-instance Enum IOCondition
-instance Eq IOCondition
-instance Flags IOCondition
-inputAdd :: FD -> [IOCondition] -> Priority -> IO Bool -> IO HandlerId
-inputRemove :: HandlerId -> IO ()
-type Priority = Int
-priorityLow :: Int
-priorityDefaultIdle :: Int
-priorityHighIdle :: Int
-priorityDefault :: Int
-priorityHigh :: Int
-
-module System.Glib.UTFString
-withUTFString :: String -> (CString -> IO a) -> IO a
-withUTFStringLen :: String -> (CStringLen -> IO a) -> IO a
-newUTFString :: String -> IO CString
-newUTFStringLen :: String -> IO CStringLen
-peekUTFString :: CString -> IO String
-peekUTFStringLen :: CStringLen -> IO String
-readUTFString :: CString -> IO String
-readCString :: CString -> IO String
-withUTFStrings :: [String] -> ([CString] -> IO a) -> IO a
-withUTFStringArray :: [String] -> (Ptr CString -> IO a) -> IO a
-withUTFStringArray0 :: [String] -> (Ptr CString -> IO a) -> IO a
-peekUTFStringArray :: Int -> Ptr CString -> IO [String]
-peekUTFStringArray0 :: Ptr CString -> IO [String]
-data UTFCorrection
-instance Show UTFCorrection
-genUTFOfs :: String -> UTFCorrection
-ofsToUTF :: Int -> UTFCorrection -> Int
-ofsFromUTF :: Int -> UTFCorrection -> Int
-
-module System.Glib.GError
-data GError
-GError :: GErrorDomain -> GErrorCode -> GErrorMessage -> GError
-instance Storable GError
-instance Typeable GError
-type GErrorDomain = GQuark
-type GErrorCode = Int
-type GErrorMessage = String
-catchGError :: IO a -> (GError -> IO a) -> IO a
-catchGErrorJust :: GErrorClass err => err -> IO a -> (GErrorMessage -> IO a) -> IO a
-catchGErrorJustDomain :: GErrorClass err => IO a -> (err -> GErrorMessage -> IO a) -> IO a
-handleGError :: (GError -> IO a) -> IO a -> IO a
-handleGErrorJust :: GErrorClass err => err -> (GErrorMessage -> IO a) -> IO a -> IO a
-handleGErrorJustDomain :: GErrorClass err => (err -> GErrorMessage -> IO a) -> IO a -> IO a
-failOnGError :: IO a -> IO a
-throwGError :: GError -> IO a
-class Enum err => GErrorClass err
-gerrorDomain :: GErrorClass err => err -> GErrorDomain
-instance GErrorClass FileChooserError
-instance GErrorClass GConfError
-instance GErrorClass PixbufError
-propagateGError :: (Ptr (Ptr ()) -> IO a) -> IO a
-checkGError :: (Ptr (Ptr ()) -> IO a) -> (GError -> IO a) -> IO a
-checkGErrorWithCont :: (Ptr (Ptr ()) -> IO b) -> (GError -> IO a) -> (b -> IO a) -> IO a
-
-module System.Glib.GValueTypes
-valueSetUInt :: GValue -> Word -> IO ()
-valueGetUInt :: GValue -> IO Word
-valueSetInt :: GValue -> Int -> IO ()
-valueGetInt :: GValue -> IO Int
-valueSetBool :: GValue -> Bool -> IO ()
-valueGetBool :: GValue -> IO Bool
-valueSetPointer :: GValue -> Ptr () -> IO ()
-valueGetPointer :: GValue -> IO (Ptr ())
-valueSetFloat :: GValue -> Float -> IO ()
-valueGetFloat :: GValue -> IO Float
-valueSetDouble :: GValue -> Double -> IO ()
-valueGetDouble :: GValue -> IO Double
-valueSetEnum :: Enum enum => GValue -> enum -> IO ()
-valueGetEnum :: Enum enum => GValue -> IO enum
-valueSetFlags :: Flags flag => GValue -> [flag] -> IO ()
-valueGetFlags :: Flags flag => GValue -> IO [flag]
-valueSetString :: GValue -> String -> IO ()
-valueGetString :: GValue -> IO String
-valueSetMaybeString :: GValue -> Maybe String -> IO ()
-valueGetMaybeString :: GValue -> IO (Maybe String)
-valueSetGObject :: GObjectClass gobj => GValue -> gobj -> IO ()
-valueGetGObject :: GObjectClass gobj => GValue -> IO gobj
-
-module System.Glib.Signals
-data ConnectId o
-ConnectId :: CULong -> o -> ConnectId o
-disconnect :: GObjectClass obj => ConnectId obj -> IO ()
-
-module System.Gnome.GConf.GConfValue
-class GConfValueClass value => GConfPrimitiveValueClass value
-instance GConfPrimitiveValueClass Bool
-instance GConfPrimitiveValueClass Double
-instance GConfPrimitiveValueClass Int
-instance GConfPrimitiveValueClass String
-class GConfValueClass value
-marshalFromGConfValue :: GConfValueClass value => GConfValue -> IO value
-marshalToGConfValue :: GConfValueClass value => value -> IO GConfValue
-instance GConfValueClass Bool
-instance GConfValueClass Double
-instance GConfValueClass GConfValueDyn
-instance GConfValueClass Int
-instance GConfValueClass String
-instance (GConfPrimitiveValueClass a, GConfPrimitiveValueClass b) => GConfValueClass (a, b)
-instance GConfValueClass value => GConfValueClass Maybe value
-instance GConfPrimitiveValueClass a => GConfValueClass [a]
-marshalFromGConfValue :: GConfValueClass value => GConfValue -> IO value
-marshalToGConfValue :: GConfValueClass value => value -> IO GConfValue
-newtype GConfValue
-GConfValue :: Ptr GConfValue -> GConfValue
-data GConfValueDyn
-GConfValueString :: String -> GConfValueDyn
-GConfValueInt :: Int -> GConfValueDyn
-GConfValueFloat :: Double -> GConfValueDyn
-GConfValueBool :: Bool -> GConfValueDyn
-GConfValueSchema :: GConfValueDyn
-GConfValueList :: [GConfValueDyn] -> GConfValueDyn
-GConfValuePair :: (GConfValueDyn, GConfValueDyn) -> GConfValueDyn
-instance GConfValueClass GConfValueDyn
-
-module System.Gnome.GConf.GConfClient
-data GConf
-instance GConfClass GConf
-instance GObjectClass GConf
-data GConfPreloadType
-instance Enum GConfPreloadType
-data GConfError
-instance Enum GConfError
-instance GErrorClass GConfError
-gconfGetDefault :: IO GConf
-gconfAddDir :: GConf -> String -> IO ()
-gconfRemoveDir :: GConf -> String -> IO ()
-gconfNotifyAdd :: GConfValueClass value => GConf -> String -> (String -> value -> IO ()) -> IO GConfConnectId
-gconfNotifyRemove :: GConf -> GConfConnectId -> IO ()
-onValueChanged :: GConf -> (String -> Maybe GConfValueDyn -> IO ()) -> IO (ConnectId GConf)
-afterValueChanged :: GConf -> (String -> Maybe GConfValueDyn -> IO ()) -> IO (ConnectId GConf)
-gconfGet :: GConfValueClass value => GConf -> String -> IO value
-gconfSet :: GConfValueClass value => GConf -> String -> value -> IO ()
-gconfGetWithoutDefault :: GConfValueClass value => GConf -> String -> IO value
-gconfGetDefaultFromSchema :: GConfValueClass value => GConf -> String -> IO value
-gconfUnset :: GConf -> String -> IO ()
-gconfClearCache :: GConf -> IO ()
-gconfPreload :: GConf -> String -> GConfPreloadType -> IO ()
-gconfSuggestSync :: GConf -> IO ()
-gconfAllEntries :: GConf -> String -> IO [(String, GConfValueDyn)]
-gconfAllDirs :: GConf -> String -> IO [String]
-gconfDirExists :: GConf -> String -> IO Bool
-class GConfValueClass value
-instance GConfValueClass Bool
-instance GConfValueClass Double
-instance GConfValueClass GConfValueDyn
-instance GConfValueClass Int
-instance GConfValueClass String
-instance (GConfPrimitiveValueClass a, GConfPrimitiveValueClass b) => GConfValueClass (a, b)
-instance GConfValueClass value => GConfValueClass Maybe value
-instance GConfPrimitiveValueClass a => GConfValueClass [a]
-class GConfValueClass value => GConfPrimitiveValueClass value
-instance GConfPrimitiveValueClass Bool
-instance GConfPrimitiveValueClass Double
-instance GConfPrimitiveValueClass Int
-instance GConfPrimitiveValueClass String
-data GConfValue
-data GConfValueDyn
-GConfValueString :: String -> GConfValueDyn
-GConfValueInt :: Int -> GConfValueDyn
-GConfValueFloat :: Double -> GConfValueDyn
-GConfValueBool :: Bool -> GConfValueDyn
-GConfValueSchema :: GConfValueDyn
-GConfValueList :: [GConfValueDyn] -> GConfValueDyn
-GConfValuePair :: (GConfValueDyn, GConfValueDyn) -> GConfValueDyn
-instance GConfValueClass GConfValueDyn
-
-module System.Gnome.GConf
-
-module System.Glib.Attributes
-type Attr o a = ReadWriteAttr o a a
-type ReadAttr o a = ReadWriteAttr o a ()
-type WriteAttr o b = ReadWriteAttr o () b
-data ReadWriteAttr o a b
-data AttrOp o
-:= :: ReadWriteAttr o a b -> b -> AttrOp o
-:~ :: ReadWriteAttr o a b -> (a -> b) -> AttrOp o
-:=> :: ReadWriteAttr o a b -> IO b -> AttrOp o
-:~> :: ReadWriteAttr o a b -> (a -> IO b) -> AttrOp o
-::= :: ReadWriteAttr o a b -> (o -> b) -> AttrOp o
-::~ :: ReadWriteAttr o a b -> (o -> a -> b) -> AttrOp o
-get :: o -> ReadWriteAttr o a b -> IO a
-set :: o -> [AttrOp o] -> IO ()
-newAttr :: (o -> IO a) -> (o -> b -> IO ()) -> ReadWriteAttr o a b
-readAttr :: (o -> IO a) -> ReadAttr o a
-writeAttr :: (o -> b -> IO ()) -> WriteAttr o b
-
-module System.Glib.Properties
-objectSetPropertyInt :: GObjectClass gobj => String -> gobj -> Int -> IO ()
-objectGetPropertyInt :: GObjectClass gobj => String -> gobj -> IO Int
-objectSetPropertyUInt :: GObjectClass gobj => String -> gobj -> Int -> IO ()
-objectGetPropertyUInt :: GObjectClass gobj => String -> gobj -> IO Int
-objectSetPropertyBool :: GObjectClass gobj => String -> gobj -> Bool -> IO ()
-objectGetPropertyBool :: GObjectClass gobj => String -> gobj -> IO Bool
-objectSetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> enum -> IO ()
-objectGetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> IO enum
-objectSetPropertyFlags :: (GObjectClass gobj, Flags flag) => String -> gobj -> [flag] -> IO ()
-objectGetPropertyFlags :: (GObjectClass gobj, Flags flag) => String -> gobj -> IO [flag]
-objectSetPropertyFloat :: GObjectClass gobj => String -> gobj -> Float -> IO ()
-objectGetPropertyFloat :: GObjectClass gobj => String -> gobj -> IO Float
-objectSetPropertyDouble :: GObjectClass gobj => String -> gobj -> Double -> IO ()
-objectGetPropertyDouble :: GObjectClass gobj => String -> gobj -> IO Double
-objectSetPropertyString :: GObjectClass gobj => String -> gobj -> String -> IO ()
-objectGetPropertyString :: GObjectClass gobj => String -> gobj -> IO String
-objectSetPropertyMaybeString :: GObjectClass gobj => String -> gobj -> Maybe String -> IO ()
-objectGetPropertyMaybeString :: GObjectClass gobj => String -> gobj -> IO (Maybe String)
-objectSetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> gobj' -> IO ()
-objectGetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> IO gobj'
-objectSetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> a -> IO ()) -> String -> gobj -> a -> IO ()
-objectGetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> IO a) -> String -> gobj -> IO a
-newAttrFromIntProperty :: GObjectClass gobj => String -> Attr gobj Int
-readAttrFromIntProperty :: GObjectClass gobj => String -> ReadAttr gobj Int
-newAttrFromUIntProperty :: GObjectClass gobj => String -> Attr gobj Int
-writeAttrFromUIntProperty :: GObjectClass gobj => String -> WriteAttr gobj Int
-newAttrFromBoolProperty :: GObjectClass gobj => String -> Attr gobj Bool
-newAttrFromFloatProperty :: GObjectClass gobj => String -> Attr gobj Float
-newAttrFromDoubleProperty :: GObjectClass gobj => String -> Attr gobj Double
-newAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> Attr gobj enum
-readAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> ReadAttr gobj enum
-newAttrFromFlagsProperty :: (GObjectClass gobj, Flags flag) => String -> Attr gobj [flag]
-newAttrFromStringProperty :: GObjectClass gobj => String -> Attr gobj String
-readAttrFromStringProperty :: GObjectClass gobj => String -> ReadAttr gobj String
-writeAttrFromStringProperty :: GObjectClass gobj => String -> WriteAttr gobj String
-newAttrFromMaybeStringProperty :: GObjectClass gobj => String -> Attr gobj (Maybe String)
-newAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj', GObjectClass gobj'') => String -> GType -> ReadWriteAttr gobj gobj' gobj''
-writeAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> WriteAttr gobj gobj'
-
-module System.Glib.StoreValue
-data TMType
-TMinvalid :: TMType
-TMuint :: TMType
-TMint :: TMType
-TMboolean :: TMType
-TMenum :: TMType
-TMflags :: TMType
-TMfloat :: TMType
-TMdouble :: TMType
-TMstring :: TMType
-TMobject :: TMType
-instance Enum TMType
-data GenericValue
-GVuint :: Word -> GenericValue
-GVint :: Int -> GenericValue
-GVboolean :: Bool -> GenericValue
-GVenum :: Int -> GenericValue
-GVflags :: Int -> GenericValue
-GVfloat :: Float -> GenericValue
-GVdouble :: Double -> GenericValue
-GVstring :: Maybe String -> GenericValue
-GVobject :: GObject -> GenericValue
-valueSetGenericValue :: GValue -> GenericValue -> IO ()
-valueGetGenericValue :: GValue -> IO GenericValue
-
-module System.Glib
-
-module Graphics.UI.Gtk.Windows.WindowGroup
-data WindowGroup
-instance GObjectClass WindowGroup
-instance WindowGroupClass WindowGroup
-class GObjectClass o => WindowGroupClass o
-instance WindowGroupClass WindowGroup
-castToWindowGroup :: GObjectClass obj => obj -> WindowGroup
-toWindowGroup :: WindowGroupClass o => o -> WindowGroup
-windowGroupNew :: IO WindowGroup
-windowGroupAddWindow :: (WindowGroupClass self, WindowClass window) => self -> window -> IO ()
-windowGroupRemoveWindow :: (WindowGroupClass self, WindowClass window) => self -> window -> IO ()
-
-module Graphics.UI.Gtk.TreeList.CellRenderer
-data CellRenderer
-instance CellRendererClass CellRenderer
-instance GObjectClass CellRenderer
-instance ObjectClass CellRenderer
-class ObjectClass o => CellRendererClass o
-instance CellRendererClass CellRenderer
-instance CellRendererClass CellRendererPixbuf
-instance CellRendererClass CellRendererText
-instance CellRendererClass CellRendererToggle
-castToCellRenderer :: GObjectClass obj => obj -> CellRenderer
-toCellRenderer :: CellRendererClass o => o -> CellRenderer
-data Attribute cr a
-Attribute :: [String] -> [TMType] -> (a -> IO [GenericValue]) -> ([GenericValue] -> IO a) -> Attribute cr a
-cellRendererSet :: CellRendererClass cr => cr -> Attribute cr val -> val -> IO ()
-cellRendererGet :: CellRendererClass cr => cr -> Attribute cr val -> IO val
-
-module Graphics.UI.Gtk.SourceView.SourceMarker
-data SourceMarker
-instance GObjectClass SourceMarker
-instance SourceMarkerClass SourceMarker
-instance TextMarkClass SourceMarker
-castToSourceMarker :: GObjectClass obj => obj -> SourceMarker
-sourceMarkerSetMarkerType :: SourceMarker -> String -> IO ()
-sourceMarkerGetMarkerType :: SourceMarker -> IO String
-sourceMarkerGetLine :: SourceMarker -> IO Int
-sourceMarkerGetName :: SourceMarker -> IO String
-sourceMarkerGetBuffer :: SourceMarker -> IO SourceBuffer
-sourceMarkerNext :: SourceMarker -> IO SourceMarker
-sourceMarkerPrev :: SourceMarker -> IO SourceMarker
-
-module Graphics.UI.Gtk.SourceView.SourceLanguagesManager
-data SourceLanguagesManager
-instance GObjectClass SourceLanguagesManager
-instance SourceLanguagesManagerClass SourceLanguagesManager
-castToSourceLanguagesManager :: GObjectClass obj => obj -> SourceLanguagesManager
-sourceLanguagesManagerNew :: IO SourceLanguagesManager
-sourceLanguagesManagerGetAvailableLanguages :: SourceLanguagesManager -> IO [SourceLanguage]
-sourceLanguagesManagerGetLanguageFromMimeType :: SourceLanguagesManager -> String -> IO (Maybe SourceLanguage)
-sourceLanguagesManagerGetLangFilesDirs :: SourceLanguagesManager -> IO [FilePath]
-
-module Graphics.UI.Gtk.Pango.Enums
-data FontStyle
-StyleNormal :: FontStyle
-StyleOblique :: FontStyle
-StyleItalic :: FontStyle
-instance Enum FontStyle
-instance Eq FontStyle
-instance Show FontStyle
-data Weight
-WeightUltralight :: Weight
-WeightLight :: Weight
-WeightNormal :: Weight
-WeightSemibold :: Weight
-WeightBold :: Weight
-WeightUltrabold :: Weight
-WeightHeavy :: Weight
-instance Enum Weight
-instance Eq Weight
-instance Show Weight
-data Variant
-VariantNormal :: Variant
-VariantSmallCaps :: Variant
-instance Enum Variant
-instance Eq Variant
-instance Show Variant
-data Stretch
-StretchUltraCondensed :: Stretch
-StretchExtraCondensed :: Stretch
-StretchCondensed :: Stretch
-StretchSemiCondensed :: Stretch
-StretchNormal :: Stretch
-StretchSemiExpanded :: Stretch
-StretchExpanded :: Stretch
-StretchExtraExpanded :: Stretch
-StretchUltraExpanded :: Stretch
-instance Enum Stretch
-instance Eq Stretch
-instance Show Stretch
-data Underline
-UnderlineNone :: Underline
-UnderlineSingle :: Underline
-UnderlineDouble :: Underline
-UnderlineLow :: Underline
-UnderlineError :: Underline
-instance Enum Underline
-instance Eq Underline
-instance Show Underline
-data EllipsizeMode
-EllipsizeNone :: EllipsizeMode
-EllipsizeStart :: EllipsizeMode
-EllipsizeMiddle :: EllipsizeMode
-EllipsizeEnd :: EllipsizeMode
-instance Enum EllipsizeMode
-instance Eq EllipsizeMode
-
-module Graphics.UI.Gtk.Multiline.TextTagTable
-data TextTagTable
-instance GObjectClass TextTagTable
-instance TextTagTableClass TextTagTable
-class GObjectClass o => TextTagTableClass o
-instance TextTagTableClass SourceTagTable
-instance TextTagTableClass TextTagTable
-castToTextTagTable :: GObjectClass obj => obj -> TextTagTable
-toTextTagTable :: TextTagTableClass o => o -> TextTagTable
-textTagTableNew :: IO TextTagTable
-textTagTableAdd :: (TextTagTableClass self, TextTagClass tag) => self -> tag -> IO ()
-textTagTableRemove :: (TextTagTableClass self, TextTagClass tag) => self -> tag -> IO ()
-textTagTableLookup :: TextTagTableClass self => self -> String -> IO (Maybe TextTag)
-textTagTableForeach :: TextTagTableClass self => self -> (TextTag -> IO ()) -> IO ()
-textTagTableGetSize :: TextTagTableClass self => self -> IO Int
-
-module Graphics.UI.Gtk.Multiline.TextMark
-data TextMark
-instance GObjectClass TextMark
-instance TextMarkClass TextMark
-class GObjectClass o => TextMarkClass o
-instance TextMarkClass SourceMarker
-instance TextMarkClass TextMark
-castToTextMark :: GObjectClass obj => obj -> TextMark
-toTextMark :: TextMarkClass o => o -> TextMark
-type MarkName = String
-textMarkSetVisible :: TextMarkClass self => self -> Bool -> IO ()
-textMarkGetVisible :: TextMarkClass self => self -> IO Bool
-textMarkGetDeleted :: TextMarkClass self => self -> IO Bool
-textMarkGetName :: TextMarkClass self => self -> IO (Maybe MarkName)
-textMarkGetBuffer :: TextMarkClass self => self -> IO (Maybe TextBuffer)
-textMarkGetLeftGravity :: TextMarkClass self => self -> IO Bool
-textMarkVisible :: TextMarkClass self => Attr self Bool
-
-module Graphics.UI.Gtk.Misc.SizeGroup
-data SizeGroup
-instance GObjectClass SizeGroup
-instance SizeGroupClass SizeGroup
-class GObjectClass o => SizeGroupClass o
-instance SizeGroupClass SizeGroup
-castToSizeGroup :: GObjectClass obj => obj -> SizeGroup
-toSizeGroup :: SizeGroupClass o => o -> SizeGroup
-sizeGroupNew :: SizeGroupMode -> IO SizeGroup
-data SizeGroupMode
-SizeGroupNone :: SizeGroupMode
-SizeGroupHorizontal :: SizeGroupMode
-SizeGroupVertical :: SizeGroupMode
-SizeGroupBoth :: SizeGroupMode
-instance Enum SizeGroupMode
-sizeGroupSetMode :: SizeGroupClass self => self -> SizeGroupMode -> IO ()
-sizeGroupGetMode :: SizeGroupClass self => self -> IO SizeGroupMode
-sizeGroupAddWidget :: (SizeGroupClass self, WidgetClass widget) => self -> widget -> IO ()
-sizeGroupRemoveWidget :: (SizeGroupClass self, WidgetClass widget) => self -> widget -> IO ()
-sizeGroupSetIgnoreHidden :: SizeGroupClass self => self -> Bool -> IO ()
-sizeGroupGetIgnoreHidden :: SizeGroupClass self => self -> IO Bool
-sizeGroupMode :: SizeGroupClass self => Attr self SizeGroupMode
-sizeGroupIgnoreHidden :: SizeGroupClass self => Attr self Bool
-
-module Graphics.UI.Gtk.Gdk.Keys
-type KeyVal = Word32
-keyvalName :: KeyVal -> IO String
-keyvalFromName :: String -> IO KeyVal
-keyvalToChar :: KeyVal -> IO (Maybe Char)
-
-module Graphics.UI.Gtk.Gdk.Gdk
-beep :: IO ()
-flush :: IO ()
-
-module Graphics.UI.Gtk.Gdk.Enums
-data CapStyle
-CapNotLast :: CapStyle
-CapButt :: CapStyle
-CapRound :: CapStyle
-CapProjecting :: CapStyle
-instance Enum CapStyle
-data CrossingMode
-CrossingNormal :: CrossingMode
-CrossingGrab :: CrossingMode
-CrossingUngrab :: CrossingMode
-instance Enum CrossingMode
-data Dither
-RgbDitherNone :: Dither
-RgbDitherNormal :: Dither
-RgbDitherMax :: Dither
-instance Enum Dither
-data EventMask
-ExposureMask :: EventMask
-PointerMotionMask :: EventMask
-PointerMotionHintMask :: EventMask
-ButtonMotionMask :: EventMask
-Button1MotionMask :: EventMask
-Button2MotionMask :: EventMask
-Button3MotionMask :: EventMask
-ButtonPressMask :: EventMask
-ButtonReleaseMask :: EventMask
-KeyPressMask :: EventMask
-KeyReleaseMask :: EventMask
-EnterNotifyMask :: EventMask
-LeaveNotifyMask :: EventMask
-FocusChangeMask :: EventMask
-StructureMask :: EventMask
-PropertyChangeMask :: EventMask
-VisibilityNotifyMask :: EventMask
-ProximityInMask :: EventMask
-ProximityOutMask :: EventMask
-SubstructureMask :: EventMask
-ScrollMask :: EventMask
-AllEventsMask :: EventMask
-instance Bounded EventMask
-instance Enum EventMask
-instance Flags EventMask
-data ExtensionMode
-ExtensionEventsNone :: ExtensionMode
-ExtensionEventsAll :: ExtensionMode
-ExtensionEventsCursor :: ExtensionMode
-instance Bounded ExtensionMode
-instance Enum ExtensionMode
-instance Flags ExtensionMode
-data Fill
-Solid :: Fill
-Tiled :: Fill
-Stippled :: Fill
-OpaqueStippled :: Fill
-instance Enum Fill
-data FillRule
-EvenOddRule :: FillRule
-WindingRule :: FillRule
-instance Enum FillRule
-data Function
-Copy :: Function
-Invert :: Function
-Xor :: Function
-Clear :: Function
-And :: Function
-AndReverse :: Function
-AndInvert :: Function
-Noop :: Function
-Or :: Function
-Equiv :: Function
-OrReverse :: Function
-CopyInvert :: Function
-OrInvert :: Function
-Nand :: Function
-Nor :: Function
-Set :: Function
-instance Enum Function
-data InputCondition
-InputRead :: InputCondition
-InputWrite :: InputCondition
-InputException :: InputCondition
-instance Bounded InputCondition
-instance Enum InputCondition
-instance Flags InputCondition
-data JoinStyle
-JoinMiter :: JoinStyle
-JoinRound :: JoinStyle
-JoinBevel :: JoinStyle
-instance Enum JoinStyle
-data LineStyle
-LineSolid :: LineStyle
-LineOnOffDash :: LineStyle
-LineDoubleDash :: LineStyle
-instance Enum LineStyle
-data NotifyType
-NotifyAncestor :: NotifyType
-NotifyVirtual :: NotifyType
-NotifyInferior :: NotifyType
-NotifyNonlinear :: NotifyType
-NotifyNonlinearVirtual :: NotifyType
-NotifyUnknown :: NotifyType
-instance Enum NotifyType
-data OverlapType
-OverlapRectangleIn :: OverlapType
-OverlapRectangleOut :: OverlapType
-OverlapRectanglePart :: OverlapType
-instance Enum OverlapType
-data ScrollDirection
-ScrollUp :: ScrollDirection
-ScrollDown :: ScrollDirection
-ScrollLeft :: ScrollDirection
-ScrollRight :: ScrollDirection
-instance Enum ScrollDirection
-data SubwindowMode
-ClipByChildren :: SubwindowMode
-IncludeInferiors :: SubwindowMode
-instance Enum SubwindowMode
-data VisibilityState
-VisibilityUnobscured :: VisibilityState
-VisibilityPartialObscured :: VisibilityState
-VisibilityFullyObscured :: VisibilityState
-instance Enum VisibilityState
-data WindowState
-WindowStateWithdrawn :: WindowState
-WindowStateIconified :: WindowState
-WindowStateMaximized :: WindowState
-WindowStateSticky :: WindowState
-WindowStateFullscreen :: WindowState
-WindowStateAbove :: WindowState
-WindowStateBelow :: WindowState
-instance Bounded WindowState
-instance Enum WindowState
-instance Flags WindowState
-data WindowEdge
-WindowEdgeNorthWest :: WindowEdge
-WindowEdgeNorth :: WindowEdge
-WindowEdgeNorthEast :: WindowEdge
-WindowEdgeWest :: WindowEdge
-WindowEdgeEast :: WindowEdge
-WindowEdgeSouthWest :: WindowEdge
-WindowEdgeSouth :: WindowEdge
-WindowEdgeSouthEast :: WindowEdge
-instance Enum WindowEdge
-data WindowTypeHint
-WindowTypeHintNormal :: WindowTypeHint
-WindowTypeHintDialog :: WindowTypeHint
-WindowTypeHintMenu :: WindowTypeHint
-WindowTypeHintToolbar :: WindowTypeHint
-WindowTypeHintSplashscreen :: WindowTypeHint
-WindowTypeHintUtility :: WindowTypeHint
-WindowTypeHintDock :: WindowTypeHint
-WindowTypeHintDesktop :: WindowTypeHint
-instance Enum WindowTypeHint
-data Gravity
-GravityNorthWest :: Gravity
-GravityNorth :: Gravity
-GravityNorthEast :: Gravity
-GravityWest :: Gravity
-GravityCenter :: Gravity
-GravityEast :: Gravity
-GravitySouthWest :: Gravity
-GravitySouth :: Gravity
-GravitySouthEast :: Gravity
-GravityStatic :: Gravity
-instance Enum Gravity
-
-module Graphics.UI.Gtk.General.Enums
-data AccelFlags
-AccelVisible :: AccelFlags
-AccelLocked :: AccelFlags
-AccelMask :: AccelFlags
-instance Bounded AccelFlags
-instance Enum AccelFlags
-instance Eq AccelFlags
-instance Flags AccelFlags
-data ArrowType
-ArrowUp :: ArrowType
-ArrowDown :: ArrowType
-ArrowLeft :: ArrowType
-ArrowRight :: ArrowType
-instance Enum ArrowType
-instance Eq ArrowType
-data AttachOptions
-Expand :: AttachOptions
-Shrink :: AttachOptions
-Fill :: AttachOptions
-instance Bounded AttachOptions
-instance Enum AttachOptions
-instance Eq AttachOptions
-instance Flags AttachOptions
-data MouseButton
-LeftButton :: MouseButton
-MiddleButton :: MouseButton
-RightButton :: MouseButton
-instance Enum MouseButton
-instance Eq MouseButton
-instance Show MouseButton
-data ButtonBoxStyle
-ButtonboxDefaultStyle :: ButtonBoxStyle
-ButtonboxSpread :: ButtonBoxStyle
-ButtonboxEdge :: ButtonBoxStyle
-ButtonboxStart :: ButtonBoxStyle
-ButtonboxEnd :: ButtonBoxStyle
-instance Enum ButtonBoxStyle
-instance Eq ButtonBoxStyle
-data CalendarDisplayOptions
-CalendarShowHeading :: CalendarDisplayOptions
-CalendarShowDayNames :: CalendarDisplayOptions
-CalendarNoMonthChange :: CalendarDisplayOptions
-CalendarShowWeekNumbers :: CalendarDisplayOptions
-CalendarWeekStartMonday :: CalendarDisplayOptions
-instance Bounded CalendarDisplayOptions
-instance Enum CalendarDisplayOptions
-instance Eq CalendarDisplayOptions
-instance Flags CalendarDisplayOptions
-data Click
-SingleClick :: Click
-DoubleClick :: Click
-TripleClick :: Click
-ReleaseClick :: Click
-data CornerType
-CornerTopLeft :: CornerType
-CornerBottomLeft :: CornerType
-CornerTopRight :: CornerType
-CornerBottomRight :: CornerType
-instance Enum CornerType
-instance Eq CornerType
-data CurveType
-CurveTypeLinear :: CurveType
-CurveTypeSpline :: CurveType
-CurveTypeFree :: CurveType
-instance Enum CurveType
-instance Eq CurveType
-data DeleteType
-DeleteChars :: DeleteType
-DeleteWordEnds :: DeleteType
-DeleteWords :: DeleteType
-DeleteDisplayLines :: DeleteType
-DeleteDisplayLineEnds :: DeleteType
-DeleteParagraphEnds :: DeleteType
-DeleteParagraphs :: DeleteType
-DeleteWhitespace :: DeleteType
-instance Enum DeleteType
-instance Eq DeleteType
-data DirectionType
-DirTabForward :: DirectionType
-DirTabBackward :: DirectionType
-DirUp :: DirectionType
-DirDown :: DirectionType
-DirLeft :: DirectionType
-DirRight :: DirectionType
-instance Enum DirectionType
-instance Eq DirectionType
-data Justification
-JustifyLeft :: Justification
-JustifyRight :: Justification
-JustifyCenter :: Justification
-JustifyFill :: Justification
-instance Enum Justification
-instance Eq Justification
-data MatchType
-MatchAll :: MatchType
-MatchAllTail :: MatchType
-MatchHead :: MatchType
-MatchTail :: MatchType
-MatchExact :: MatchType
-MatchLast :: MatchType
-instance Enum MatchType
-instance Eq MatchType
-data MenuDirectionType
-MenuDirParent :: MenuDirectionType
-MenuDirChild :: MenuDirectionType
-MenuDirNext :: MenuDirectionType
-MenuDirPrev :: MenuDirectionType
-instance Enum MenuDirectionType
-instance Eq MenuDirectionType
-data MetricType
-Pixels :: MetricType
-Inches :: MetricType
-Centimeters :: MetricType
-instance Enum MetricType
-instance Eq MetricType
-data MovementStep
-MovementLogicalPositions :: MovementStep
-MovementVisualPositions :: MovementStep
-MovementWords :: MovementStep
-MovementDisplayLines :: MovementStep
-MovementDisplayLineEnds :: MovementStep
-MovementParagraphs :: MovementStep
-MovementParagraphEnds :: MovementStep
-MovementPages :: MovementStep
-MovementBufferEnds :: MovementStep
-MovementHorizontalPages :: MovementStep
-instance Enum MovementStep
-instance Eq MovementStep
-data Orientation
-OrientationHorizontal :: Orientation
-OrientationVertical :: Orientation
-instance Enum Orientation
-instance Eq Orientation
-data Packing
-PackRepel :: Packing
-PackGrow :: Packing
-PackNatural :: Packing
-instance Enum Packing
-instance Eq Packing
-toPacking :: Bool -> Bool -> Packing
-fromPacking :: Packing -> (Bool, Bool)
-data PackType
-PackStart :: PackType
-PackEnd :: PackType
-instance Enum PackType
-instance Eq PackType
-data PathPriorityType
-PathPrioLowest :: PathPriorityType
-PathPrioGtk :: PathPriorityType
-PathPrioApplication :: PathPriorityType
-PathPrioTheme :: PathPriorityType
-PathPrioRc :: PathPriorityType
-PathPrioHighest :: PathPriorityType
-instance Enum PathPriorityType
-instance Eq PathPriorityType
-data PathType
-PathWidget :: PathType
-PathWidgetClass :: PathType
-PathClass :: PathType
-instance Enum PathType
-instance Eq PathType
-data PolicyType
-PolicyAlways :: PolicyType
-PolicyAutomatic :: PolicyType
-PolicyNever :: PolicyType
-instance Enum PolicyType
-instance Eq PolicyType
-data PositionType
-PosLeft :: PositionType
-PosRight :: PositionType
-PosTop :: PositionType
-PosBottom :: PositionType
-instance Enum PositionType
-instance Eq PositionType
-data ProgressBarOrientation
-ProgressLeftToRight :: ProgressBarOrientation
-ProgressRightToLeft :: ProgressBarOrientation
-ProgressBottomToTop :: ProgressBarOrientation
-ProgressTopToBottom :: ProgressBarOrientation
-instance Enum ProgressBarOrientation
-instance Eq ProgressBarOrientation
-data ReliefStyle
-ReliefNormal :: ReliefStyle
-ReliefHalf :: ReliefStyle
-ReliefNone :: ReliefStyle
-instance Enum ReliefStyle
-instance Eq ReliefStyle
-data ResizeMode
-ResizeParent :: ResizeMode
-ResizeQueue :: ResizeMode
-ResizeImmediate :: ResizeMode
-instance Enum ResizeMode
-instance Eq ResizeMode
-data ScrollType
-ScrollNone :: ScrollType
-ScrollJump :: ScrollType
-ScrollStepBackward :: ScrollType
-ScrollStepForward :: ScrollType
-ScrollPageBackward :: ScrollType
-ScrollPageForward :: ScrollType
-ScrollStepUp :: ScrollType
-ScrollStepDown :: ScrollType
-ScrollPageUp :: ScrollType
-ScrollPageDown :: ScrollType
-ScrollStepLeft :: ScrollType
-ScrollStepRight :: ScrollType
-ScrollPageLeft :: ScrollType
-ScrollPageRight :: ScrollType
-ScrollStart :: ScrollType
-ScrollEnd :: ScrollType
-instance Enum ScrollType
-instance Eq ScrollType
-data SelectionMode
-SelectionNone :: SelectionMode
-SelectionSingle :: SelectionMode
-SelectionBrowse :: SelectionMode
-SelectionMultiple :: SelectionMode
-instance Enum SelectionMode
-data ShadowType
-ShadowNone :: ShadowType
-ShadowIn :: ShadowType
-ShadowOut :: ShadowType
-ShadowEtchedIn :: ShadowType
-ShadowEtchedOut :: ShadowType
-instance Enum ShadowType
-instance Eq ShadowType
-data StateType
-StateNormal :: StateType
-StateActive :: StateType
-StatePrelight :: StateType
-StateSelected :: StateType
-StateInsensitive :: StateType
-instance Enum StateType
-instance Eq StateType
-data SubmenuDirection
-DirectionLeft :: SubmenuDirection
-DirectionRight :: SubmenuDirection
-instance Enum SubmenuDirection
-instance Eq SubmenuDirection
-data SubmenuPlacement
-TopBottom :: SubmenuPlacement
-LeftRight :: SubmenuPlacement
-instance Enum SubmenuPlacement
-instance Eq SubmenuPlacement
-data SpinButtonUpdatePolicy
-UpdateAlways :: SpinButtonUpdatePolicy
-UpdateIfValid :: SpinButtonUpdatePolicy
-instance Enum SpinButtonUpdatePolicy
-instance Eq SpinButtonUpdatePolicy
-data SpinType
-SpinStepForward :: SpinType
-SpinStepBackward :: SpinType
-SpinPageForward :: SpinType
-SpinPageBackward :: SpinType
-SpinHome :: SpinType
-SpinEnd :: SpinType
-SpinUserDefined :: SpinType
-instance Enum SpinType
-instance Eq SpinType
-data TextDirection
-TextDirNone :: TextDirection
-TextDirLtr :: TextDirection
-TextDirRtl :: TextDirection
-instance Enum TextDirection
-instance Eq TextDirection
-data TextSearchFlags
-TextSearchVisibleOnly :: TextSearchFlags
-TextSearchTextOnly :: TextSearchFlags
-instance Bounded TextSearchFlags
-instance Enum TextSearchFlags
-instance Eq TextSearchFlags
-instance Flags TextSearchFlags
-data TextWindowType
-TextWindowPrivate :: TextWindowType
-TextWindowWidget :: TextWindowType
-TextWindowText :: TextWindowType
-TextWindowLeft :: TextWindowType
-TextWindowRight :: TextWindowType
-TextWindowTop :: TextWindowType
-TextWindowBottom :: TextWindowType
-instance Enum TextWindowType
-instance Eq TextWindowType
-data ToolbarStyle
-ToolbarIcons :: ToolbarStyle
-ToolbarText :: ToolbarStyle
-ToolbarBoth :: ToolbarStyle
-ToolbarBothHoriz :: ToolbarStyle
-instance Enum ToolbarStyle
-instance Eq ToolbarStyle
-data TreeViewColumnSizing
-TreeViewColumnGrowOnly :: TreeViewColumnSizing
-TreeViewColumnAutosize :: TreeViewColumnSizing
-TreeViewColumnFixed :: TreeViewColumnSizing
-instance Enum TreeViewColumnSizing
-instance Eq TreeViewColumnSizing
-data UpdateType
-UpdateContinuous :: UpdateType
-UpdateDiscontinuous :: UpdateType
-UpdateDelayed :: UpdateType
-instance Enum UpdateType
-instance Eq UpdateType
-data Visibility
-VisibilityNone :: Visibility
-VisibilityPartial :: Visibility
-VisibilityFull :: Visibility
-instance Enum Visibility
-instance Eq Visibility
-data WindowPosition
-WinPosNone :: WindowPosition
-WinPosCenter :: WindowPosition
-WinPosMouse :: WindowPosition
-WinPosCenterAlways :: WindowPosition
-WinPosCenterOnParent :: WindowPosition
-instance Enum WindowPosition
-instance Eq WindowPosition
-data WindowType
-WindowToplevel :: WindowType
-WindowPopup :: WindowType
-instance Enum WindowType
-instance Eq WindowType
-data WrapMode
-WrapNone :: WrapMode
-WrapChar :: WrapMode
-WrapWord :: WrapMode
-WrapWordChar :: WrapMode
-instance Enum WrapMode
-instance Eq WrapMode
-data SortType
-SortAscending :: SortType
-SortDescending :: SortType
-instance Enum SortType
-instance Eq SortType
-
-module Graphics.UI.Gtk.Multiline.TextTag
-data TextTag
-instance GObjectClass TextTag
-instance TextTagClass TextTag
-class GObjectClass o => TextTagClass o
-instance TextTagClass SourceTag
-instance TextTagClass TextTag
-castToTextTag :: GObjectClass obj => obj -> TextTag
-toTextTag :: TextTagClass o => o -> TextTag
-type TagName = String
-textTagNew :: TagName -> IO TextTag
-textTagSetPriority :: TextTagClass self => self -> Int -> IO ()
-textTagGetPriority :: TextTagClass self => self -> IO Int
-newtype TextAttributes
-TextAttributes :: ForeignPtr TextAttributes -> TextAttributes
-textAttributesNew :: IO TextAttributes
-makeNewTextAttributes :: Ptr TextAttributes -> IO TextAttributes
-textTagName :: TextTagClass self => Attr self (Maybe String)
-textTagBackground :: TextTagClass self => WriteAttr self String
-textTagBackgroundFullHeight :: TextTagClass self => Attr self Bool
-textTagBackgroundStipple :: (TextTagClass self, PixmapClass pixmap) => ReadWriteAttr self Pixmap pixmap
-textTagForeground :: TextTagClass self => WriteAttr self String
-textTagForegroundStipple :: (TextTagClass self, PixmapClass pixmap) => ReadWriteAttr self Pixmap pixmap
-textTagDirection :: TextTagClass self => Attr self TextDirection
-textTagEditable :: TextTagClass self => Attr self Bool
-textTagFont :: TextTagClass self => Attr self String
-textTagFamily :: TextTagClass self => Attr self String
-textTagStyle :: TextTagClass self => Attr self FontStyle
-textTagVariant :: TextTagClass self => Attr self Variant
-textTagWeight :: TextTagClass self => Attr self Int
-textTagStretch :: TextTagClass self => Attr self Stretch
-textTagSize :: TextTagClass self => Attr self Int
-textTagScale :: TextTagClass self => Attr self Double
-textTagSizePoints :: TextTagClass self => Attr self Double
-textTagJustification :: TextTagClass self => Attr self Justification
-textTagLanguage :: TextTagClass self => Attr self String
-textTagLeftMargin :: TextTagClass self => Attr self Int
-textTagRightMargin :: TextTagClass self => Attr self Int
-textTagIndent :: TextTagClass self => Attr self Int
-textTagRise :: TextTagClass self => Attr self Int
-textTagPixelsAboveLines :: TextTagClass self => Attr self Int
-textTagPixelsBelowLines :: TextTagClass self => Attr self Int
-textTagPixelsInsideWrap :: TextTagClass self => Attr self Int
-textTagStrikethrough :: TextTagClass self => Attr self Bool
-textTagUnderline :: TextTagClass self => Attr self Underline
-textTagWrapMode :: TextTagClass self => Attr self WrapMode
-textTagInvisible :: TextTagClass self => Attr self Bool
-textTagParagraphBackground :: TextTagClass self => WriteAttr self String
-textTagPriority :: TextTagClass self => Attr self Int
-
-module Graphics.UI.Gtk.Embedding.Embedding
-socketHasPlug :: SocketClass s => s -> IO Bool
-type NativeWindowId = Word32
-
-module Graphics.UI.Gtk.ActionMenuToolbar.ToggleAction
-data ToggleAction
-instance ActionClass ToggleAction
-instance GObjectClass ToggleAction
-instance ToggleActionClass ToggleAction
-class ActionClass o => ToggleActionClass o
-instance ToggleActionClass RadioAction
-instance ToggleActionClass ToggleAction
-castToToggleAction :: GObjectClass obj => obj -> ToggleAction
-toToggleAction :: ToggleActionClass o => o -> ToggleAction
-toggleActionNew :: String -> String -> Maybe String -> Maybe String -> IO ToggleAction
-toggleActionToggled :: ToggleActionClass self => self -> IO ()
-toggleActionSetActive :: ToggleActionClass self => self -> Bool -> IO ()
-toggleActionGetActive :: ToggleActionClass self => self -> IO Bool
-toggleActionSetDrawAsRadio :: ToggleActionClass self => self -> Bool -> IO ()
-toggleActionGetDrawAsRadio :: ToggleActionClass self => self -> IO Bool
-toggleActionDrawAsRadio :: ToggleActionClass self => Attr self Bool
-toggleActionActive :: ToggleActionClass self => Attr self Bool
-onToggleActionToggled :: ToggleActionClass self => self -> IO () -> IO (ConnectId self)
-afterToggleActionToggled :: ToggleActionClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.ActionMenuToolbar.RadioAction
-data RadioAction
-instance ActionClass RadioAction
-instance GObjectClass RadioAction
-instance RadioActionClass RadioAction
-instance ToggleActionClass RadioAction
-class ToggleActionClass o => RadioActionClass o
-instance RadioActionClass RadioAction
-castToRadioAction :: GObjectClass obj => obj -> RadioAction
-toRadioAction :: RadioActionClass o => o -> RadioAction
-radioActionNew :: String -> String -> Maybe String -> Maybe String -> Int -> IO RadioAction
-radioActionGetGroup :: RadioActionClass self => self -> IO [RadioAction]
-radioActionSetGroup :: (RadioActionClass self, RadioActionClass groupMember) => self -> groupMember -> IO ()
-radioActionGetCurrentValue :: RadioActionClass self => self -> IO Int
-radioActionGroup :: RadioActionClass self => ReadWriteAttr self [RadioAction] RadioAction
-onRadioActionChanged :: RadioActionClass self => self -> (RadioAction -> IO ()) -> IO (ConnectId self)
-afterRadioActionChanged :: RadioActionClass self => self -> (RadioAction -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Abstract.Separator
-data Separator
-instance GObjectClass Separator
-instance ObjectClass Separator
-instance SeparatorClass Separator
-instance WidgetClass Separator
-class WidgetClass o => SeparatorClass o
-instance SeparatorClass HSeparator
-instance SeparatorClass Separator
-instance SeparatorClass VSeparator
-castToSeparator :: GObjectClass obj => obj -> Separator
-toSeparator :: SeparatorClass o => o -> Separator
-
-module Graphics.UI.Gtk.Abstract.Scrollbar
-data Scrollbar
-instance GObjectClass Scrollbar
-instance ObjectClass Scrollbar
-instance RangeClass Scrollbar
-instance ScrollbarClass Scrollbar
-instance WidgetClass Scrollbar
-class RangeClass o => ScrollbarClass o
-instance ScrollbarClass HScrollbar
-instance ScrollbarClass Scrollbar
-instance ScrollbarClass VScrollbar
-castToScrollbar :: GObjectClass obj => obj -> Scrollbar
-toScrollbar :: ScrollbarClass o => o -> Scrollbar
-
-module Graphics.UI.Gtk.Abstract.Object
-data Object
-instance GObjectClass Object
-instance ObjectClass Object
-class GObjectClass o => ObjectClass o
-instance ObjectClass AboutDialog
-instance ObjectClass AccelLabel
-instance ObjectClass Adjustment
-instance ObjectClass Alignment
-instance ObjectClass Arrow
-instance ObjectClass AspectFrame
-instance ObjectClass Bin
-instance ObjectClass Box
-instance ObjectClass Button
-instance ObjectClass ButtonBox
-instance ObjectClass CList
-instance ObjectClass CTree
-instance ObjectClass Calendar
-instance ObjectClass CellRenderer
-instance ObjectClass CellRendererPixbuf
-instance ObjectClass CellRendererText
-instance ObjectClass CellRendererToggle
-instance ObjectClass CellView
-instance ObjectClass CheckButton
-instance ObjectClass CheckMenuItem
-instance ObjectClass ColorButton
-instance ObjectClass ColorSelection
-instance ObjectClass ColorSelectionDialog
-instance ObjectClass Combo
-instance ObjectClass ComboBox
-instance ObjectClass ComboBoxEntry
-instance ObjectClass Container
-instance ObjectClass Curve
-instance ObjectClass Dialog
-instance ObjectClass DrawingArea
-instance ObjectClass Entry
-instance ObjectClass EventBox
-instance ObjectClass Expander
-instance ObjectClass FileChooserButton
-instance ObjectClass FileChooserDialog
-instance ObjectClass FileChooserWidget
-instance ObjectClass FileFilter
-instance ObjectClass FileSelection
-instance ObjectClass Fixed
-instance ObjectClass FontButton
-instance ObjectClass FontSelection
-instance ObjectClass FontSelectionDialog
-instance ObjectClass Frame
-instance ObjectClass GammaCurve
-instance ObjectClass HBox
-instance ObjectClass HButtonBox
-instance ObjectClass HPaned
-instance ObjectClass HRuler
-instance ObjectClass HScale
-instance ObjectClass HScrollbar
-instance ObjectClass HSeparator
-instance ObjectClass HandleBox
-instance ObjectClass IMContext
-instance ObjectClass IMMulticontext
-instance ObjectClass IconView
-instance ObjectClass Image
-instance ObjectClass ImageMenuItem
-instance ObjectClass InputDialog
-instance ObjectClass Invisible
-instance ObjectClass Item
-instance ObjectClass ItemFactory
-instance ObjectClass Label
-instance ObjectClass Layout
-instance ObjectClass List
-instance ObjectClass ListItem
-instance ObjectClass Menu
-instance ObjectClass MenuBar
-instance ObjectClass MenuItem
-instance ObjectClass MenuShell
-instance ObjectClass MenuToolButton
-instance ObjectClass MessageDialog
-instance ObjectClass Misc
-instance ObjectClass MozEmbed
-instance ObjectClass Notebook
-instance ObjectClass Object
-instance ObjectClass OptionMenu
-instance ObjectClass Paned
-instance ObjectClass Plug
-instance ObjectClass Preview
-instance ObjectClass ProgressBar
-instance ObjectClass RadioButton
-instance ObjectClass RadioMenuItem
-instance ObjectClass RadioToolButton
-instance ObjectClass Range
-instance ObjectClass Ruler
-instance ObjectClass Scale
-instance ObjectClass Scrollbar
-instance ObjectClass ScrolledWindow
-instance ObjectClass Separator
-instance ObjectClass SeparatorMenuItem
-instance ObjectClass SeparatorToolItem
-instance ObjectClass Socket
-instance ObjectClass SourceView
-instance ObjectClass SpinButton
-instance ObjectClass Statusbar
-instance ObjectClass Table
-instance ObjectClass TearoffMenuItem
-instance ObjectClass TextView
-instance ObjectClass TipsQuery
-instance ObjectClass ToggleButton
-instance ObjectClass ToggleToolButton
-instance ObjectClass ToolButton
-instance ObjectClass ToolItem
-instance ObjectClass Toolbar
-instance ObjectClass Tooltips
-instance ObjectClass TreeView
-instance ObjectClass TreeViewColumn
-instance ObjectClass VBox
-instance ObjectClass VButtonBox
-instance ObjectClass VPaned
-instance ObjectClass VRuler
-instance ObjectClass VScale
-instance ObjectClass VScrollbar
-instance ObjectClass VSeparator
-instance ObjectClass Viewport
-instance ObjectClass Widget
-instance ObjectClass Window
-castToObject :: GObjectClass obj => obj -> Object
-toObject :: ObjectClass o => o -> Object
-objectSink :: ObjectClass obj => Ptr obj -> IO ()
-makeNewObject :: ObjectClass obj => (ForeignPtr obj -> obj) -> IO (Ptr obj) -> IO obj
-
-module Graphics.UI.Gtk.Abstract.Range
-data Range
-instance GObjectClass Range
-instance ObjectClass Range
-instance RangeClass Range
-instance WidgetClass Range
-class WidgetClass o => RangeClass o
-instance RangeClass HScale
-instance RangeClass HScrollbar
-instance RangeClass Range
-instance RangeClass Scale
-instance RangeClass Scrollbar
-instance RangeClass VScale
-instance RangeClass VScrollbar
-castToRange :: GObjectClass obj => obj -> Range
-toRange :: RangeClass o => o -> Range
-rangeGetAdjustment :: RangeClass self => self -> IO Adjustment
-rangeSetAdjustment :: RangeClass self => self -> Adjustment -> IO ()
-data UpdateType
-UpdateContinuous :: UpdateType
-UpdateDiscontinuous :: UpdateType
-UpdateDelayed :: UpdateType
-instance Enum UpdateType
-instance Eq UpdateType
-rangeGetUpdatePolicy :: RangeClass self => self -> IO UpdateType
-rangeSetUpdatePolicy :: RangeClass self => self -> UpdateType -> IO ()
-rangeGetInverted :: RangeClass self => self -> IO Bool
-rangeSetInverted :: RangeClass self => self -> Bool -> IO ()
-rangeGetValue :: RangeClass self => self -> IO Double
-rangeSetValue :: RangeClass self => self -> Double -> IO ()
-rangeSetIncrements :: RangeClass self => self -> Double -> Double -> IO ()
-rangeSetRange :: RangeClass self => self -> Double -> Double -> IO ()
-data ScrollType
-ScrollNone :: ScrollType
-ScrollJump :: ScrollType
-ScrollStepBackward :: ScrollType
-ScrollStepForward :: ScrollType
-ScrollPageBackward :: ScrollType
-ScrollPageForward :: ScrollType
-ScrollStepUp :: ScrollType
-ScrollStepDown :: ScrollType
-ScrollPageUp :: ScrollType
-ScrollPageDown :: ScrollType
-ScrollStepLeft :: ScrollType
-ScrollStepRight :: ScrollType
-ScrollPageLeft :: ScrollType
-ScrollPageRight :: ScrollType
-ScrollStart :: ScrollType
-ScrollEnd :: ScrollType
-instance Enum ScrollType
-instance Eq ScrollType
-rangeUpdatePolicy :: RangeClass self => Attr self UpdateType
-rangeAdjustment :: RangeClass self => Attr self Adjustment
-rangeInverted :: RangeClass self => Attr self Bool
-rangeValue :: RangeClass self => Attr self Double
-onMoveSlider :: RangeClass self => self -> (ScrollType -> IO ()) -> IO (ConnectId self)
-afterMoveSlider :: RangeClass self => self -> (ScrollType -> IO ()) -> IO (ConnectId self)
-onAdjustBounds :: RangeClass self => self -> (Double -> IO ()) -> IO (ConnectId self)
-afterAdjustBounds :: RangeClass self => self -> (Double -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Abstract.Scale
-data Scale
-instance GObjectClass Scale
-instance ObjectClass Scale
-instance RangeClass Scale
-instance ScaleClass Scale
-instance WidgetClass Scale
-class RangeClass o => ScaleClass o
-instance ScaleClass HScale
-instance ScaleClass Scale
-instance ScaleClass VScale
-castToScale :: GObjectClass obj => obj -> Scale
-toScale :: ScaleClass o => o -> Scale
-scaleSetDigits :: ScaleClass self => self -> Int -> IO ()
-scaleGetDigits :: ScaleClass self => self -> IO Int
-scaleSetDrawValue :: ScaleClass self => self -> Bool -> IO ()
-scaleGetDrawValue :: ScaleClass self => self -> IO Bool
-data PositionType
-PosLeft :: PositionType
-PosRight :: PositionType
-PosTop :: PositionType
-PosBottom :: PositionType
-instance Enum PositionType
-instance Eq PositionType
-scaleSetValuePos :: ScaleClass self => self -> PositionType -> IO ()
-scaleGetValuePos :: ScaleClass self => self -> IO PositionType
-scaleDigits :: ScaleClass self => Attr self Int
-scaleDrawValue :: ScaleClass self => Attr self Bool
-scaleValuePos :: ScaleClass self => Attr self PositionType
-
-module Graphics.UI.Gtk.ActionMenuToolbar.UIManager
-data UIManager
-instance GObjectClass UIManager
-instance UIManagerClass UIManager
-class GObjectClass o => UIManagerClass o
-instance UIManagerClass UIManager
-castToUIManager :: GObjectClass obj => obj -> UIManager
-toUIManager :: UIManagerClass o => o -> UIManager
-data UIManagerItemType
-UiManagerAuto :: UIManagerItemType
-UiManagerMenubar :: UIManagerItemType
-UiManagerMenu :: UIManagerItemType
-UiManagerToolbar :: UIManagerItemType
-UiManagerPlaceholder :: UIManagerItemType
-UiManagerPopup :: UIManagerItemType
-UiManagerMenuitem :: UIManagerItemType
-UiManagerToolitem :: UIManagerItemType
-UiManagerSeparator :: UIManagerItemType
-UiManagerAccelerator :: UIManagerItemType
-instance Bounded UIManagerItemType
-instance Enum UIManagerItemType
-instance Flags UIManagerItemType
-data MergeId
-uiManagerNew :: IO UIManager
-uiManagerSetAddTearoffs :: UIManager -> Bool -> IO ()
-uiManagerGetAddTearoffs :: UIManager -> IO Bool
-uiManagerInsertActionGroup :: UIManager -> ActionGroup -> Int -> IO ()
-uiManagerRemoveActionGroup :: UIManager -> ActionGroup -> IO ()
-uiManagerGetActionGroups :: UIManager -> IO [ActionGroup]
-uiManagerGetAccelGroup :: UIManager -> IO AccelGroup
-uiManagerGetWidget :: UIManager -> String -> IO (Maybe Widget)
-uiManagerGetToplevels :: UIManager -> [UIManagerItemType] -> IO [Widget]
-uiManagerGetAction :: UIManager -> String -> IO (Maybe Action)
-uiManagerAddUiFromString :: UIManager -> String -> IO MergeId
-uiManagerAddUiFromFile :: UIManager -> String -> IO MergeId
-uiManagerNewMergeId :: UIManager -> IO MergeId
-uiManagerAddUi :: UIManager -> MergeId -> String -> String -> Maybe String -> [UIManagerItemType] -> Bool -> IO ()
-uiManagerRemoveUi :: UIManager -> MergeId -> IO ()
-uiManagerGetUi :: UIManager -> IO String
-uiManagerEnsureUpdate :: UIManager -> IO ()
-uiManagerAddTearoffs :: Attr UIManager Bool
-uiManagerUi :: ReadAttr UIManager String
-onAddWidget :: UIManagerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-afterAddWidget :: UIManagerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-onActionsChanged :: UIManagerClass self => self -> IO () -> IO (ConnectId self)
-afterActionsChanged :: UIManagerClass self => self -> IO () -> IO (ConnectId self)
-onConnectProxy :: UIManagerClass self => self -> (Action -> Widget -> IO ()) -> IO (ConnectId self)
-afterConnectProxy :: UIManagerClass self => self -> (Action -> Widget -> IO ()) -> IO (ConnectId self)
-onDisconnectProxy :: UIManagerClass self => self -> (Action -> Widget -> IO ()) -> IO (ConnectId self)
-afterDisconnectProxy :: UIManagerClass self => self -> (Action -> Widget -> IO ()) -> IO (ConnectId self)
-onPreActivate :: UIManagerClass self => self -> (Action -> IO ()) -> IO (ConnectId self)
-afterPreActivate :: UIManagerClass self => self -> (Action -> IO ()) -> IO (ConnectId self)
-onPostActivate :: UIManagerClass self => self -> (Action -> IO ()) -> IO (ConnectId self)
-afterPostActivate :: UIManagerClass self => self -> (Action -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Buttons.Button
-data Button
-instance BinClass Button
-instance ButtonClass Button
-instance ContainerClass Button
-instance GObjectClass Button
-instance ObjectClass Button
-instance WidgetClass Button
-class BinClass o => ButtonClass o
-instance ButtonClass Button
-instance ButtonClass CheckButton
-instance ButtonClass ColorButton
-instance ButtonClass FontButton
-instance ButtonClass OptionMenu
-instance ButtonClass RadioButton
-instance ButtonClass ToggleButton
-castToButton :: GObjectClass obj => obj -> Button
-toButton :: ButtonClass o => o -> Button
-buttonNew :: IO Button
-buttonNewWithLabel :: String -> IO Button
-buttonNewWithMnemonic :: String -> IO Button
-buttonNewFromStock :: String -> IO Button
-buttonPressed :: ButtonClass self => self -> IO ()
-buttonReleased :: ButtonClass self => self -> IO ()
-buttonClicked :: ButtonClass self => self -> IO ()
-buttonEnter :: ButtonClass self => self -> IO ()
-buttonLeave :: ButtonClass self => self -> IO ()
-data ReliefStyle
-ReliefNormal :: ReliefStyle
-ReliefHalf :: ReliefStyle
-ReliefNone :: ReliefStyle
-instance Enum ReliefStyle
-instance Eq ReliefStyle
-buttonSetRelief :: ButtonClass self => self -> ReliefStyle -> IO ()
-buttonGetRelief :: ButtonClass self => self -> IO ReliefStyle
-buttonSetLabel :: ButtonClass self => self -> String -> IO ()
-buttonGetLabel :: ButtonClass self => self -> IO String
-buttonSetUseStock :: ButtonClass self => self -> Bool -> IO ()
-buttonGetUseStock :: ButtonClass self => self -> IO Bool
-buttonSetUseUnderline :: ButtonClass self => self -> Bool -> IO ()
-buttonGetUseUnderline :: ButtonClass self => self -> IO Bool
-buttonSetFocusOnClick :: ButtonClass self => self -> Bool -> IO ()
-buttonGetFocusOnClick :: ButtonClass self => self -> IO Bool
-buttonSetAlignment :: ButtonClass self => self -> (Float, Float) -> IO ()
-buttonGetAlignment :: ButtonClass self => self -> IO (Float, Float)
-buttonGetImage :: ButtonClass self => self -> IO (Maybe Widget)
-buttonSetImage :: (ButtonClass self, WidgetClass image) => self -> image -> IO ()
-buttonLabel :: ButtonClass self => Attr self String
-buttonUseUnderline :: ButtonClass self => Attr self Bool
-buttonUseStock :: ButtonClass self => Attr self Bool
-buttonFocusOnClick :: ButtonClass self => Attr self Bool
-buttonRelief :: ButtonClass self => Attr self ReliefStyle
-buttonXalign :: ButtonClass self => Attr self Float
-buttonYalign :: ButtonClass self => Attr self Float
-buttonImage :: (ButtonClass self, WidgetClass image) => ReadWriteAttr self (Maybe Widget) image
-onButtonActivate :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-afterButtonActivate :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-onClicked :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-afterClicked :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-onEnter :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-afterEnter :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-onLeave :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-afterLeave :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-onPressed :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-afterPressed :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-onReleased :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-afterReleased :: ButtonClass b => b -> IO () -> IO (ConnectId b)
-
-module Graphics.UI.Gtk.Buttons.CheckButton
-data CheckButton
-instance BinClass CheckButton
-instance ButtonClass CheckButton
-instance CheckButtonClass CheckButton
-instance ContainerClass CheckButton
-instance GObjectClass CheckButton
-instance ObjectClass CheckButton
-instance ToggleButtonClass CheckButton
-instance WidgetClass CheckButton
-class ToggleButtonClass o => CheckButtonClass o
-instance CheckButtonClass CheckButton
-instance CheckButtonClass RadioButton
-castToCheckButton :: GObjectClass obj => obj -> CheckButton
-toCheckButton :: CheckButtonClass o => o -> CheckButton
-checkButtonNew :: IO CheckButton
-checkButtonNewWithLabel :: String -> IO CheckButton
-checkButtonNewWithMnemonic :: String -> IO CheckButton
-
-module Graphics.UI.Gtk.Buttons.RadioButton
-data RadioButton
-instance BinClass RadioButton
-instance ButtonClass RadioButton
-instance CheckButtonClass RadioButton
-instance ContainerClass RadioButton
-instance GObjectClass RadioButton
-instance ObjectClass RadioButton
-instance RadioButtonClass RadioButton
-instance ToggleButtonClass RadioButton
-instance WidgetClass RadioButton
-class CheckButtonClass o => RadioButtonClass o
-instance RadioButtonClass RadioButton
-castToRadioButton :: GObjectClass obj => obj -> RadioButton
-toRadioButton :: RadioButtonClass o => o -> RadioButton
-radioButtonNew :: IO RadioButton
-radioButtonNewWithLabel :: String -> IO RadioButton
-radioButtonNewWithMnemonic :: String -> IO RadioButton
-radioButtonNewFromWidget :: RadioButton -> IO RadioButton
-radioButtonNewWithLabelFromWidget :: RadioButton -> String -> IO RadioButton
-radioButtonNewWithMnemonicFromWidget :: RadioButton -> String -> IO RadioButton
-radioButtonSetGroup :: RadioButton -> RadioButton -> IO ()
-radioButtonGetGroup :: RadioButton -> IO [RadioButton]
-radioButtonGroup :: ReadWriteAttr RadioButton [RadioButton] RadioButton
-onGroupChanged :: RadioButtonClass self => self -> IO () -> IO (ConnectId self)
-afterGroupChanged :: RadioButtonClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Buttons.ToggleButton
-data ToggleButton
-instance BinClass ToggleButton
-instance ButtonClass ToggleButton
-instance ContainerClass ToggleButton
-instance GObjectClass ToggleButton
-instance ObjectClass ToggleButton
-instance ToggleButtonClass ToggleButton
-instance WidgetClass ToggleButton
-class ButtonClass o => ToggleButtonClass o
-instance ToggleButtonClass CheckButton
-instance ToggleButtonClass RadioButton
-instance ToggleButtonClass ToggleButton
-castToToggleButton :: GObjectClass obj => obj -> ToggleButton
-toToggleButton :: ToggleButtonClass o => o -> ToggleButton
-toggleButtonNew :: IO ToggleButton
-toggleButtonNewWithLabel :: String -> IO ToggleButton
-toggleButtonNewWithMnemonic :: String -> IO ToggleButton
-toggleButtonSetMode :: ToggleButtonClass self => self -> Bool -> IO ()
-toggleButtonGetMode :: ToggleButtonClass self => self -> IO Bool
-toggleButtonToggled :: ToggleButtonClass self => self -> IO ()
-toggleButtonGetActive :: ToggleButtonClass self => self -> IO Bool
-toggleButtonSetActive :: ToggleButtonClass self => self -> Bool -> IO ()
-toggleButtonGetInconsistent :: ToggleButtonClass self => self -> IO Bool
-toggleButtonSetInconsistent :: ToggleButtonClass self => self -> Bool -> IO ()
-toggleButtonActive :: ToggleButtonClass self => Attr self Bool
-toggleButtonInconsistent :: ToggleButtonClass self => Attr self Bool
-toggleButtonDrawIndicator :: ToggleButtonClass self => Attr self Bool
-toggleButtonMode :: ToggleButtonClass self => Attr self Bool
-onToggled :: ToggleButtonClass self => self -> IO () -> IO (ConnectId self)
-afterToggled :: ToggleButtonClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Display.AccelLabel
-data AccelLabel
-instance AccelLabelClass AccelLabel
-instance GObjectClass AccelLabel
-instance LabelClass AccelLabel
-instance MiscClass AccelLabel
-instance ObjectClass AccelLabel
-instance WidgetClass AccelLabel
-class LabelClass o => AccelLabelClass o
-instance AccelLabelClass AccelLabel
-castToAccelLabel :: GObjectClass obj => obj -> AccelLabel
-toAccelLabel :: AccelLabelClass o => o -> AccelLabel
-accelLabelNew :: String -> IO AccelLabel
-accelLabelSetAccelWidget :: (AccelLabelClass self, WidgetClass accelWidget) => self -> accelWidget -> IO ()
-accelLabelGetAccelWidget :: AccelLabelClass self => self -> IO (Maybe Widget)
-accelLabelAccelWidget :: (AccelLabelClass self, WidgetClass accelWidget) => ReadWriteAttr self (Maybe Widget) accelWidget
-
-module Graphics.UI.Gtk.Display.ProgressBar
-data ProgressBar
-instance GObjectClass ProgressBar
-instance ObjectClass ProgressBar
-instance ProgressBarClass ProgressBar
-instance WidgetClass ProgressBar
-class WidgetClass o => ProgressBarClass o
-instance ProgressBarClass ProgressBar
-castToProgressBar :: GObjectClass obj => obj -> ProgressBar
-toProgressBar :: ProgressBarClass o => o -> ProgressBar
-progressBarNew :: IO ProgressBar
-progressBarPulse :: ProgressBarClass self => self -> IO ()
-progressBarSetText :: ProgressBarClass self => self -> String -> IO ()
-progressBarSetFraction :: ProgressBarClass self => self -> Double -> IO ()
-progressBarSetPulseStep :: ProgressBarClass self => self -> Double -> IO ()
-progressBarGetFraction :: ProgressBarClass self => self -> IO Double
-progressBarGetPulseStep :: ProgressBarClass self => self -> IO Double
-progressBarGetText :: ProgressBarClass self => self -> IO (Maybe String)
-data ProgressBarOrientation
-ProgressLeftToRight :: ProgressBarOrientation
-ProgressRightToLeft :: ProgressBarOrientation
-ProgressBottomToTop :: ProgressBarOrientation
-ProgressTopToBottom :: ProgressBarOrientation
-instance Enum ProgressBarOrientation
-instance Eq ProgressBarOrientation
-progressBarSetOrientation :: ProgressBarClass self => self -> ProgressBarOrientation -> IO ()
-progressBarGetOrientation :: ProgressBarClass self => self -> IO ProgressBarOrientation
-progressBarSetEllipsize :: ProgressBarClass self => self -> EllipsizeMode -> IO ()
-progressBarGetEllipsize :: ProgressBarClass self => self -> IO EllipsizeMode
-progressBarOrientation :: ProgressBarClass self => Attr self ProgressBarOrientation
-progressBarDiscreteBlocks :: ProgressBarClass self => Attr self Int
-progressBarFraction :: ProgressBarClass self => Attr self Double
-progressBarPulseStep :: ProgressBarClass self => Attr self Double
-progressBarText :: ProgressBarClass self => ReadWriteAttr self (Maybe String) String
-progressBarEllipsize :: ProgressBarClass self => Attr self EllipsizeMode
-
-module Graphics.UI.Gtk.Display.Statusbar
-data Statusbar
-instance BoxClass Statusbar
-instance ContainerClass Statusbar
-instance GObjectClass Statusbar
-instance HBoxClass Statusbar
-instance ObjectClass Statusbar
-instance StatusbarClass Statusbar
-instance WidgetClass Statusbar
-class HBoxClass o => StatusbarClass o
-instance StatusbarClass Statusbar
-castToStatusbar :: GObjectClass obj => obj -> Statusbar
-toStatusbar :: StatusbarClass o => o -> Statusbar
-statusbarNew :: IO Statusbar
-statusbarGetContextId :: StatusbarClass self => self -> String -> IO ContextId
-statusbarPush :: StatusbarClass self => self -> ContextId -> String -> IO MessageId
-statusbarPop :: StatusbarClass self => self -> ContextId -> IO ()
-statusbarRemove :: StatusbarClass self => self -> ContextId -> MessageId -> IO ()
-statusbarSetHasResizeGrip :: StatusbarClass self => self -> Bool -> IO ()
-statusbarGetHasResizeGrip :: StatusbarClass self => self -> IO Bool
-statusbarHasResizeGrip :: StatusbarClass self => Attr self Bool
-onTextPopped :: StatusbarClass self => self -> (ContextId -> String -> IO ()) -> IO (ConnectId self)
-afterTextPopped :: StatusbarClass self => self -> (ContextId -> String -> IO ()) -> IO (ConnectId self)
-onTextPushed :: StatusbarClass self => self -> (ContextId -> String -> IO ()) -> IO (ConnectId self)
-afterTextPushed :: StatusbarClass self => self -> (ContextId -> String -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Embedding.Plug
-data Plug
-instance BinClass Plug
-instance ContainerClass Plug
-instance GObjectClass Plug
-instance ObjectClass Plug
-instance PlugClass Plug
-instance WidgetClass Plug
-instance WindowClass Plug
-class WindowClass o => PlugClass o
-instance PlugClass Plug
-castToPlug :: GObjectClass obj => obj -> Plug
-toPlug :: PlugClass o => o -> Plug
-type NativeWindowId = Word32
-plugNew :: Maybe NativeWindowId -> IO Plug
-plugGetId :: PlugClass self => self -> IO NativeWindowId
-onEmbedded :: PlugClass self => self -> IO () -> IO (ConnectId self)
-afterEmbedded :: PlugClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Embedding.Socket
-data Socket
-instance ContainerClass Socket
-instance GObjectClass Socket
-instance ObjectClass Socket
-instance SocketClass Socket
-instance WidgetClass Socket
-class ContainerClass o => SocketClass o
-instance SocketClass Socket
-castToSocket :: GObjectClass obj => obj -> Socket
-toSocket :: SocketClass o => o -> Socket
-type NativeWindowId = Word32
-socketNew :: IO Socket
-socketHasPlug :: SocketClass s => s -> IO Bool
-socketAddId :: SocketClass self => self -> NativeWindowId -> IO ()
-socketGetId :: SocketClass self => self -> IO NativeWindowId
-onPlugAdded :: SocketClass self => self -> IO () -> IO (ConnectId self)
-afterPlugAdded :: SocketClass self => self -> IO () -> IO (ConnectId self)
-onPlugRemoved :: SocketClass self => self -> IO () -> IO (ConnectId self)
-afterPlugRemoved :: SocketClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Entry.Editable
-data Editable
-instance EditableClass Editable
-instance GObjectClass Editable
-class GObjectClass o => EditableClass o
-instance EditableClass Editable
-instance EditableClass Entry
-instance EditableClass SpinButton
-castToEditable :: GObjectClass obj => obj -> Editable
-toEditable :: EditableClass o => o -> Editable
-editableSelectRegion :: EditableClass self => self -> Int -> Int -> IO ()
-editableGetSelectionBounds :: EditableClass self => self -> IO (Int, Int)
-editableInsertText :: EditableClass self => self -> String -> Int -> IO Int
-editableDeleteText :: EditableClass self => self -> Int -> Int -> IO ()
-editableGetChars :: EditableClass self => self -> Int -> Int -> IO String
-editableCutClipboard :: EditableClass self => self -> IO ()
-editableCopyClipboard :: EditableClass self => self -> IO ()
-editablePasteClipboard :: EditableClass self => self -> IO ()
-editableDeleteSelection :: EditableClass self => self -> IO ()
-editableSetEditable :: EditableClass self => self -> Bool -> IO ()
-editableGetEditable :: EditableClass self => self -> IO Bool
-editableSetPosition :: EditableClass self => self -> Int -> IO ()
-editableGetPosition :: EditableClass self => self -> IO Int
-editablePosition :: EditableClass self => Attr self Int
-editableEditable :: EditableClass self => Attr self Bool
-onEditableChanged :: EditableClass ec => ec -> IO () -> IO (ConnectId ec)
-afterEditableChanged :: EditableClass ec => ec -> IO () -> IO (ConnectId ec)
-onDeleteText :: EditableClass self => self -> (Int -> Int -> IO ()) -> IO (ConnectId self)
-afterDeleteText :: EditableClass self => self -> (Int -> Int -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Entry.Entry
-data Entry
-instance EditableClass Entry
-instance EntryClass Entry
-instance GObjectClass Entry
-instance ObjectClass Entry
-instance WidgetClass Entry
-class WidgetClass o => EntryClass o
-instance EntryClass Entry
-instance EntryClass SpinButton
-castToEntry :: GObjectClass obj => obj -> Entry
-toEntry :: EntryClass o => o -> Entry
-entryNew :: IO Entry
-entrySetText :: EntryClass self => self -> String -> IO ()
-entryGetText :: EntryClass self => self -> IO String
-entryAppendText :: EntryClass self => self -> String -> IO ()
-entryPrependText :: EntryClass self => self -> String -> IO ()
-entrySetVisibility :: EntryClass self => self -> Bool -> IO ()
-entryGetVisibility :: EntryClass self => self -> IO Bool
-entrySetInvisibleChar :: EntryClass self => self -> Char -> IO ()
-entryGetInvisibleChar :: EntryClass self => self -> IO Char
-entrySetMaxLength :: EntryClass self => self -> Int -> IO ()
-entryGetMaxLength :: EntryClass self => self -> IO Int
-entryGetActivatesDefault :: EntryClass self => self -> IO Bool
-entrySetActivatesDefault :: EntryClass self => self -> Bool -> IO ()
-entryGetHasFrame :: EntryClass self => self -> IO Bool
-entrySetHasFrame :: EntryClass self => self -> Bool -> IO ()
-entryGetWidthChars :: EntryClass self => self -> IO Int
-entrySetWidthChars :: EntryClass self => self -> Int -> IO ()
-entrySetAlignment :: EntryClass self => self -> Float -> IO ()
-entryGetAlignment :: EntryClass self => self -> IO Float
-entrySetCompletion :: EntryClass self => self -> EntryCompletion -> IO ()
-entryGetCompletion :: EntryClass self => self -> IO EntryCompletion
-entryCursorPosition :: EntryClass self => ReadAttr self Int
-entrySelectionBound :: EntryClass self => ReadAttr self Int
-entryEditable :: EntryClass self => Attr self Bool
-entryMaxLength :: EntryClass self => Attr self Int
-entryVisibility :: EntryClass self => Attr self Bool
-entryHasFrame :: EntryClass self => Attr self Bool
-entryInvisibleChar :: EntryClass self => Attr self Char
-entryActivatesDefault :: EntryClass self => Attr self Bool
-entryWidthChars :: EntryClass self => Attr self Int
-entryScrollOffset :: EntryClass self => ReadAttr self Int
-entryText :: EntryClass self => Attr self String
-entryXalign :: EntryClass self => Attr self Float
-entryAlignment :: EntryClass self => Attr self Float
-entryCompletion :: EntryClass self => Attr self EntryCompletion
-onEntryActivate :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-afterEntryActivate :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-onCopyClipboard :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-afterCopyClipboard :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-onCutClipboard :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-afterCutClipboard :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-onPasteClipboard :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-afterPasteClipboard :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-onInsertAtCursor :: EntryClass ec => ec -> (String -> IO ()) -> IO (ConnectId ec)
-afterInsertAtCursor :: EntryClass ec => ec -> (String -> IO ()) -> IO (ConnectId ec)
-onToggleOverwrite :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-afterToggleOverwrite :: EntryClass ec => ec -> IO () -> IO (ConnectId ec)
-
-module Graphics.UI.Gtk.Entry.HScale
-data HScale
-instance GObjectClass HScale
-instance HScaleClass HScale
-instance ObjectClass HScale
-instance RangeClass HScale
-instance ScaleClass HScale
-instance WidgetClass HScale
-class ScaleClass o => HScaleClass o
-instance HScaleClass HScale
-castToHScale :: GObjectClass obj => obj -> HScale
-toHScale :: HScaleClass o => o -> HScale
-hScaleNew :: Adjustment -> IO HScale
-hScaleNewWithRange :: Double -> Double -> Double -> IO HScale
-
-module Graphics.UI.Gtk.Entry.VScale
-data VScale
-instance GObjectClass VScale
-instance ObjectClass VScale
-instance RangeClass VScale
-instance ScaleClass VScale
-instance VScaleClass VScale
-instance WidgetClass VScale
-class ScaleClass o => VScaleClass o
-instance VScaleClass VScale
-castToVScale :: GObjectClass obj => obj -> VScale
-toVScale :: VScaleClass o => o -> VScale
-vScaleNew :: Adjustment -> IO VScale
-vScaleNewWithRange :: Double -> Double -> Double -> IO VScale
-
-module Graphics.UI.Gtk.General.General
-initGUI :: IO [String]
-eventsPending :: IO Int
-mainGUI :: IO ()
-mainLevel :: IO Int
-mainQuit :: IO ()
-mainIteration :: IO Bool
-mainIterationDo :: Bool -> IO Bool
-grabAdd :: WidgetClass wd => wd -> IO ()
-grabGetCurrent :: IO (Maybe Widget)
-grabRemove :: WidgetClass w => w -> IO ()
-type Priority = Int
-priorityLow :: Int
-priorityDefaultIdle :: Int
-priorityHighIdle :: Int
-priorityDefault :: Int
-priorityHigh :: Int
-timeoutAdd :: IO Bool -> Int -> IO HandlerId
-timeoutAddFull :: IO Bool -> Priority -> Int -> IO HandlerId
-timeoutRemove :: HandlerId -> IO ()
-idleAdd :: IO Bool -> Priority -> IO HandlerId
-idleRemove :: HandlerId -> IO ()
-inputAdd :: FD -> [IOCondition] -> Priority -> IO Bool -> IO HandlerId
-inputRemove :: HandlerId -> IO ()
-data IOCondition
-instance Bounded IOCondition
-instance Enum IOCondition
-instance Eq IOCondition
-instance Flags IOCondition
-type HandlerId = CUInt
-
-module Graphics.UI.Gtk.General.Structs
-type Point = (Int, Int)
-data Rectangle
-Rectangle :: Int -> Int -> Int -> Int -> Rectangle
-instance Storable Rectangle
-data Color
-Color :: Word16 -> Word16 -> Word16 -> Color
-instance Storable Color
-data GCValues
-GCValues :: Color -> Color -> Function -> Fill -> Maybe Pixmap -> Maybe Pixmap -> Maybe Pixmap -> SubwindowMode -> Int -> Int -> Int -> Int -> Bool -> Int -> LineStyle -> CapStyle -> JoinStyle -> GCValues
-foreground :: GCValues -> Color
-background :: GCValues -> Color
-function :: GCValues -> Function
-fill :: GCValues -> Fill
-tile :: GCValues -> Maybe Pixmap
-stipple :: GCValues -> Maybe Pixmap
-clipMask :: GCValues -> Maybe Pixmap
-subwindowMode :: GCValues -> SubwindowMode
-tsXOrigin :: GCValues -> Int
-tsYOrigin :: GCValues -> Int
-clipXOrigin :: GCValues -> Int
-clipYOrigin :: GCValues -> Int
-graphicsExposure :: GCValues -> Bool
-lineWidth :: GCValues -> Int
-lineStyle :: GCValues -> LineStyle
-capStyle :: GCValues -> CapStyle
-joinStyle :: GCValues -> JoinStyle
-instance Storable GCValues
-pokeGCValues :: Ptr GCValues -> GCValues -> IO CInt
-newGCValues :: GCValues
-widgetGetState :: WidgetClass w => w -> IO StateType
-widgetGetSavedState :: WidgetClass w => w -> IO StateType
-type Allocation = Rectangle
-data Requisition
-Requisition :: Int -> Int -> Requisition
-instance Storable Requisition
-treeIterSize :: Int
-textIterSize :: Int
-inputError :: Int32
-dialogGetUpper :: DialogClass dc => dc -> IO VBox
-dialogGetActionArea :: DialogClass dc => dc -> IO HBox
-fileSelectionGetButtons :: FileSelectionClass fsel => fsel -> IO (Button, Button)
-data ResponseId
-ResponseNone :: ResponseId
-ResponseReject :: ResponseId
-ResponseAccept :: ResponseId
-ResponseDeleteEvent :: ResponseId
-ResponseOk :: ResponseId
-ResponseCancel :: ResponseId
-ResponseClose :: ResponseId
-ResponseYes :: ResponseId
-ResponseNo :: ResponseId
-ResponseApply :: ResponseId
-ResponseHelp :: ResponseId
-ResponseUser :: Int -> ResponseId
-instance Show ResponseId
-fromResponse :: Integral a => ResponseId -> a
-toResponse :: Integral a => a -> ResponseId
-toolbarChildButton :: CInt
-toolbarChildToggleButton :: CInt
-toolbarChildRadioButton :: CInt
-type IconSize = Int
-iconSizeInvalid :: IconSize
-iconSizeMenu :: IconSize
-iconSizeSmallToolbar :: IconSize
-iconSizeLargeToolbar :: IconSize
-iconSizeButton :: IconSize
-iconSizeDialog :: IconSize
-comboGetList :: Combo -> IO List
-drawingAreaGetDrawWindow :: DrawingArea -> IO DrawWindow
-drawingAreaGetSize :: DrawingArea -> IO (Int, Int)
-layoutGetDrawWindow :: Layout -> IO DrawWindow
-pangoScale :: Int
-data PangoDirection
-PangoDirectionLtr :: PangoDirection
-PangoDirectionRtl :: PangoDirection
-PangoDirectionWeakLtr :: PangoDirection
-PangoDirectionWeakRtl :: PangoDirection
-PangoDirectionNeutral :: PangoDirection
-instance Enum PangoDirection
-instance Eq PangoDirection
-instance Ord PangoDirection
-pangodirToLevel :: PangoDirection -> Int
-setAttrPos :: UTFCorrection -> Int -> Int -> IO (Ptr ()) -> IO (Ptr ())
-pangoItemRawGetFont :: Ptr pangoItem -> IO Font
-pangoItemRawGetLanguage :: Ptr pangoItem -> IO (Ptr CChar)
-pangoItemRawAnalysis :: Ptr pangoItem -> Ptr pangoAnalysis
-pangoItemRawGetLevel :: Ptr pangoItem -> IO Bool
-styleGetForeground :: StateType -> Style -> IO GC
-styleGetBackground :: StateType -> Style -> IO GC
-styleGetLight :: StateType -> Style -> IO GC
-styleGetMiddle :: StateType -> Style -> IO GC
-styleGetDark :: StateType -> Style -> IO GC
-styleGetText :: StateType -> Style -> IO GC
-styleGetBase :: StateType -> Style -> IO GC
-styleGetAntiAliasing :: StateType -> Style -> IO GC
-
-module Graphics.UI.Gtk.ActionMenuToolbar.Action
-data Action
-instance ActionClass Action
-instance GObjectClass Action
-class GObjectClass o => ActionClass o
-instance ActionClass Action
-instance ActionClass RadioAction
-instance ActionClass ToggleAction
-castToAction :: GObjectClass obj => obj -> Action
-toAction :: ActionClass o => o -> Action
-actionNew :: String -> String -> Maybe String -> Maybe String -> IO Action
-actionGetName :: ActionClass self => self -> IO String
-actionIsSensitive :: ActionClass self => self -> IO Bool
-actionGetSensitive :: ActionClass self => self -> IO Bool
-actionSetSensitive :: ActionClass self => self -> Bool -> IO ()
-actionIsVisible :: ActionClass self => self -> IO Bool
-actionGetVisible :: ActionClass self => self -> IO Bool
-actionSetVisible :: ActionClass self => self -> Bool -> IO ()
-actionActivate :: ActionClass self => self -> IO ()
-actionCreateMenuItem :: ActionClass self => self -> IO Widget
-actionCreateToolItem :: ActionClass self => self -> IO Widget
-actionConnectProxy :: (ActionClass self, WidgetClass proxy) => self -> proxy -> IO ()
-actionDisconnectProxy :: (ActionClass self, WidgetClass proxy) => self -> proxy -> IO ()
-actionGetProxies :: ActionClass self => self -> IO [Widget]
-actionConnectAccelerator :: ActionClass self => self -> IO ()
-actionDisconnectAccelerator :: ActionClass self => self -> IO ()
-actionGetAccelPath :: ActionClass self => self -> IO (Maybe String)
-actionSetAccelPath :: ActionClass self => self -> String -> IO ()
-actionSetAccelGroup :: ActionClass self => self -> AccelGroup -> IO ()
-actionName :: ActionClass self => Attr self String
-actionLabel :: ActionClass self => Attr self String
-actionShortLabel :: ActionClass self => Attr self String
-actionTooltip :: ActionClass self => Attr self (Maybe String)
-actionStockId :: ActionClass self => Attr self (Maybe String)
-actionVisibleHorizontal :: ActionClass self => Attr self Bool
-actionVisibleOverflown :: ActionClass self => Attr self Bool
-actionVisibleVertical :: ActionClass self => Attr self Bool
-actionIsImportant :: ActionClass self => Attr self Bool
-actionHideIfEmpty :: ActionClass self => Attr self Bool
-actionSensitive :: ActionClass self => Attr self Bool
-actionVisible :: ActionClass self => Attr self Bool
-actionAccelPath :: ActionClass self => ReadWriteAttr self (Maybe String) String
-onActionActivate :: ActionClass self => self -> IO () -> IO (ConnectId self)
-afterActionActivate :: ActionClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.ActionMenuToolbar.ActionGroup
-data ActionGroup
-instance ActionGroupClass ActionGroup
-instance GObjectClass ActionGroup
-class GObjectClass o => ActionGroupClass o
-instance ActionGroupClass ActionGroup
-castToActionGroup :: GObjectClass obj => obj -> ActionGroup
-toActionGroup :: ActionGroupClass o => o -> ActionGroup
-actionGroupNew :: String -> IO ActionGroup
-actionGroupGetName :: ActionGroup -> IO String
-actionGroupGetSensitive :: ActionGroup -> IO Bool
-actionGroupSetSensitive :: ActionGroup -> Bool -> IO ()
-actionGroupGetVisible :: ActionGroup -> IO Bool
-actionGroupSetVisible :: ActionGroup -> Bool -> IO ()
-actionGroupGetAction :: ActionGroup -> String -> IO (Maybe Action)
-actionGroupListActions :: ActionGroup -> IO [Action]
-actionGroupAddAction :: ActionClass action => ActionGroup -> action -> IO ()
-actionGroupAddActionWithAccel :: ActionClass action => ActionGroup -> action -> Maybe String -> IO ()
-actionGroupRemoveAction :: ActionClass action => ActionGroup -> action -> IO ()
-actionGroupAddActions :: ActionGroup -> [ActionEntry] -> IO ()
-actionGroupAddToggleActions :: ActionGroup -> [ToggleActionEntry] -> IO ()
-actionGroupAddRadioActions :: ActionGroup -> [RadioActionEntry] -> Int -> (RadioAction -> IO ()) -> IO ()
-actionGroupSetTranslateFunc :: ActionGroup -> (String -> IO String) -> IO ()
-actionGroupSetTranslationDomain :: ActionGroup -> String -> IO ()
-actionGroupTranslateString :: ActionGroup -> String -> IO String
-actionGroupName :: Attr ActionGroup String
-actionGroupSensitive :: Attr ActionGroup Bool
-actionGroupVisible :: Attr ActionGroup Bool
-
-module Graphics.UI.Gtk.Display.Image
-data Image
-instance GObjectClass Image
-instance ImageClass Image
-instance MiscClass Image
-instance ObjectClass Image
-instance WidgetClass Image
-class MiscClass o => ImageClass o
-instance ImageClass Image
-castToImage :: GObjectClass obj => obj -> Image
-toImage :: ImageClass o => o -> Image
-imageNewFromFile :: FilePath -> IO Image
-imageNewFromPixbuf :: Pixbuf -> IO Image
-imageNewFromStock :: String -> IconSize -> IO Image
-imageNew :: IO Image
-imageNewFromIconName :: String -> IconSize -> IO Image
-imageGetPixbuf :: Image -> IO Pixbuf
-imageSetFromPixbuf :: Image -> Pixbuf -> IO ()
-imageSetFromFile :: Image -> FilePath -> IO ()
-imageSetFromStock :: Image -> String -> IconSize -> IO ()
-imageSetFromIconName :: Image -> String -> IconSize -> IO ()
-imageSetPixelSize :: Image -> Int -> IO ()
-imageGetPixelSize :: Image -> IO Int
-imageClear :: Image -> IO ()
-type IconSize = Int
-iconSizeMenu :: IconSize
-iconSizeSmallToolbar :: IconSize
-iconSizeLargeToolbar :: IconSize
-iconSizeButton :: IconSize
-iconSizeDialog :: IconSize
-imagePixbuf :: PixbufClass pixbuf => ReadWriteAttr Image Pixbuf pixbuf
-imagePixmap :: PixmapClass pixmap => ReadWriteAttr Image Pixmap pixmap
-imageImage :: ImageClass image => ReadWriteAttr Image Image image
-imageMask :: PixmapClass pixmap => ReadWriteAttr Image Pixmap pixmap
-imageFile :: Attr Image String
-imageStock :: Attr Image String
-imageIconSize :: Attr Image Int
-imagePixelSize :: Attr Image Int
-imageIconName :: Attr Image String
-imageStorageType :: ReadAttr Image ImageType
-
-module Graphics.UI.Gtk.Entry.SpinButton
-data SpinButton
-instance EditableClass SpinButton
-instance EntryClass SpinButton
-instance GObjectClass SpinButton
-instance ObjectClass SpinButton
-instance SpinButtonClass SpinButton
-instance WidgetClass SpinButton
-class EntryClass o => SpinButtonClass o
-instance SpinButtonClass SpinButton
-castToSpinButton :: GObjectClass obj => obj -> SpinButton
-toSpinButton :: SpinButtonClass o => o -> SpinButton
-spinButtonNew :: Adjustment -> Double -> Int -> IO SpinButton
-spinButtonNewWithRange :: Double -> Double -> Double -> IO SpinButton
-spinButtonConfigure :: SpinButtonClass self => self -> Adjustment -> Double -> Int -> IO ()
-spinButtonSetAdjustment :: SpinButtonClass self => self -> Adjustment -> IO ()
-spinButtonGetAdjustment :: SpinButtonClass self => self -> IO Adjustment
-spinButtonSetDigits :: SpinButtonClass self => self -> Int -> IO ()
-spinButtonGetDigits :: SpinButtonClass self => self -> IO Int
-spinButtonSetIncrements :: SpinButtonClass self => self -> Double -> Double -> IO ()
-spinButtonGetIncrements :: SpinButtonClass self => self -> IO (Double, Double)
-spinButtonSetRange :: SpinButtonClass self => self -> Double -> Double -> IO ()
-spinButtonGetRange :: SpinButtonClass self => self -> IO (Double, Double)
-spinButtonGetValue :: SpinButtonClass self => self -> IO Double
-spinButtonGetValueAsInt :: SpinButtonClass self => self -> IO Int
-spinButtonSetValue :: SpinButtonClass self => self -> Double -> IO ()
-data SpinButtonUpdatePolicy
-UpdateAlways :: SpinButtonUpdatePolicy
-UpdateIfValid :: SpinButtonUpdatePolicy
-instance Enum SpinButtonUpdatePolicy
-instance Eq SpinButtonUpdatePolicy
-spinButtonSetUpdatePolicy :: SpinButtonClass self => self -> SpinButtonUpdatePolicy -> IO ()
-spinButtonGetUpdatePolicy :: SpinButtonClass self => self -> IO SpinButtonUpdatePolicy
-spinButtonSetNumeric :: SpinButtonClass self => self -> Bool -> IO ()
-spinButtonGetNumeric :: SpinButtonClass self => self -> IO Bool
-data SpinType
-SpinStepForward :: SpinType
-SpinStepBackward :: SpinType
-SpinPageForward :: SpinType
-SpinPageBackward :: SpinType
-SpinHome :: SpinType
-SpinEnd :: SpinType
-SpinUserDefined :: SpinType
-instance Enum SpinType
-instance Eq SpinType
-spinButtonSpin :: SpinButtonClass self => self -> SpinType -> Double -> IO ()
-spinButtonSetWrap :: SpinButtonClass self => self -> Bool -> IO ()
-spinButtonGetWrap :: SpinButtonClass self => self -> IO Bool
-spinButtonSetSnapToTicks :: SpinButtonClass self => self -> Bool -> IO ()
-spinButtonGetSnapToTicks :: SpinButtonClass self => self -> IO Bool
-spinButtonUpdate :: SpinButtonClass self => self -> IO ()
-spinButtonAdjustment :: SpinButtonClass self => Attr self Adjustment
-spinButtonClimbRate :: SpinButtonClass self => Attr self Double
-spinButtonDigits :: SpinButtonClass self => Attr self Int
-spinButtonSnapToTicks :: SpinButtonClass self => Attr self Bool
-spinButtonNumeric :: SpinButtonClass self => Attr self Bool
-spinButtonWrap :: SpinButtonClass self => Attr self Bool
-spinButtonUpdatePolicy :: SpinButtonClass self => Attr self SpinButtonUpdatePolicy
-spinButtonValue :: SpinButtonClass self => Attr self Double
-onInput :: SpinButtonClass sb => sb -> IO (Maybe Double) -> IO (ConnectId sb)
-afterInput :: SpinButtonClass sb => sb -> IO (Maybe Double) -> IO (ConnectId sb)
-onOutput :: SpinButtonClass sb => sb -> IO Bool -> IO (ConnectId sb)
-afterOutput :: SpinButtonClass sb => sb -> IO Bool -> IO (ConnectId sb)
-onValueSpinned :: SpinButtonClass sb => sb -> IO () -> IO (ConnectId sb)
-afterValueSpinned :: SpinButtonClass sb => sb -> IO () -> IO (ConnectId sb)
-
-module Graphics.UI.Gtk.Gdk.Pixbuf
-data Pixbuf
-instance GObjectClass Pixbuf
-instance PixbufClass Pixbuf
-class GObjectClass o => PixbufClass o
-instance PixbufClass Pixbuf
-data PixbufError
-PixbufErrorCorruptImage :: PixbufError
-PixbufErrorInsufficientMemory :: PixbufError
-PixbufErrorBadOption :: PixbufError
-PixbufErrorUnknownType :: PixbufError
-PixbufErrorUnsupportedOperation :: PixbufError
-PixbufErrorFailed :: PixbufError
-instance Enum PixbufError
-instance GErrorClass PixbufError
-data Colorspace
-ColorspaceRgb :: Colorspace
-instance Enum Colorspace
-pixbufGetColorSpace :: Pixbuf -> IO Colorspace
-pixbufGetNChannels :: Pixbuf -> IO Int
-pixbufGetHasAlpha :: Pixbuf -> IO Bool
-pixbufGetBitsPerSample :: Pixbuf -> IO Int
-data PixbufData i e
-instance HasBounds PixbufData
-instance Storable e => MArray PixbufData e IO
-pixbufGetPixels :: (Ix i, Num i, Storable e) => Pixbuf -> IO (PixbufData i e)
-pixbufGetWidth :: Pixbuf -> IO Int
-pixbufGetHeight :: Pixbuf -> IO Int
-pixbufGetRowstride :: Pixbuf -> IO Int
-pixbufGetOption :: Pixbuf -> String -> IO (Maybe String)
-pixbufNewFromFile :: FilePath -> IO (Either (PixbufError, String) Pixbuf)
-type ImageType = String
-pixbufGetFormats :: [ImageType]
-pixbufSave :: Pixbuf -> FilePath -> ImageType -> [(String, String)] -> IO (Maybe (PixbufError, String))
-pixbufNew :: Colorspace -> Bool -> Int -> Int -> Int -> IO Pixbuf
-pixbufNewFromXPMData :: [String] -> IO Pixbuf
-data InlineImage
-pixbufNewFromInline :: Ptr InlineImage -> IO Pixbuf
-pixbufNewSubpixbuf :: Pixbuf -> Int -> Int -> Int -> Int -> IO Pixbuf
-pixbufCopy :: Pixbuf -> IO Pixbuf
-data InterpType
-InterpNearest :: InterpType
-InterpTiles :: InterpType
-InterpBilinear :: InterpType
-InterpHyper :: InterpType
-instance Enum InterpType
-pixbufScaleSimple :: Pixbuf -> Int -> Int -> InterpType -> IO Pixbuf
-pixbufScale :: Pixbuf -> Pixbuf -> Int -> Int -> Int -> Int -> Double -> Double -> Double -> Double -> InterpType -> IO ()
-pixbufComposite :: Pixbuf -> Pixbuf -> Int -> Int -> Int -> Int -> Double -> Double -> Double -> Double -> InterpType -> Word8 -> IO ()
-pixbufAddAlpha :: Pixbuf -> Maybe (Word8, Word8, Word8) -> IO Pixbuf
-pixbufCopyArea :: Pixbuf -> Int -> Int -> Int -> Int -> Pixbuf -> Int -> Int -> IO ()
-pixbufFill :: Pixbuf -> Word8 -> Word8 -> Word8 -> Word8 -> IO ()
-pixbufGetFromDrawable :: DrawableClass d => d -> Rectangle -> IO (Maybe Pixbuf)
-
-module Graphics.UI.Gtk.Gdk.Region
-makeNewRegion :: Ptr Region -> IO Region
-newtype Region
-Region :: ForeignPtr Region -> Region
-regionNew :: IO Region
-data FillRule
-EvenOddRule :: FillRule
-WindingRule :: FillRule
-instance Enum FillRule
-regionPolygon :: [Point] -> FillRule -> IO Region
-regionCopy :: Region -> IO Region
-regionRectangle :: Rectangle -> IO Region
-regionGetClipbox :: Region -> IO Rectangle
-regionGetRectangles :: Region -> IO [Rectangle]
-regionEmpty :: Region -> IO Bool
-regionEqual :: Region -> Region -> IO Bool
-regionPointIn :: Region -> Point -> IO Bool
-data OverlapType
-OverlapRectangleIn :: OverlapType
-OverlapRectangleOut :: OverlapType
-OverlapRectanglePart :: OverlapType
-instance Enum OverlapType
-regionRectIn :: Region -> Rectangle -> IO OverlapType
-regionOffset :: Region -> Int -> Int -> IO ()
-regionShrink :: Region -> Int -> Int -> IO ()
-regionUnionWithRect :: Region -> Rectangle -> IO ()
-regionIntersect :: Region -> Region -> IO ()
-regionUnion :: Region -> Region -> IO ()
-regionSubtract :: Region -> Region -> IO ()
-regionXor :: Region -> Region -> IO ()
-
-module Graphics.UI.Gtk.Gdk.Events
-data Modifier
-Shift :: Modifier
-Control :: Modifier
-Alt :: Modifier
-Apple :: Modifier
-Compose :: Modifier
-instance Bounded Modifier
-instance Enum Modifier
-instance Eq Modifier
-instance Flags Modifier
-instance Ord Modifier
-data Event
-Event :: Bool -> Event
-eventSent :: Event -> Bool
-Expose :: Bool -> Rectangle -> Region -> Int -> Event
-eventSent :: Event -> Bool
-eventArea :: Event -> Rectangle
-eventRegion :: Event -> Region
-eventCount :: Event -> Int
-Motion :: Bool -> Word32 -> Double -> Double -> [Modifier] -> Bool -> Double -> Double -> Event
-eventSent :: Event -> Bool
-eventTime :: Event -> Word32
-eventX :: Event -> Double
-eventY :: Event -> Double
-eventModifier :: Event -> [Modifier]
-eventIsHint :: Event -> Bool
-eventXRoot :: Event -> Double
-eventYRoot :: Event -> Double
-Button :: Bool -> Click -> Word32 -> Double -> Double -> [Modifier] -> MouseButton -> Double -> Double -> Event
-eventSent :: Event -> Bool
-eventClick :: Event -> Click
-eventTime :: Event -> Word32
-eventX :: Event -> Double
-eventY :: Event -> Double
-eventModifier :: Event -> [Modifier]
-eventButton :: Event -> MouseButton
-eventXRoot :: Event -> Double
-eventYRoot :: Event -> Double
-Key :: Bool -> Bool -> Word32 -> [Modifier] -> Bool -> Bool -> Bool -> String -> Maybe Char -> Event
-eventRelease :: Event -> Bool
-eventSent :: Event -> Bool
-eventTime :: Event -> Word32
-eventModifier :: Event -> [Modifier]
-eventWithCapsLock :: Event -> Bool
-eventWithNumLock :: Event -> Bool
-eventWithScrollLock :: Event -> Bool
-eventKeyName :: Event -> String
-eventKeyChar :: Event -> Maybe Char
-Crossing :: Bool -> Word32 -> Double -> Double -> Double -> Double -> CrossingMode -> NotifyType -> [Modifier] -> Event
-eventSent :: Event -> Bool
-eventTime :: Event -> Word32
-eventX :: Event -> Double
-eventY :: Event -> Double
-eventXRoot :: Event -> Double
-eventYRoot :: Event -> Double
-eventCrossingMode :: Event -> CrossingMode
-eventNotifyType :: Event -> NotifyType
-eventModifier :: Event -> [Modifier]
-Focus :: Bool -> Bool -> Event
-eventSent :: Event -> Bool
-eventInFocus :: Event -> Bool
-Configure :: Bool -> Int -> Int -> Int -> Int -> Event
-eventSent :: Event -> Bool
-eventXParent :: Event -> Int
-eventYParent :: Event -> Int
-eventWidth :: Event -> Int
-eventHeight :: Event -> Int
-Visibility :: Bool -> VisibilityState -> Event
-eventSent :: Event -> Bool
-eventVisible :: Event -> VisibilityState
-Scroll :: Bool -> Word32 -> Double -> Double -> ScrollDirection -> Double -> Double -> Event
-eventSent :: Event -> Bool
-eventTime :: Event -> Word32
-eventX :: Event -> Double
-eventY :: Event -> Double
-eventDirection :: Event -> ScrollDirection
-eventXRoot :: Event -> Double
-eventYRoot :: Event -> Double
-WindowState :: Bool -> [WindowState] -> [WindowState] -> Event
-eventSent :: Event -> Bool
-eventWindowMask :: Event -> [WindowState]
-eventWindowState :: Event -> [WindowState]
-Proximity :: Bool -> Word32 -> Bool -> Event
-eventSent :: Event -> Bool
-eventTime :: Event -> Word32
-eventInContact :: Event -> Bool
-data VisibilityState
-VisibilityUnobscured :: VisibilityState
-VisibilityPartialObscured :: VisibilityState
-VisibilityFullyObscured :: VisibilityState
-instance Enum VisibilityState
-data CrossingMode
-CrossingNormal :: CrossingMode
-CrossingGrab :: CrossingMode
-CrossingUngrab :: CrossingMode
-instance Enum CrossingMode
-data NotifyType
-NotifyAncestor :: NotifyType
-NotifyVirtual :: NotifyType
-NotifyInferior :: NotifyType
-NotifyNonlinear :: NotifyType
-NotifyNonlinearVirtual :: NotifyType
-NotifyUnknown :: NotifyType
-instance Enum NotifyType
-data WindowState
-WindowStateWithdrawn :: WindowState
-WindowStateIconified :: WindowState
-WindowStateMaximized :: WindowState
-WindowStateSticky :: WindowState
-WindowStateFullscreen :: WindowState
-WindowStateAbove :: WindowState
-WindowStateBelow :: WindowState
-instance Bounded WindowState
-instance Enum WindowState
-instance Flags WindowState
-data ScrollDirection
-ScrollUp :: ScrollDirection
-ScrollDown :: ScrollDirection
-ScrollLeft :: ScrollDirection
-ScrollRight :: ScrollDirection
-instance Enum ScrollDirection
-data MouseButton
-LeftButton :: MouseButton
-MiddleButton :: MouseButton
-RightButton :: MouseButton
-instance Enum MouseButton
-instance Eq MouseButton
-instance Show MouseButton
-data Click
-SingleClick :: Click
-DoubleClick :: Click
-TripleClick :: Click
-ReleaseClick :: Click
-data Rectangle
-Rectangle :: Int -> Int -> Int -> Int -> Rectangle
-instance Storable Rectangle
-
-module Graphics.UI.Gtk.Gdk.DrawWindow
-data DrawWindow
-instance DrawWindowClass DrawWindow
-instance DrawableClass DrawWindow
-instance GObjectClass DrawWindow
-class DrawableClass o => DrawWindowClass o
-instance DrawWindowClass DrawWindow
-castToDrawWindow :: GObjectClass obj => obj -> DrawWindow
-data WindowState
-WindowStateWithdrawn :: WindowState
-WindowStateIconified :: WindowState
-WindowStateMaximized :: WindowState
-WindowStateSticky :: WindowState
-WindowStateFullscreen :: WindowState
-WindowStateAbove :: WindowState
-WindowStateBelow :: WindowState
-instance Bounded WindowState
-instance Enum WindowState
-instance Flags WindowState
-drawWindowGetState :: DrawWindowClass self => self -> IO [WindowState]
-drawWindowClear :: DrawWindowClass self => self -> IO ()
-drawWindowClearArea :: DrawWindowClass self => self -> Int -> Int -> Int -> Int -> IO ()
-drawWindowClearAreaExpose :: DrawWindowClass self => self -> Int -> Int -> Int -> Int -> IO ()
-drawWindowRaise :: DrawWindowClass self => self -> IO ()
-drawWindowLower :: DrawWindowClass self => self -> IO ()
-drawWindowBeginPaintRect :: DrawWindowClass self => self -> Rectangle -> IO ()
-drawWindowBeginPaintRegion :: DrawWindowClass self => self -> Region -> IO ()
-drawWindowEndPaint :: DrawWindowClass self => self -> IO ()
-drawWindowInvalidateRect :: DrawWindowClass self => self -> Rectangle -> Bool -> IO ()
-drawWindowInvalidateRegion :: DrawWindowClass self => self -> Region -> Bool -> IO ()
-drawWindowGetUpdateArea :: DrawWindowClass self => self -> IO (Maybe Region)
-drawWindowFreezeUpdates :: DrawWindowClass self => self -> IO ()
-drawWindowThawUpdates :: DrawWindowClass self => self -> IO ()
-drawWindowProcessUpdates :: DrawWindowClass self => self -> Bool -> IO ()
-drawWindowSetAcceptFocus :: DrawWindowClass self => self -> Bool -> IO ()
-drawWindowShapeCombineRegion :: DrawWindowClass self => self -> Maybe Region -> Int -> Int -> IO ()
-drawWindowSetChildShapes :: DrawWindowClass self => self -> IO ()
-drawWindowMergeChildShapes :: DrawWindowClass self => self -> IO ()
-drawWindowGetPointer :: DrawWindowClass self => self -> IO (Maybe (Bool, Int, Int, [Modifier]))
-
-module Graphics.UI.Gtk.General.StockItems
-data StockItem
-StockItem :: StockId -> String -> [Modifier] -> KeyVal -> String -> StockItem
-siStockId :: StockItem -> StockId
-siLabel :: StockItem -> String
-siModifier :: StockItem -> [Modifier]
-siKeyval :: StockItem -> KeyVal
-siTransDom :: StockItem -> String
-instance Storable StockItem
-type StockId = String
-siStockId :: StockItem -> StockId
-siLabel :: StockItem -> String
-siModifier :: StockItem -> [Modifier]
-siKeyval :: StockItem -> KeyVal
-siTransDom :: StockItem -> String
-stockAddItem :: [StockItem] -> IO ()
-stockLookupItem :: StockId -> IO (Maybe StockItem)
-stockListIds :: IO [StockId]
-stockAdd :: StockId
-stockApply :: StockId
-stockBold :: StockId
-stockCancel :: StockId
-stockCDROM :: StockId
-stockClear :: StockId
-stockClose :: StockId
-stockColorPicker :: StockId
-stockConvert :: StockId
-stockCopy :: StockId
-stockCut :: StockId
-stockDelete :: StockId
-stockDialogError :: StockId
-stockDialogInfo :: StockId
-stockDialogQuestion :: StockId
-stockDialogWarning :: StockId
-stockDnd :: StockId
-stockDndMultiple :: StockId
-stockExecute :: StockId
-stockFind :: StockId
-stockFindAndRelpace :: StockId
-stockFloppy :: StockId
-stockGotoBottom :: StockId
-stockGotoFirst :: StockId
-stockGotoLast :: StockId
-stockGotoTop :: StockId
-stockGoBack :: StockId
-stockGoDown :: StockId
-stockGoForward :: StockId
-stockGoUp :: StockId
-stockHelp :: StockId
-stockHome :: StockId
-stockIndex :: StockId
-stockItalic :: StockId
-stockJumpTo :: StockId
-stockJustifyCenter :: StockId
-stockJustifyFill :: StockId
-stockJustifyLeft :: StockId
-stockJustifyRight :: StockId
-stockMissingImage :: StockId
-stockNew :: StockId
-stockNo :: StockId
-stockOk :: StockId
-stockOpen :: StockId
-stockPaste :: StockId
-stockPreferences :: StockId
-stockPrint :: StockId
-stockPrintPreview :: StockId
-stockProperties :: StockId
-stockQuit :: StockId
-stockRedo :: StockId
-stockRefresh :: StockId
-stockRemove :: StockId
-stockRevertToSaved :: StockId
-stockSave :: StockId
-stockSaveAs :: StockId
-stockSelectColor :: StockId
-stockSelectFont :: StockId
-stockSortAscending :: StockId
-stockSortDescending :: StockId
-stockSpellCheck :: StockId
-stockStop :: StockId
-stockStrikethrough :: StockId
-stockUndelete :: StockId
-stockUnderline :: StockId
-stockUndo :: StockId
-stockYes :: StockId
-stockZoom100 :: StockId
-stockZoomFit :: StockId
-stockZoomIn :: StockId
-stockZoomOut :: StockId
-
-module Graphics.UI.Gtk.Gdk.GC
-data GC
-instance GCClass GC
-instance GObjectClass GC
-class GObjectClass o => GCClass o
-instance GCClass GC
-castToGC :: GObjectClass obj => obj -> GC
-gcNew :: DrawableClass d => d -> IO GC
-data GCValues
-GCValues :: Color -> Color -> Function -> Fill -> Maybe Pixmap -> Maybe Pixmap -> Maybe Pixmap -> SubwindowMode -> Int -> Int -> Int -> Int -> Bool -> Int -> LineStyle -> CapStyle -> JoinStyle -> GCValues
-foreground :: GCValues -> Color
-background :: GCValues -> Color
-function :: GCValues -> Function
-fill :: GCValues -> Fill
-tile :: GCValues -> Maybe Pixmap
-stipple :: GCValues -> Maybe Pixmap
-clipMask :: GCValues -> Maybe Pixmap
-subwindowMode :: GCValues -> SubwindowMode
-tsXOrigin :: GCValues -> Int
-tsYOrigin :: GCValues -> Int
-clipXOrigin :: GCValues -> Int
-clipYOrigin :: GCValues -> Int
-graphicsExposure :: GCValues -> Bool
-lineWidth :: GCValues -> Int
-lineStyle :: GCValues -> LineStyle
-capStyle :: GCValues -> CapStyle
-joinStyle :: GCValues -> JoinStyle
-instance Storable GCValues
-newGCValues :: GCValues
-data Color
-Color :: Word16 -> Word16 -> Word16 -> Color
-instance Storable Color
-foreground :: GCValues -> Color
-background :: GCValues -> Color
-data Function
-Copy :: Function
-Invert :: Function
-Xor :: Function
-Clear :: Function
-And :: Function
-AndReverse :: Function
-AndInvert :: Function
-Noop :: Function
-Or :: Function
-Equiv :: Function
-OrReverse :: Function
-CopyInvert :: Function
-OrInvert :: Function
-Nand :: Function
-Nor :: Function
-Set :: Function
-instance Enum Function
-function :: GCValues -> Function
-data Fill
-Solid :: Fill
-Tiled :: Fill
-Stippled :: Fill
-OpaqueStippled :: Fill
-instance Enum Fill
-fill :: GCValues -> Fill
-tile :: GCValues -> Maybe Pixmap
-stipple :: GCValues -> Maybe Pixmap
-clipMask :: GCValues -> Maybe Pixmap
-data SubwindowMode
-ClipByChildren :: SubwindowMode
-IncludeInferiors :: SubwindowMode
-instance Enum SubwindowMode
-subwindowMode :: GCValues -> SubwindowMode
-tsXOrigin :: GCValues -> Int
-tsYOrigin :: GCValues -> Int
-clipXOrigin :: GCValues -> Int
-clipYOrigin :: GCValues -> Int
-graphicsExposure :: GCValues -> Bool
-lineWidth :: GCValues -> Int
-data LineStyle
-LineSolid :: LineStyle
-LineOnOffDash :: LineStyle
-LineDoubleDash :: LineStyle
-instance Enum LineStyle
-lineStyle :: GCValues -> LineStyle
-data CapStyle
-CapNotLast :: CapStyle
-CapButt :: CapStyle
-CapRound :: CapStyle
-CapProjecting :: CapStyle
-instance Enum CapStyle
-capStyle :: GCValues -> CapStyle
-data JoinStyle
-JoinMiter :: JoinStyle
-JoinRound :: JoinStyle
-JoinBevel :: JoinStyle
-instance Enum JoinStyle
-joinStyle :: GCValues -> JoinStyle
-gcNewWithValues :: DrawableClass d => d -> GCValues -> IO GC
-gcSetValues :: GC -> GCValues -> IO ()
-gcGetValues :: GC -> IO GCValues
-gcSetClipRectangle :: GC -> Rectangle -> IO ()
-gcSetClipRegion :: GC -> Region -> IO ()
-gcSetDashes :: GC -> Int -> [(Int, Int)] -> IO ()
-
-module Graphics.UI.Gtk.General.IconFactory
-data IconFactory
-instance GObjectClass IconFactory
-instance IconFactoryClass IconFactory
-class GObjectClass o => IconFactoryClass o
-instance IconFactoryClass IconFactory
-castToIconFactory :: GObjectClass obj => obj -> IconFactory
-toIconFactory :: IconFactoryClass o => o -> IconFactory
-iconFactoryNew :: IO IconFactory
-iconFactoryAdd :: IconFactory -> String -> IconSet -> IO ()
-iconFactoryAddDefault :: IconFactory -> IO ()
-iconFactoryLookup :: IconFactory -> String -> IO (Maybe IconSet)
-iconFactoryLookupDefault :: String -> IO (Maybe IconSet)
-iconFactoryRemoveDefault :: IconFactory -> IO ()
-data IconSet
-iconSetNew :: IO IconSet
-iconSetNewFromPixbuf :: Pixbuf -> IO IconSet
-iconSetAddSource :: IconSet -> IconSource -> IO ()
-iconSetRenderIcon :: WidgetClass widget => IconSet -> TextDirection -> StateType -> IconSize -> widget -> IO Pixbuf
-iconSetGetSizes :: IconSet -> IO [IconSize]
-data IconSource
-iconSourceNew :: IO IconSource
-data TextDirection
-TextDirNone :: TextDirection
-TextDirLtr :: TextDirection
-TextDirRtl :: TextDirection
-instance Enum TextDirection
-instance Eq TextDirection
-iconSourceGetDirection :: IconSource -> IO (Maybe TextDirection)
-iconSourceSetDirection :: IconSource -> TextDirection -> IO ()
-iconSourceGetFilename :: IconSource -> IO (Maybe String)
-iconSourceSetFilename :: IconSource -> FilePath -> IO ()
-iconSourceGetPixbuf :: IconSource -> IO (Maybe Pixbuf)
-iconSourceSetPixbuf :: IconSource -> Pixbuf -> IO ()
-iconSourceGetSize :: IconSource -> IO (Maybe IconSize)
-iconSourceSetSize :: IconSource -> IconSize -> IO ()
-iconSourceResetSize :: IconSource -> IO ()
-data StateType
-StateNormal :: StateType
-StateActive :: StateType
-StatePrelight :: StateType
-StateSelected :: StateType
-StateInsensitive :: StateType
-instance Enum StateType
-instance Eq StateType
-iconSourceGetState :: IconSource -> IO (Maybe StateType)
-iconSourceSetState :: IconSource -> StateType -> IO ()
-iconSourceResetState :: IconSource -> IO ()
-type IconSize = Int
-iconSizeInvalid :: IconSize
-iconSizeMenu :: IconSize
-iconSizeSmallToolbar :: IconSize
-iconSizeLargeToolbar :: IconSize
-iconSizeButton :: IconSize
-iconSizeDialog :: IconSize
-iconSizeCheck :: IconSize -> IO Bool
-iconSizeRegister :: Int -> String -> Int -> IO IconSize
-iconSizeRegisterAlias :: IconSize -> String -> IO ()
-iconSizeFromName :: String -> IO IconSize
-iconSizeGetName :: IconSize -> IO (Maybe String)
-
-module Graphics.UI.Gtk.General.Style
-data Style
-instance GObjectClass Style
-instance StyleClass Style
-class GObjectClass o => StyleClass o
-instance StyleClass Style
-castToStyle :: GObjectClass obj => obj -> Style
-toStyle :: StyleClass o => o -> Style
-styleGetForeground :: StateType -> Style -> IO GC
-styleGetBackground :: StateType -> Style -> IO GC
-styleGetLight :: StateType -> Style -> IO GC
-styleGetMiddle :: StateType -> Style -> IO GC
-styleGetDark :: StateType -> Style -> IO GC
-styleGetText :: StateType -> Style -> IO GC
-styleGetBase :: StateType -> Style -> IO GC
-styleGetAntiAliasing :: StateType -> Style -> IO GC
-
-module Graphics.UI.Gtk.Multiline.TextIter
-newtype TextIter
-TextIter :: ForeignPtr TextIter -> TextIter
-data TextSearchFlags
-TextSearchVisibleOnly :: TextSearchFlags
-TextSearchTextOnly :: TextSearchFlags
-instance Bounded TextSearchFlags
-instance Enum TextSearchFlags
-instance Eq TextSearchFlags
-instance Flags TextSearchFlags
-mkTextIterCopy :: Ptr TextIter -> IO TextIter
-makeEmptyTextIter :: IO TextIter
-textIterGetBuffer :: TextIter -> IO TextBuffer
-textIterCopy :: TextIter -> IO TextIter
-textIterGetOffset :: TextIter -> IO Int
-textIterGetLine :: TextIter -> IO Int
-textIterGetLineOffset :: TextIter -> IO Int
-textIterGetVisibleLineOffset :: TextIter -> IO Int
-textIterGetChar :: TextIter -> IO (Maybe Char)
-textIterGetSlice :: TextIter -> TextIter -> IO String
-textIterGetText :: TextIter -> TextIter -> IO String
-textIterGetVisibleSlice :: TextIter -> TextIter -> IO String
-textIterGetVisibleText :: TextIter -> TextIter -> IO String
-textIterGetPixbuf :: TextIter -> IO (Maybe Pixbuf)
-textIterBeginsTag :: TextIter -> TextTag -> IO Bool
-textIterEndsTag :: TextIter -> TextTag -> IO Bool
-textIterTogglesTag :: TextIter -> TextTag -> IO Bool
-textIterHasTag :: TextIter -> TextTag -> IO Bool
-textIterEditable :: TextIter -> Bool -> IO Bool
-textIterCanInsert :: TextIter -> Bool -> IO Bool
-textIterStartsWord :: TextIter -> IO Bool
-textIterEndsWord :: TextIter -> IO Bool
-textIterInsideWord :: TextIter -> IO Bool
-textIterStartsLine :: TextIter -> IO Bool
-textIterEndsLine :: TextIter -> IO Bool
-textIterStartsSentence :: TextIter -> IO Bool
-textIterEndsSentence :: TextIter -> IO Bool
-textIterInsideSentence :: TextIter -> IO Bool
-textIterIsCursorPosition :: TextIter -> IO Bool
-textIterGetCharsInLine :: TextIter -> IO Int
-textIterIsEnd :: TextIter -> IO Bool
-textIterIsStart :: TextIter -> IO Bool
-textIterForwardChar :: TextIter -> IO Bool
-textIterBackwardChar :: TextIter -> IO Bool
-textIterForwardChars :: TextIter -> Int -> IO Bool
-textIterBackwardChars :: TextIter -> Int -> IO Bool
-textIterForwardLine :: TextIter -> IO Bool
-textIterBackwardLine :: TextIter -> IO Bool
-textIterForwardLines :: TextIter -> Int -> IO Bool
-textIterBackwardLines :: TextIter -> Int -> IO Bool
-textIterForwardWordEnds :: TextIter -> Int -> IO Bool
-textIterBackwardWordStarts :: TextIter -> Int -> IO Bool
-textIterForwardWordEnd :: TextIter -> IO Bool
-textIterBackwardWordStart :: TextIter -> IO Bool
-textIterForwardCursorPosition :: TextIter -> IO Bool
-textIterBackwardCursorPosition :: TextIter -> IO Bool
-textIterForwardCursorPositions :: TextIter -> Int -> IO Bool
-textIterBackwardCursorPositions :: TextIter -> Int -> IO Bool
-textIterForwardSentenceEnds :: TextIter -> Int -> IO Bool
-textIterBackwardSentenceStarts :: TextIter -> Int -> IO Bool
-textIterForwardSentenceEnd :: TextIter -> IO Bool
-textIterBackwardSentenceStart :: TextIter -> IO Bool
-textIterSetOffset :: TextIter -> Int -> IO ()
-textIterSetLine :: TextIter -> Int -> IO ()
-textIterSetLineOffset :: TextIter -> Int -> IO ()
-textIterSetVisibleLineOffset :: TextIter -> Int -> IO ()
-textIterForwardToEnd :: TextIter -> IO ()
-textIterForwardToLineEnd :: TextIter -> IO Bool
-textIterForwardToTagToggle :: TextIter -> Maybe TextTag -> IO Bool
-textIterBackwardToTagToggle :: TextIter -> Maybe TextTag -> IO Bool
-textIterForwardFindChar :: TextIter -> (Char -> Bool) -> Maybe TextIter -> IO Bool
-textIterBackwardFindChar :: TextIter -> (Char -> Bool) -> Maybe TextIter -> IO Bool
-textIterForwardSearch :: TextIter -> String -> [TextSearchFlags] -> Maybe TextIter -> IO (Maybe (TextIter, TextIter))
-textIterBackwardSearch :: TextIter -> String -> [TextSearchFlags] -> Maybe TextIter -> IO (Maybe (TextIter, TextIter))
-textIterEqual :: TextIter -> TextIter -> IO Bool
-textIterCompare :: TextIter -> TextIter -> IO Ordering
-textIterForwardVisibleLine :: TextIter -> IO Bool
-textIterBackwardVisibleLine :: TextIter -> IO Bool
-textIterForwardVisibleLines :: TextIter -> Int -> IO Bool
-textIterBackwardVisibleLines :: TextIter -> Int -> IO Bool
-textIterVisibleLineOffset :: Attr TextIter Int
-textIterOffset :: Attr TextIter Int
-textIterLineOffset :: Attr TextIter Int
-textIterLine :: Attr TextIter Int
-
-module Graphics.UI.Gtk.Multiline.TextBuffer
-data TextBuffer
-instance GObjectClass TextBuffer
-instance TextBufferClass TextBuffer
-class GObjectClass o => TextBufferClass o
-instance TextBufferClass SourceBuffer
-instance TextBufferClass TextBuffer
-castToTextBuffer :: GObjectClass obj => obj -> TextBuffer
-toTextBuffer :: TextBufferClass o => o -> TextBuffer
-textBufferNew :: Maybe TextTagTable -> IO TextBuffer
-textBufferGetLineCount :: TextBufferClass self => self -> IO Int
-textBufferGetCharCount :: TextBufferClass self => self -> IO Int
-textBufferGetTagTable :: TextBufferClass self => self -> IO TextTagTable
-textBufferInsert :: TextBufferClass self => self -> TextIter -> String -> IO ()
-textBufferInsertAtCursor :: TextBufferClass self => self -> String -> IO ()
-textBufferInsertInteractive :: TextBufferClass self => self -> TextIter -> String -> Bool -> IO Bool
-textBufferInsertInteractiveAtCursor :: TextBufferClass self => self -> String -> Bool -> IO Bool
-textBufferInsertRange :: TextBufferClass self => self -> TextIter -> TextIter -> TextIter -> IO ()
-textBufferInsertRangeInteractive :: TextBufferClass self => self -> TextIter -> TextIter -> TextIter -> Bool -> IO Bool
-textBufferDelete :: TextBufferClass self => self -> TextIter -> TextIter -> IO ()
-textBufferDeleteInteractive :: TextBufferClass self => self -> TextIter -> TextIter -> Bool -> IO Bool
-textBufferSetText :: TextBufferClass self => self -> String -> IO ()
-textBufferGetText :: TextBufferClass self => self -> TextIter -> TextIter -> Bool -> IO String
-textBufferGetSlice :: TextBufferClass self => self -> TextIter -> TextIter -> Bool -> IO String
-textBufferInsertPixbuf :: TextBufferClass self => self -> TextIter -> Pixbuf -> IO ()
-textBufferCreateMark :: TextBufferClass self => self -> Maybe MarkName -> TextIter -> Bool -> IO TextMark
-textBufferMoveMark :: (TextBufferClass self, TextMarkClass mark) => self -> mark -> TextIter -> IO ()
-textBufferMoveMarkByName :: TextBufferClass self => self -> MarkName -> TextIter -> IO ()
-textBufferDeleteMark :: (TextBufferClass self, TextMarkClass mark) => self -> mark -> IO ()
-textBufferDeleteMarkByName :: TextBufferClass self => self -> MarkName -> IO ()
-textBufferGetMark :: TextBufferClass self => self -> MarkName -> IO (Maybe TextMark)
-textBufferGetInsert :: TextBufferClass self => self -> IO TextMark
-textBufferGetSelectionBound :: TextBufferClass self => self -> IO TextMark
-textBufferPlaceCursor :: TextBufferClass self => self -> TextIter -> IO ()
-textBufferApplyTag :: (TextBufferClass self, TextTagClass tag) => self -> tag -> TextIter -> TextIter -> IO ()
-textBufferRemoveTag :: (TextBufferClass self, TextTagClass tag) => self -> tag -> TextIter -> TextIter -> IO ()
-textBufferApplyTagByName :: TextBufferClass self => self -> TagName -> TextIter -> TextIter -> IO ()
-textBufferRemoveTagByName :: TextBufferClass self => self -> TagName -> TextIter -> TextIter -> IO ()
-textBufferRemoveAllTags :: TextBufferClass self => self -> TextIter -> TextIter -> IO ()
-textBufferGetIterAtLineOffset :: TextBufferClass self => self -> Int -> Int -> IO TextIter
-textBufferGetIterAtOffset :: TextBufferClass self => self -> Int -> IO TextIter
-textBufferGetIterAtLine :: TextBufferClass self => self -> Int -> IO TextIter
-textBufferGetIterAtMark :: (TextBufferClass self, TextMarkClass mark) => self -> mark -> IO TextIter
-textBufferGetStartIter :: TextBufferClass self => self -> IO TextIter
-textBufferGetEndIter :: TextBufferClass self => self -> IO TextIter
-textBufferGetModified :: TextBufferClass self => self -> IO Bool
-textBufferSetModified :: TextBufferClass self => self -> Bool -> IO ()
-textBufferDeleteSelection :: TextBufferClass self => self -> Bool -> Bool -> IO Bool
-textBufferHasSelection :: TextBufferClass self => self -> IO Bool
-textBufferGetSelectionBounds :: TextBufferClass self => self -> IO (TextIter, TextIter)
-textBufferSelectRange :: TextBufferClass self => self -> TextIter -> TextIter -> IO ()
-textBufferGetBounds :: TextBufferClass self => self -> TextIter -> TextIter -> IO ()
-textBufferBeginUserAction :: TextBufferClass self => self -> IO ()
-textBufferEndUserAction :: TextBufferClass self => self -> IO ()
-textBufferBackspace :: TextBufferClass self => self -> TextIter -> Bool -> Bool -> IO Bool
-textBufferInsertChildAnchor :: TextBufferClass self => self -> TextIter -> TextChildAnchor -> IO ()
-textBufferCreateChildAnchor :: TextBufferClass self => self -> TextIter -> IO TextChildAnchor
-textBufferGetIterAtChildAnchor :: TextBufferClass self => self -> TextIter -> TextChildAnchor -> IO ()
-textBufferTagTable :: (TextBufferClass self, TextTagTableClass textTagTable) => ReadWriteAttr self TextTagTable textTagTable
-textBufferText :: TextBufferClass self => Attr self String
-textBufferModified :: TextBufferClass self => Attr self Bool
-onApplyTag :: TextBufferClass self => self -> (TextTag -> TextIter -> TextIter -> IO ()) -> IO (ConnectId self)
-afterApplyTag :: TextBufferClass self => self -> (TextTag -> TextIter -> TextIter -> IO ()) -> IO (ConnectId self)
-onBeginUserAction :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-afterBeginUserAction :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-onBufferChanged :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-afterBufferChanged :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-onDeleteRange :: TextBufferClass self => self -> (TextIter -> TextIter -> IO ()) -> IO (ConnectId self)
-afterDeleteRange :: TextBufferClass self => self -> (TextIter -> TextIter -> IO ()) -> IO (ConnectId self)
-onEndUserAction :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-afterEndUserAction :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-onInsertPixbuf :: TextBufferClass self => self -> (TextIter -> Pixbuf -> IO ()) -> IO (ConnectId self)
-afterInsertPixbuf :: TextBufferClass self => self -> (TextIter -> Pixbuf -> IO ()) -> IO (ConnectId self)
-onInsertText :: TextBufferClass self => self -> (TextIter -> String -> IO ()) -> IO (ConnectId self)
-afterInsertText :: TextBufferClass self => self -> (TextIter -> String -> IO ()) -> IO (ConnectId self)
-onMarkDeleted :: TextBufferClass self => self -> (TextMark -> IO ()) -> IO (ConnectId self)
-afterMarkDeleted :: TextBufferClass self => self -> (TextMark -> IO ()) -> IO (ConnectId self)
-onMarkSet :: TextBufferClass self => self -> (TextIter -> TextMark -> IO ()) -> IO (ConnectId self)
-afterMarkSet :: TextBufferClass self => self -> (TextIter -> TextMark -> IO ()) -> IO (ConnectId self)
-onModifiedChanged :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-afterModifiedChanged :: TextBufferClass self => self -> IO () -> IO (ConnectId self)
-onRemoveTag :: TextBufferClass self => self -> (TextTag -> TextIter -> TextIter -> IO ()) -> IO (ConnectId self)
-afterRemoveTag :: TextBufferClass self => self -> (TextTag -> TextIter -> TextIter -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Abstract.Widget
-data Widget
-instance GObjectClass Widget
-instance ObjectClass Widget
-instance WidgetClass Widget
-class ObjectClass o => WidgetClass o
-instance WidgetClass AboutDialog
-instance WidgetClass AccelLabel
-instance WidgetClass Alignment
-instance WidgetClass Arrow
-instance WidgetClass AspectFrame
-instance WidgetClass Bin
-instance WidgetClass Box
-instance WidgetClass Button
-instance WidgetClass ButtonBox
-instance WidgetClass CList
-instance WidgetClass CTree
-instance WidgetClass Calendar
-instance WidgetClass CellView
-instance WidgetClass CheckButton
-instance WidgetClass CheckMenuItem
-instance WidgetClass ColorButton
-instance WidgetClass ColorSelection
-instance WidgetClass ColorSelectionDialog
-instance WidgetClass Combo
-instance WidgetClass ComboBox
-instance WidgetClass ComboBoxEntry
-instance WidgetClass Container
-instance WidgetClass Curve
-instance WidgetClass Dialog
-instance WidgetClass DrawingArea
-instance WidgetClass Entry
-instance WidgetClass EventBox
-instance WidgetClass Expander
-instance WidgetClass FileChooserButton
-instance WidgetClass FileChooserDialog
-instance WidgetClass FileChooserWidget
-instance WidgetClass FileSelection
-instance WidgetClass Fixed
-instance WidgetClass FontButton
-instance WidgetClass FontSelection
-instance WidgetClass FontSelectionDialog
-instance WidgetClass Frame
-instance WidgetClass GammaCurve
-instance WidgetClass HBox
-instance WidgetClass HButtonBox
-instance WidgetClass HPaned
-instance WidgetClass HRuler
-instance WidgetClass HScale
-instance WidgetClass HScrollbar
-instance WidgetClass HSeparator
-instance WidgetClass HandleBox
-instance WidgetClass IconView
-instance WidgetClass Image
-instance WidgetClass ImageMenuItem
-instance WidgetClass InputDialog
-instance WidgetClass Invisible
-instance WidgetClass Item
-instance WidgetClass Label
-instance WidgetClass Layout
-instance WidgetClass List
-instance WidgetClass ListItem
-instance WidgetClass Menu
-instance WidgetClass MenuBar
-instance WidgetClass MenuItem
-instance WidgetClass MenuShell
-instance WidgetClass MenuToolButton
-instance WidgetClass MessageDialog
-instance WidgetClass Misc
-instance WidgetClass MozEmbed
-instance WidgetClass Notebook
-instance WidgetClass OptionMenu
-instance WidgetClass Paned
-instance WidgetClass Plug
-instance WidgetClass Preview
-instance WidgetClass ProgressBar
-instance WidgetClass RadioButton
-instance WidgetClass RadioMenuItem
-instance WidgetClass RadioToolButton
-instance WidgetClass Range
-instance WidgetClass Ruler
-instance WidgetClass Scale
-instance WidgetClass Scrollbar
-instance WidgetClass ScrolledWindow
-instance WidgetClass Separator
-instance WidgetClass SeparatorMenuItem
-instance WidgetClass SeparatorToolItem
-instance WidgetClass Socket
-instance WidgetClass SourceView
-instance WidgetClass SpinButton
-instance WidgetClass Statusbar
-instance WidgetClass Table
-instance WidgetClass TearoffMenuItem
-instance WidgetClass TextView
-instance WidgetClass TipsQuery
-instance WidgetClass ToggleButton
-instance WidgetClass ToggleToolButton
-instance WidgetClass ToolButton
-instance WidgetClass ToolItem
-instance WidgetClass Toolbar
-instance WidgetClass TreeView
-instance WidgetClass VBox
-instance WidgetClass VButtonBox
-instance WidgetClass VPaned
-instance WidgetClass VRuler
-instance WidgetClass VScale
-instance WidgetClass VScrollbar
-instance WidgetClass VSeparator
-instance WidgetClass Viewport
-instance WidgetClass Widget
-instance WidgetClass Window
-castToWidget :: GObjectClass obj => obj -> Widget
-toWidget :: WidgetClass o => o -> Widget
-type Allocation = Rectangle
-data Requisition
-Requisition :: Int -> Int -> Requisition
-instance Storable Requisition
-data Rectangle
-Rectangle :: Int -> Int -> Int -> Int -> Rectangle
-instance Storable Rectangle
-widgetGetState :: WidgetClass w => w -> IO StateType
-widgetGetSavedState :: WidgetClass w => w -> IO StateType
-widgetShow :: WidgetClass self => self -> IO ()
-widgetShowNow :: WidgetClass self => self -> IO ()
-widgetHide :: WidgetClass self => self -> IO ()
-widgetShowAll :: WidgetClass self => self -> IO ()
-widgetHideAll :: WidgetClass self => self -> IO ()
-widgetDestroy :: WidgetClass self => self -> IO ()
-widgetQueueDraw :: WidgetClass self => self -> IO ()
-widgetHasIntersection :: WidgetClass self => self -> Rectangle -> IO Bool
-widgetIntersect :: WidgetClass self => self -> Rectangle -> IO (Maybe Rectangle)
-widgetRegionIntersect :: WidgetClass self => self -> Region -> IO Region
-widgetActivate :: WidgetClass self => self -> IO Bool
-widgetSetSensitivity :: WidgetClass self => self -> Bool -> IO ()
-widgetSetSizeRequest :: WidgetClass self => self -> Int -> Int -> IO ()
-widgetGetSizeRequest :: WidgetClass self => self -> IO (Int, Int)
-widgetIsFocus :: WidgetClass self => self -> IO Bool
-widgetGrabFocus :: WidgetClass self => self -> IO ()
-widgetSetAppPaintable :: WidgetClass self => self -> Bool -> IO ()
-widgetSetName :: WidgetClass self => self -> String -> IO ()
-widgetGetName :: WidgetClass self => self -> IO String
-data EventMask
-ExposureMask :: EventMask
-PointerMotionMask :: EventMask
-PointerMotionHintMask :: EventMask
-ButtonMotionMask :: EventMask
-Button1MotionMask :: EventMask
-Button2MotionMask :: EventMask
-Button3MotionMask :: EventMask
-ButtonPressMask :: EventMask
-ButtonReleaseMask :: EventMask
-KeyPressMask :: EventMask
-KeyReleaseMask :: EventMask
-EnterNotifyMask :: EventMask
-LeaveNotifyMask :: EventMask
-FocusChangeMask :: EventMask
-StructureMask :: EventMask
-PropertyChangeMask :: EventMask
-VisibilityNotifyMask :: EventMask
-ProximityInMask :: EventMask
-ProximityOutMask :: EventMask
-SubstructureMask :: EventMask
-ScrollMask :: EventMask
-AllEventsMask :: EventMask
-instance Bounded EventMask
-instance Enum EventMask
-instance Flags EventMask
-widgetDelEvents :: WidgetClass self => self -> [EventMask] -> IO ()
-widgetAddEvents :: WidgetClass self => self -> [EventMask] -> IO ()
-widgetGetEvents :: WidgetClass self => self -> IO [EventMask]
-data ExtensionMode
-ExtensionEventsNone :: ExtensionMode
-ExtensionEventsAll :: ExtensionMode
-ExtensionEventsCursor :: ExtensionMode
-instance Bounded ExtensionMode
-instance Enum ExtensionMode
-instance Flags ExtensionMode
-widgetSetExtensionEvents :: WidgetClass self => self -> [ExtensionMode] -> IO ()
-widgetGetExtensionEvents :: WidgetClass self => self -> IO [ExtensionMode]
-widgetGetToplevel :: WidgetClass self => self -> IO Widget
-widgetIsAncestor :: (WidgetClass self, WidgetClass ancestor) => self -> ancestor -> IO Bool
-widgetReparent :: (WidgetClass self, WidgetClass newParent) => self -> newParent -> IO ()
-data TextDirection
-TextDirNone :: TextDirection
-TextDirLtr :: TextDirection
-TextDirRtl :: TextDirection
-instance Enum TextDirection
-instance Eq TextDirection
-widgetSetDirection :: WidgetClass self => self -> TextDirection -> IO ()
-widgetGetDirection :: WidgetClass self => self -> IO TextDirection
-widgetQueueDrawArea :: WidgetClass self => self -> Int -> Int -> Int -> Int -> IO ()
-widgetSetDoubleBuffered :: WidgetClass self => self -> Bool -> IO ()
-widgetSetRedrawOnAllocate :: WidgetClass self => self -> Bool -> IO ()
-widgetGetParentWindow :: WidgetClass self => self -> IO DrawWindow
-widgetGetPointer :: WidgetClass self => self -> IO (Int, Int)
-widgetTranslateCoordinates :: (WidgetClass self, WidgetClass destWidget) => self -> destWidget -> Int -> Int -> IO (Maybe (Int, Int))
-widgetPath :: WidgetClass self => self -> IO (Int, String, String)
-widgetClassPath :: WidgetClass self => self -> IO (Int, String, String)
-widgetGetCompositeName :: WidgetClass self => self -> IO (Maybe String)
-widgetSetCompositeName :: WidgetClass self => self -> String -> IO ()
-widgetGetParent :: WidgetClass self => self -> IO (Maybe Widget)
-widgetSetDefaultDirection :: TextDirection -> IO ()
-widgetGetDefaultDirection :: IO TextDirection
-widgetModifyStyle :: (WidgetClass self, RcStyleClass style) => self -> style -> IO ()
-widgetGetModifierStyle :: WidgetClass self => self -> IO RcStyle
-widgetModifyFg :: WidgetClass self => self -> StateType -> Color -> IO ()
-widgetModifyBg :: WidgetClass self => self -> StateType -> Color -> IO ()
-widgetModifyText :: WidgetClass self => self -> StateType -> Color -> IO ()
-widgetModifyBase :: WidgetClass self => self -> StateType -> Color -> IO ()
-widgetModifyFont :: WidgetClass self => self -> Maybe FontDescription -> IO ()
-widgetCreateLayout :: WidgetClass self => self -> String -> IO PangoLayout
-widgetCreatePangoContext :: WidgetClass self => self -> IO PangoContext
-widgetGetPangoContext :: WidgetClass self => self -> IO PangoContext
-widgetRenderIcon :: WidgetClass self => self -> StockId -> IconSize -> String -> IO (Maybe Pixbuf)
-widgetGetCanFocus :: WidgetClass self => self -> IO Bool
-widgetSetCanFocus :: WidgetClass self => self -> Bool -> IO ()
-widgetExtensionEvents :: WidgetClass self => Attr self [ExtensionMode]
-widgetDirection :: WidgetClass self => Attr self TextDirection
-widgetCanFocus :: WidgetClass self => Attr self Bool
-onButtonPress :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterButtonPress :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onButtonRelease :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterButtonRelease :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onClient :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterClient :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onConfigure :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterConfigure :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onDelete :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterDelete :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onDestroyEvent :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterDestroyEvent :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onDirectionChanged :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterDirectionChanged :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onEnterNotify :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterEnterNotify :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onLeaveNotify :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterLeaveNotify :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onExpose :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterExpose :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onExposeRect :: WidgetClass w => w -> (Rectangle -> IO ()) -> IO (ConnectId w)
-afterExposeRect :: WidgetClass w => w -> (Rectangle -> IO ()) -> IO (ConnectId w)
-onFocusIn :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterFocusIn :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onFocusOut :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterFocusOut :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onGrabFocus :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterGrabFocus :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onDestroy :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterDestroy :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onHide :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterHide :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onHierarchyChanged :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterHierarchyChanged :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onKeyPress :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterKeyPress :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onKeyRelease :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterKeyRelease :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onMnemonicActivate :: WidgetClass w => w -> (Bool -> IO Bool) -> IO (ConnectId w)
-afterMnemonicActivate :: WidgetClass w => w -> (Bool -> IO Bool) -> IO (ConnectId w)
-onMotionNotify :: WidgetClass w => w -> Bool -> (Event -> IO Bool) -> IO (ConnectId w)
-afterMotionNotify :: WidgetClass w => w -> Bool -> (Event -> IO Bool) -> IO (ConnectId w)
-onParentSet :: (WidgetClass w, WidgetClass old) => w -> (old -> IO ()) -> IO (ConnectId w)
-afterParentSet :: (WidgetClass w, WidgetClass old) => w -> (old -> IO ()) -> IO (ConnectId w)
-onPopupMenu :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterPopupMenu :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onProximityIn :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterProximityIn :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onProximityOut :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterProximityOut :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onRealize :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterRealize :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onScroll :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterScroll :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onShow :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterShow :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onSizeAllocate :: WidgetClass w => w -> (Allocation -> IO ()) -> IO (ConnectId w)
-afterSizeAllocate :: WidgetClass w => w -> (Allocation -> IO ()) -> IO (ConnectId w)
-onSizeRequest :: WidgetClass w => w -> IO Requisition -> IO (ConnectId w)
-afterSizeRequest :: WidgetClass w => w -> IO Requisition -> IO (ConnectId w)
-data StateType
-StateNormal :: StateType
-StateActive :: StateType
-StatePrelight :: StateType
-StateSelected :: StateType
-StateInsensitive :: StateType
-instance Enum StateType
-instance Eq StateType
-onStateChanged :: WidgetClass w => w -> (StateType -> IO ()) -> IO (ConnectId w)
-afterStateChanged :: WidgetClass w => w -> (StateType -> IO ()) -> IO (ConnectId w)
-onUnmap :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterUnmap :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onUnrealize :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-afterUnrealize :: WidgetClass w => w -> IO () -> IO (ConnectId w)
-onVisibilityNotify :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterVisibilityNotify :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-onWindowState :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-afterWindowState :: WidgetClass w => w -> (Event -> IO Bool) -> IO (ConnectId w)
-
-module Graphics.UI.Gtk.Gdk.Drawable
-data Drawable
-instance DrawableClass Drawable
-instance GObjectClass Drawable
-class GObjectClass o => DrawableClass o
-instance DrawableClass DrawWindow
-instance DrawableClass Drawable
-instance DrawableClass Pixmap
-castToDrawable :: GObjectClass obj => obj -> Drawable
-toDrawable :: DrawableClass o => o -> Drawable
-drawableGetDepth :: DrawableClass d => d -> IO Int
-drawableGetSize :: DrawableClass d => d -> IO (Int, Int)
-drawableGetClipRegion :: DrawableClass d => d -> IO Region
-drawableGetVisibleRegion :: DrawableClass d => d -> IO Region
-type Point = (Int, Int)
-drawPoint :: DrawableClass d => d -> GC -> Point -> IO ()
-drawPoints :: DrawableClass d => d -> GC -> [Point] -> IO ()
-drawLine :: DrawableClass d => d -> GC -> Point -> Point -> IO ()
-drawLines :: DrawableClass d => d -> GC -> [Point] -> IO ()
-data Dither
-RgbDitherNone :: Dither
-RgbDitherNormal :: Dither
-RgbDitherMax :: Dither
-instance Enum Dither
-drawPixbuf :: DrawableClass d => d -> GC -> Pixbuf -> Int -> Int -> Int -> Int -> Int -> Int -> Dither -> Int -> Int -> IO ()
-drawSegments :: DrawableClass d => d -> GC -> [(Point, Point)] -> IO ()
-drawRectangle :: DrawableClass d => d -> GC -> Bool -> Int -> Int -> Int -> Int -> IO ()
-drawArc :: DrawableClass d => d -> GC -> Bool -> Int -> Int -> Int -> Int -> Int -> Int -> IO ()
-drawPolygon :: DrawableClass d => d -> GC -> Bool -> [Point] -> IO ()
-drawGlyphs :: DrawableClass d => d -> GC -> Int -> Int -> GlyphItem -> IO ()
-drawLayoutLine :: DrawableClass d => d -> GC -> Int -> Int -> LayoutLine -> IO ()
-drawLayoutLineWithColors :: DrawableClass d => d -> GC -> Int -> Int -> LayoutLine -> Maybe Color -> Maybe Color -> IO ()
-drawLayout :: DrawableClass d => d -> GC -> Int -> Int -> PangoLayout -> IO ()
-drawLayoutWithColors :: DrawableClass d => d -> GC -> Int -> Int -> PangoLayout -> Maybe Color -> Maybe Color -> IO ()
-drawDrawable :: (DrawableClass src, DrawableClass dest) => dest -> GC -> src -> Int -> Int -> Int -> Int -> Int -> Int -> IO ()
-
-module Graphics.UI.Gtk.Gdk.Pixmap
-data Pixmap
-instance DrawableClass Pixmap
-instance GObjectClass Pixmap
-instance PixmapClass Pixmap
-class DrawableClass o => PixmapClass o
-instance PixmapClass Pixmap
-pixmapNew :: DrawableClass drawable => Maybe drawable -> Int -> Int -> Maybe Int -> IO Pixmap
-
-module Graphics.UI.Gtk.Pango.Font
-data PangoUnit
-instance Enum PangoUnit
-instance Eq PangoUnit
-instance Fractional PangoUnit
-instance Integral PangoUnit
-instance Num PangoUnit
-instance Ord PangoUnit
-instance Real PangoUnit
-instance Show PangoUnit
-data FontDescription
-fontDescriptionNew :: IO FontDescription
-fontDescriptionCopy :: FontDescription -> IO FontDescription
-fontDescriptionSetFamily :: FontDescription -> String -> IO ()
-fontDescriptionGetFamily :: FontDescription -> IO (Maybe String)
-fontDescriptionSetStyle :: FontDescription -> FontStyle -> IO ()
-fontDescriptionGetStyle :: FontDescription -> IO (Maybe FontStyle)
-fontDescriptionSetVariant :: FontDescription -> Variant -> IO ()
-fontDescriptionGetVariant :: FontDescription -> IO (Maybe Variant)
-fontDescriptionSetWeight :: FontDescription -> Weight -> IO ()
-fontDescriptionGetWeight :: FontDescription -> IO (Maybe Weight)
-fontDescriptionSetStretch :: FontDescription -> Stretch -> IO ()
-fontDescriptionGetStretch :: FontDescription -> IO (Maybe Stretch)
-fontDescriptionSetSize :: FontDescription -> PangoUnit -> IO ()
-fontDescriptionGetSize :: FontDescription -> IO (Maybe PangoUnit)
-data FontMask
-PangoFontMaskFamily :: FontMask
-PangoFontMaskStyle :: FontMask
-PangoFontMaskVariant :: FontMask
-PangoFontMaskWeight :: FontMask
-PangoFontMaskStretch :: FontMask
-PangoFontMaskSize :: FontMask
-instance Bounded FontMask
-instance Enum FontMask
-instance Flags FontMask
-fontDescriptionUnsetFields :: FontDescription -> [FontMask] -> IO ()
-fontDescriptionMerge :: FontDescription -> FontDescription -> Bool -> IO ()
-fontDescriptionBetterMatch :: FontDescription -> FontDescription -> FontDescription -> Bool
-fontDescriptionFromString :: String -> IO FontDescription
-fontDescriptionToString :: FontDescription -> IO String
-data FontMap
-instance FontMapClass FontMap
-instance GObjectClass FontMap
-pangoFontMapListFamilies :: FontMap -> IO [FontFamily]
-data FontFamily
-instance FontFamilyClass FontFamily
-instance GObjectClass FontFamily
-instance Show FontFamily
-pangoFontFamilyIsMonospace :: FontFamily -> Bool
-pangoFontFamilyListFaces :: FontFamily -> IO [FontFace]
-data FontFace
-instance FontFaceClass FontFace
-instance GObjectClass FontFace
-instance Show FontFace
-pangoFontFaceListSizes :: FontFace -> IO (Maybe [PangoUnit])
-pangoFontFaceDescribe :: FontFace -> IO FontDescription
-data FontMetrics
-FontMetrics :: PangoUnit -> PangoUnit -> PangoUnit -> PangoUnit -> PangoUnit -> PangoUnit -> PangoUnit -> PangoUnit -> FontMetrics
-ascent :: FontMetrics -> PangoUnit
-descent :: FontMetrics -> PangoUnit
-approximateCharWidth :: FontMetrics -> PangoUnit
-approximateDigitWidth :: FontMetrics -> PangoUnit
-underlineThickness :: FontMetrics -> PangoUnit
-underlinePosition :: FontMetrics -> PangoUnit
-strikethroughThickenss :: FontMetrics -> PangoUnit
-strikethroughPosition :: FontMetrics -> PangoUnit
-instance Show FontMetrics
-
-module Graphics.UI.Gtk.Pango.Context
-data PangoContext
-instance GObjectClass PangoContext
-instance PangoContextClass PangoContext
-data PangoDirection
-PangoDirectionLtr :: PangoDirection
-PangoDirectionRtl :: PangoDirection
-PangoDirectionWeakLtr :: PangoDirection
-PangoDirectionWeakRtl :: PangoDirection
-PangoDirectionNeutral :: PangoDirection
-instance Enum PangoDirection
-instance Eq PangoDirection
-instance Ord PangoDirection
-contextListFamilies :: PangoContext -> IO [FontFamily]
-contextGetMetrics :: PangoContext -> FontDescription -> Language -> IO FontMetrics
-contextSetFontDescription :: PangoContext -> FontDescription -> IO ()
-contextGetFontDescription :: PangoContext -> IO FontDescription
-data Language
-instance Eq Language
-instance Show Language
-languageFromString :: String -> IO Language
-contextSetLanguage :: PangoContext -> Language -> IO ()
-contextGetLanguage :: PangoContext -> IO Language
-contextSetTextDir :: PangoContext -> PangoDirection -> IO ()
-contextGetTextDir :: PangoContext -> IO PangoDirection
-
-module Graphics.UI.Gtk.Pango.Markup
-type Markup = String
-data SpanAttribute
-FontDescr :: String -> SpanAttribute
-FontFamily :: String -> SpanAttribute
-FontSize :: Size -> SpanAttribute
-FontStyle :: FontStyle -> SpanAttribute
-FontWeight :: Weight -> SpanAttribute
-FontVariant :: Variant -> SpanAttribute
-FontStretch :: Stretch -> SpanAttribute
-FontForeground :: String -> SpanAttribute
-FontBackground :: String -> SpanAttribute
-FontUnderline :: Underline -> SpanAttribute
-FontRise :: Double -> SpanAttribute
-FontLang :: Language -> SpanAttribute
-instance Show SpanAttribute
-markSpan :: [SpanAttribute] -> String -> String
-data Size
-SizePoint :: Double -> Size
-SizeUnreadable :: Size
-SizeTiny :: Size
-SizeSmall :: Size
-SizeMedium :: Size
-SizeLarge :: Size
-SizeHuge :: Size
-SizeGiant :: Size
-SizeSmaller :: Size
-SizeLarger :: Size
-instance Show Size
-
-module Graphics.UI.Gtk.Display.Label
-data Label
-instance GObjectClass Label
-instance LabelClass Label
-instance MiscClass Label
-instance ObjectClass Label
-instance WidgetClass Label
-class MiscClass o => LabelClass o
-instance LabelClass AccelLabel
-instance LabelClass Label
-instance LabelClass TipsQuery
-castToLabel :: GObjectClass obj => obj -> Label
-toLabel :: LabelClass o => o -> Label
-labelNew :: Maybe String -> IO Label
-labelNewWithMnemonic :: String -> IO Label
-labelSetText :: LabelClass self => self -> String -> IO ()
-labelSetLabel :: LabelClass self => self -> String -> IO ()
-labelSetTextWithMnemonic :: LabelClass self => self -> String -> IO ()
-labelSetMarkup :: LabelClass self => self -> Markup -> IO ()
-labelSetMarkupWithMnemonic :: LabelClass self => self -> Markup -> IO ()
-labelSetMnemonicWidget :: (LabelClass self, WidgetClass widget) => self -> widget -> IO ()
-labelGetMnemonicWidget :: LabelClass self => self -> IO (Maybe Widget)
-type KeyVal = Word32
-labelGetMnemonicKeyval :: LabelClass self => self -> IO KeyVal
-labelSetUseMarkup :: LabelClass self => self -> Bool -> IO ()
-labelGetUseMarkup :: LabelClass self => self -> IO Bool
-labelSetUseUnderline :: LabelClass self => self -> Bool -> IO ()
-labelGetUseUnderline :: LabelClass self => self -> IO Bool
-labelGetText :: LabelClass self => self -> IO String
-labelGetLabel :: LabelClass self => self -> IO String
-labelSetPattern :: LabelClass l => l -> [Int] -> IO ()
-data Justification
-JustifyLeft :: Justification
-JustifyRight :: Justification
-JustifyCenter :: Justification
-JustifyFill :: Justification
-instance Enum Justification
-instance Eq Justification
-labelSetJustify :: LabelClass self => self -> Justification -> IO ()
-labelGetJustify :: LabelClass self => self -> IO Justification
-labelGetLayout :: LabelClass self => self -> IO PangoLayout
-labelSetLineWrap :: LabelClass self => self -> Bool -> IO ()
-labelGetLineWrap :: LabelClass self => self -> IO Bool
-labelSetSelectable :: LabelClass self => self -> Bool -> IO ()
-labelGetSelectable :: LabelClass self => self -> IO Bool
-labelSelectRegion :: LabelClass self => self -> Int -> Int -> IO ()
-labelGetSelectionBounds :: LabelClass self => self -> IO (Maybe (Int, Int))
-labelGetLayoutOffsets :: LabelClass self => self -> IO (Int, Int)
-labelSetEllipsize :: LabelClass self => self -> EllipsizeMode -> IO ()
-labelGetEllipsize :: LabelClass self => self -> IO EllipsizeMode
-labelSetWidthChars :: LabelClass self => self -> Int -> IO ()
-labelGetWidthChars :: LabelClass self => self -> IO Int
-labelSetMaxWidthChars :: LabelClass self => self -> Int -> IO ()
-labelGetMaxWidthChars :: LabelClass self => self -> IO Int
-labelSetSingleLineMode :: LabelClass self => self -> Bool -> IO ()
-labelGetSingleLineMode :: LabelClass self => self -> IO Bool
-labelSetAngle :: LabelClass self => self -> Double -> IO ()
-labelGetAngle :: LabelClass self => self -> IO Double
-labelLabel :: LabelClass self => Attr self String
-labelUseMarkup :: LabelClass self => Attr self Bool
-labelUseUnderline :: LabelClass self => Attr self Bool
-labelJustify :: LabelClass self => Attr self Justification
-labelWrap :: LabelClass self => Attr self Bool
-labelSelectable :: LabelClass self => Attr self Bool
-labelMnemonicWidget :: (LabelClass self, WidgetClass widget) => ReadWriteAttr self (Maybe Widget) widget
-labelCursorPosition :: LabelClass self => ReadAttr self Int
-labelSelectionBound :: LabelClass self => ReadAttr self Int
-labelEllipsize :: LabelClass self => Attr self EllipsizeMode
-labelWidthChars :: LabelClass self => Attr self Int
-labelSingleLineMode :: LabelClass self => Attr self Bool
-labelAngle :: LabelClass self => Attr self Double
-labelMaxWidthChars :: LabelClass self => Attr self Int
-labelLineWrap :: LabelClass self => Attr self Bool
-labelText :: LabelClass self => Attr self String
-
-module Graphics.UI.Gtk.Pango.Rendering
-data PangoAttribute
-AttrLanguage :: Int -> Int -> Language -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paLang :: PangoAttribute -> Language
-AttrFamily :: Int -> Int -> String -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paFamily :: PangoAttribute -> String
-AttrStyle :: Int -> Int -> FontStyle -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paStyle :: PangoAttribute -> FontStyle
-AttrWeight :: Int -> Int -> Weight -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paWeight :: PangoAttribute -> Weight
-AttrVariant :: Int -> Int -> Variant -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paVariant :: PangoAttribute -> Variant
-AttrStretch :: Int -> Int -> Stretch -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paStretch :: PangoAttribute -> Stretch
-AttrSize :: Int -> Int -> PangoUnit -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paSize :: PangoAttribute -> PangoUnit
-AttrAbsSize :: Int -> Int -> PangoUnit -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paSize :: PangoAttribute -> PangoUnit
-AttrFontDescription :: Int -> Int -> FontDescription -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paFontDescription :: PangoAttribute -> FontDescription
-AttrForeground :: Int -> Int -> Color -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paColor :: PangoAttribute -> Color
-AttrBackground :: Int -> Int -> Color -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paColor :: PangoAttribute -> Color
-AttrUnderline :: Int -> Int -> Underline -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paUnderline :: PangoAttribute -> Underline
-AttrUnderlineColor :: Int -> Int -> Color -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paColor :: PangoAttribute -> Color
-AttrStrikethrough :: Int -> Int -> Bool -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paStrikethrough :: PangoAttribute -> Bool
-AttrStrikethroughColor :: Int -> Int -> Color -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paColor :: PangoAttribute -> Color
-AttrRise :: Int -> Int -> PangoUnit -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paRise :: PangoAttribute -> PangoUnit
-AttrShape :: Int -> Int -> PangoRectangle -> PangoRectangle -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paInk :: PangoAttribute -> PangoRectangle
-paLogical :: PangoAttribute -> PangoRectangle
-AttrScale :: Int -> Int -> Double -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paScale :: PangoAttribute -> Double
-AttrFallback :: Int -> Int -> Bool -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paFallback :: PangoAttribute -> Bool
-AttrLetterSpacing :: Int -> Int -> PangoUnit -> PangoAttribute
-paStart :: PangoAttribute -> Int
-paEnd :: PangoAttribute -> Int
-paLetterSpacing :: PangoAttribute -> PangoUnit
-data PangoItem
-pangoItemize :: PangoContext -> String -> [PangoAttribute] -> IO [PangoItem]
-pangoItemGetFontMetrics :: PangoItem -> IO FontMetrics
-data GlyphItem
-pangoShape :: PangoItem -> IO GlyphItem
-glyphItemExtents :: GlyphItem -> IO (PangoRectangle, PangoRectangle)
-glyphItemExtentsRange :: GlyphItem -> Int -> Int -> IO (PangoRectangle, PangoRectangle)
-glyphItemIndexToX :: GlyphItem -> Int -> Bool -> IO PangoUnit
-glyphItemXToIndex :: GlyphItem -> PangoUnit -> IO (Int, Bool)
-glyphItemGetLogicalWidths :: GlyphItem -> Maybe Bool -> IO [PangoUnit]
-glyphItemSplit :: GlyphItem -> Int -> IO (GlyphItem, GlyphItem)
-
-module Graphics.UI.Gtk.Pango.Layout
-data PangoRectangle
-PangoRectangle :: PangoUnit -> PangoUnit -> PangoUnit -> PangoUnit -> PangoRectangle
-data PangoLayout
-layoutEmpty :: PangoContext -> IO PangoLayout
-layoutText :: PangoContext -> String -> IO PangoLayout
-layoutCopy :: PangoLayout -> IO PangoLayout
-layoutGetContext :: PangoLayout -> IO PangoContext
-layoutContextChanged :: PangoLayout -> IO ()
-layoutSetText :: PangoLayout -> String -> IO ()
-layoutGetText :: PangoLayout -> IO String
-layoutSetMarkup :: PangoLayout -> Markup -> IO String
-escapeMarkup :: String -> String
-layoutSetMarkupWithAccel :: PangoLayout -> Markup -> IO (Char, String)
-layoutSetAttributes :: PangoLayout -> [PangoAttribute] -> IO ()
-layoutSetFontDescription :: PangoLayout -> Maybe FontDescription -> IO ()
-layoutGetFontDescription :: PangoLayout -> IO (Maybe FontDescription)
-layoutSetWidth :: PangoLayout -> Maybe PangoUnit -> IO ()
-layoutGetWidth :: PangoLayout -> IO (Maybe PangoUnit)
-data LayoutWrapMode
-WrapWholeWords :: LayoutWrapMode
-WrapAnywhere :: LayoutWrapMode
-WrapPartialWords :: LayoutWrapMode
-instance Enum LayoutWrapMode
-layoutSetWrap :: PangoLayout -> LayoutWrapMode -> IO ()
-layoutGetWrap :: PangoLayout -> IO LayoutWrapMode
-data EllipsizeMode
-EllipsizeNone :: EllipsizeMode
-EllipsizeStart :: EllipsizeMode
-EllipsizeMiddle :: EllipsizeMode
-EllipsizeEnd :: EllipsizeMode
-instance Enum EllipsizeMode
-instance Eq EllipsizeMode
-layoutSetEllipsize :: PangoLayout -> EllipsizeMode -> IO ()
-layoutGetEllipsize :: PangoLayout -> IO EllipsizeMode
-layoutSetIndent :: PangoLayout -> PangoUnit -> IO ()
-layoutGetIndent :: PangoLayout -> IO PangoUnit
-layoutSetSpacing :: PangoLayout -> PangoUnit -> IO ()
-layoutGetSpacing :: PangoLayout -> IO PangoUnit
-layoutSetJustify :: PangoLayout -> Bool -> IO ()
-layoutGetJustify :: PangoLayout -> IO Bool
-layoutSetAutoDir :: PangoLayout -> Bool -> IO ()
-layoutGetAutoDir :: PangoLayout -> IO Bool
-data LayoutAlignment
-AlignLeft :: LayoutAlignment
-AlignCenter :: LayoutAlignment
-AlignRight :: LayoutAlignment
-instance Enum LayoutAlignment
-layoutSetAlignment :: PangoLayout -> LayoutAlignment -> IO ()
-layoutGetAlignment :: PangoLayout -> IO LayoutAlignment
-data TabAlign
-instance Enum TabAlign
-type TabPosition = (PangoUnit, TabAlign)
-layoutSetTabs :: PangoLayout -> [TabPosition] -> IO ()
-layoutResetTabs :: PangoLayout -> IO ()
-layoutGetTabs :: PangoLayout -> IO (Maybe [TabPosition])
-layoutSetSingleParagraphMode :: PangoLayout -> Bool -> IO ()
-layoutGetSingleParagraphMode :: PangoLayout -> IO Bool
-layoutXYToIndex :: PangoLayout -> PangoUnit -> PangoUnit -> IO (Bool, Int, Int)
-layoutIndexToPos :: PangoLayout -> Int -> IO PangoRectangle
-layoutGetCursorPos :: PangoLayout -> Int -> IO (PangoRectangle, PangoRectangle)
-data CursorPos
-CursorPosPrevPara :: CursorPos
-CursorPos :: Int -> Int -> CursorPos
-CursorPosNextPara :: CursorPos
-layoutMoveCursorVisually :: PangoLayout -> Bool -> Int -> Bool -> IO CursorPos
-layoutGetExtents :: PangoLayout -> IO (PangoRectangle, PangoRectangle)
-layoutGetPixelExtents :: PangoLayout -> IO (Rectangle, Rectangle)
-layoutGetLineCount :: PangoLayout -> IO Int
-layoutGetLine :: PangoLayout -> Int -> IO LayoutLine
-layoutGetLines :: PangoLayout -> IO [LayoutLine]
-data LayoutIter
-layoutGetIter :: PangoLayout -> IO LayoutIter
-layoutIterNextItem :: LayoutIter -> IO Bool
-layoutIterNextChar :: LayoutIter -> IO Bool
-layoutIterNextCluster :: LayoutIter -> IO Bool
-layoutIterNextLine :: LayoutIter -> IO Bool
-layoutIterAtLastLine :: LayoutIter -> IO Bool
-layoutIterGetIndex :: LayoutIter -> IO Int
-layoutIterGetBaseline :: LayoutIter -> IO PangoUnit
-layoutIterGetItem :: LayoutIter -> IO (Maybe GlyphItem)
-layoutIterGetLine :: LayoutIter -> IO (Maybe LayoutLine)
-layoutIterGetCharExtents :: LayoutIter -> IO PangoRectangle
-layoutIterGetClusterExtents :: LayoutIter -> IO (PangoRectangle, PangoRectangle)
-layoutIterGetRunExtents :: LayoutIter -> IO (PangoRectangle, PangoRectangle)
-layoutIterGetLineYRange :: LayoutIter -> IO (PangoUnit, PangoUnit)
-layoutIterGetLineExtents :: LayoutIter -> IO (PangoRectangle, PangoRectangle)
-data LayoutLine
-layoutLineGetExtents :: LayoutLine -> IO (PangoRectangle, PangoRectangle)
-layoutLineGetPixelExtents :: LayoutLine -> IO (Rectangle, Rectangle)
-layoutLineIndexToX :: LayoutLine -> Int -> Bool -> IO PangoUnit
-layoutLineXToIndex :: LayoutLine -> PangoUnit -> IO (Bool, Int, Int)
-layoutLineGetXRanges :: LayoutLine -> Int -> Int -> IO [(PangoUnit, PangoUnit)]
-
-module Graphics.UI.Gtk.SourceView.SourceTagStyle
-data SourceTagStyle
-SourceTagStyle :: Bool -> Maybe Color -> Maybe Color -> Bool -> Bool -> Bool -> Bool -> SourceTagStyle
-isDefault :: SourceTagStyle -> Bool
-foreground :: SourceTagStyle -> Maybe Color
-background :: SourceTagStyle -> Maybe Color
-italic :: SourceTagStyle -> Bool
-bold :: SourceTagStyle -> Bool
-underline :: SourceTagStyle -> Bool
-strikethrough :: SourceTagStyle -> Bool
-instance Storable SourceTagStyle
-
-module Graphics.UI.Gtk.SourceView.SourceStyleScheme
-data SourceStyleScheme
-instance GObjectClass SourceStyleScheme
-instance SourceStyleSchemeClass SourceStyleScheme
-castToSourceStyleScheme :: GObjectClass obj => obj -> SourceStyleScheme
-sourceStyleSchemeGetTagStyle :: SourceStyleScheme -> String -> IO SourceTagStyle
-sourceStyleSchemeGetName :: SourceStyleScheme -> IO String
-sourceStyleSchemeGetDefault :: IO SourceStyleScheme
-
-module Graphics.UI.Gtk.SourceView.SourceTag
-data SourceTag
-instance GObjectClass SourceTag
-instance SourceTagClass SourceTag
-instance TextTagClass SourceTag
-castToSourceTag :: GObjectClass obj => obj -> SourceTag
-syntaxTagNew :: String -> String -> String -> String -> IO SourceTag
-patternTagNew :: String -> String -> String -> IO SourceTag
-keywordListTagNew :: String -> String -> [String] -> Bool -> Bool -> Bool -> String -> String -> IO SourceTag
-blockCommentTagNew :: String -> String -> String -> String -> IO SourceTag
-lineCommentTagNew :: String -> String -> String -> IO SourceTag
-stringTagNew :: String -> String -> String -> String -> Bool -> IO SourceTag
-sourceTagGetStyle :: SourceTag -> IO SourceTagStyle
-sourceTagSetStyle :: SourceTag -> SourceTagStyle -> IO ()
-
-module Graphics.UI.Gtk.SourceView.SourceTagTable
-data SourceTagTable
-instance GObjectClass SourceTagTable
-instance SourceTagTableClass SourceTagTable
-instance TextTagTableClass SourceTagTable
-class TextTagTableClass o => SourceTagTableClass o
-instance SourceTagTableClass SourceTagTable
-castToSourceTagTable :: GObjectClass obj => obj -> SourceTagTable
-sourceTagTableNew :: IO SourceTagTable
-sourceTagTableAddTags :: SourceTagTable -> [SourceTag] -> IO ()
-sourceTagTableRemoveSourceTags :: SourceTagTable -> IO ()
-
-module Graphics.UI.Gtk.TreeList.TreeIter
-newtype TreeIter
-TreeIter :: ForeignPtr TreeIter -> TreeIter
-createTreeIter :: Ptr TreeIter -> IO TreeIter
-mallocTreeIter :: IO TreeIter
-receiveTreeIter :: (TreeIter -> IO Bool) -> IO (Maybe TreeIter)
-
-module Graphics.UI.Gtk.Entry.EntryCompletion
-data EntryCompletion
-instance EntryCompletionClass EntryCompletion
-instance GObjectClass EntryCompletion
-class GObjectClass o => EntryCompletionClass o
-instance EntryCompletionClass EntryCompletion
-castToEntryCompletion :: GObjectClass obj => obj -> EntryCompletion
-toEntryCompletion :: EntryCompletionClass o => o -> EntryCompletion
-entryCompletionNew :: IO EntryCompletion
-entryCompletionGetEntry :: EntryCompletion -> IO (Maybe Entry)
-entryCompletionSetModel :: TreeModelClass model => EntryCompletion -> Maybe model -> IO ()
-entryCompletionGetModel :: EntryCompletion -> IO (Maybe TreeModel)
-entryCompletionSetMatchFunc :: EntryCompletion -> (String -> TreeIter -> IO ()) -> IO ()
-entryCompletionSetMinimumKeyLength :: EntryCompletion -> Int -> IO ()
-entryCompletionGetMinimumKeyLength :: EntryCompletion -> IO Int
-entryCompletionComplete :: EntryCompletion -> IO ()
-entryCompletionInsertActionText :: EntryCompletion -> Int -> String -> IO ()
-entryCompletionInsertActionMarkup :: EntryCompletion -> Int -> String -> IO ()
-entryCompletionDeleteAction :: EntryCompletion -> Int -> IO ()
-entryCompletionSetTextColumn :: EntryCompletion -> Int -> IO ()
-entryCompletionInsertPrefix :: EntryCompletion -> IO ()
-entryCompletionGetTextColumn :: EntryCompletion -> IO Int
-entryCompletionSetInlineCompletion :: EntryCompletion -> Bool -> IO ()
-entryCompletionGetInlineCompletion :: EntryCompletion -> IO Bool
-entryCompletionSetPopupCompletion :: EntryCompletion -> Bool -> IO ()
-entryCompletionGetPopupCompletion :: EntryCompletion -> IO Bool
-entryCompletionSetPopupSetWidth :: EntryCompletion -> Bool -> IO ()
-entryCompletionGetPopupSetWidth :: EntryCompletion -> IO Bool
-entryCompletionSetPopupSingleMatch :: EntryCompletion -> Bool -> IO ()
-entryCompletionGetPopupSingleMatch :: EntryCompletion -> IO Bool
-entryCompletionModel :: TreeModelClass model => ReadWriteAttr EntryCompletion (Maybe TreeModel) (Maybe model)
-entryCompletionMinimumKeyLength :: Attr EntryCompletion Int
-entryCompletionTextColumn :: Attr EntryCompletion Int
-entryCompletionInlineCompletion :: Attr EntryCompletion Bool
-entryCompletionPopupCompletion :: Attr EntryCompletion Bool
-entryCompletionPopupSetWidth :: Attr EntryCompletion Bool
-entryCompletionPopupSingleMatch :: Attr EntryCompletion Bool
-onInsertPrefix :: EntryCompletionClass self => self -> (String -> IO Bool) -> IO (ConnectId self)
-afterInsertPrefix :: EntryCompletionClass self => self -> (String -> IO Bool) -> IO (ConnectId self)
-onActionActivated :: EntryCompletionClass self => self -> (Int -> IO ()) -> IO (ConnectId self)
-afterActionActivated :: EntryCompletionClass self => self -> (Int -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.TreeList.TreeModel
-data TreeModel
-instance GObjectClass TreeModel
-instance TreeModelClass TreeModel
-class GObjectClass o => TreeModelClass o
-instance TreeModelClass ListStore
-instance TreeModelClass TreeModel
-instance TreeModelClass TreeModelSort
-instance TreeModelClass TreeStore
-castToTreeModel :: GObjectClass obj => obj -> TreeModel
-toTreeModel :: TreeModelClass o => o -> TreeModel
-data TreeModelFlags
-TreeModelItersPersist :: TreeModelFlags
-TreeModelListOnly :: TreeModelFlags
-instance Bounded TreeModelFlags
-instance Enum TreeModelFlags
-instance Flags TreeModelFlags
-type TreePath = [Int]
-data TreeRowReference
-data TreeIter
-treeModelGetFlags :: TreeModelClass self => self -> IO [TreeModelFlags]
-treeModelGetNColumns :: TreeModelClass self => self -> IO Int
-treeModelGetColumnType :: TreeModelClass self => self -> Int -> IO TMType
-treeModelGetValue :: TreeModelClass self => self -> TreeIter -> Int -> IO GenericValue
-treeRowReferenceNew :: TreeModelClass self => self -> NativeTreePath -> IO TreeRowReference
-treeRowReferenceGetPath :: TreeRowReference -> IO TreePath
-treeRowReferenceValid :: TreeRowReference -> IO Bool
-treeModelGetIter :: TreeModelClass self => self -> TreePath -> IO (Maybe TreeIter)
-treeModelGetIterFromString :: TreeModelClass self => self -> String -> IO (Maybe TreeIter)
-gtk_tree_model_get_iter_from_string :: Ptr TreeModel -> Ptr TreeIter -> Ptr CChar -> IO CInt
-treeModelGetIterFirst :: TreeModelClass self => self -> IO (Maybe TreeIter)
-treeModelGetPath :: TreeModelClass self => self -> TreeIter -> IO TreePath
-treeModelIterNext :: TreeModelClass self => self -> TreeIter -> IO Bool
-treeModelIterChildren :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
-treeModelIterHasChild :: TreeModelClass self => self -> TreeIter -> IO Bool
-treeModelIterNChildren :: TreeModelClass self => self -> Maybe TreeIter -> IO Int
-treeModelIterNthChild :: TreeModelClass self => self -> Maybe TreeIter -> Int -> IO (Maybe TreeIter)
-treeModelIterParent :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
-
-module Graphics.UI.Gtk.TreeList.ListStore
-data ListStore
-instance GObjectClass ListStore
-instance ListStoreClass ListStore
-instance TreeModelClass ListStore
-class TreeModelClass o => ListStoreClass o
-instance ListStoreClass ListStore
-castToListStore :: GObjectClass obj => obj -> ListStore
-toListStore :: ListStoreClass o => o -> ListStore
-data TMType
-TMinvalid :: TMType
-TMuint :: TMType
-TMint :: TMType
-TMboolean :: TMType
-TMenum :: TMType
-TMflags :: TMType
-TMfloat :: TMType
-TMdouble :: TMType
-TMstring :: TMType
-TMobject :: TMType
-instance Enum TMType
-data GenericValue
-GVuint :: Word -> GenericValue
-GVint :: Int -> GenericValue
-GVboolean :: Bool -> GenericValue
-GVenum :: Int -> GenericValue
-GVflags :: Int -> GenericValue
-GVfloat :: Float -> GenericValue
-GVdouble :: Double -> GenericValue
-GVstring :: Maybe String -> GenericValue
-GVobject :: GObject -> GenericValue
-listStoreNew :: [TMType] -> IO ListStore
-listStoreSetValue :: ListStoreClass self => self -> TreeIter -> Int -> GenericValue -> IO ()
-listStoreRemove :: ListStoreClass self => self -> TreeIter -> IO Bool
-listStoreInsert :: ListStoreClass self => self -> Int -> IO TreeIter
-listStoreInsertBefore :: ListStoreClass self => self -> TreeIter -> IO TreeIter
-listStoreInsertAfter :: ListStoreClass self => self -> TreeIter -> IO TreeIter
-listStorePrepend :: ListStoreClass self => self -> IO TreeIter
-listStoreAppend :: ListStoreClass self => self -> IO TreeIter
-listStoreClear :: ListStoreClass self => self -> IO ()
-listStoreReorder :: ListStoreClass self => self -> [Int] -> IO ()
-listStoreSwap :: ListStoreClass self => self -> TreeIter -> TreeIter -> IO ()
-listStoreMoveBefore :: ListStoreClass self => self -> TreeIter -> Maybe TreeIter -> IO ()
-listStoreMoveAfter :: ListStoreClass self => self -> TreeIter -> Maybe TreeIter -> IO ()
-
-module Graphics.UI.Gtk.TreeList.TreeStore
-data TreeStore
-instance GObjectClass TreeStore
-instance TreeModelClass TreeStore
-instance TreeStoreClass TreeStore
-class TreeModelClass o => TreeStoreClass o
-instance TreeStoreClass TreeStore
-castToTreeStore :: GObjectClass obj => obj -> TreeStore
-toTreeStore :: TreeStoreClass o => o -> TreeStore
-data TMType
-TMinvalid :: TMType
-TMuint :: TMType
-TMint :: TMType
-TMboolean :: TMType
-TMenum :: TMType
-TMflags :: TMType
-TMfloat :: TMType
-TMdouble :: TMType
-TMstring :: TMType
-TMobject :: TMType
-instance Enum TMType
-data GenericValue
-GVuint :: Word -> GenericValue
-GVint :: Int -> GenericValue
-GVboolean :: Bool -> GenericValue
-GVenum :: Int -> GenericValue
-GVflags :: Int -> GenericValue
-GVfloat :: Float -> GenericValue
-GVdouble :: Double -> GenericValue
-GVstring :: Maybe String -> GenericValue
-GVobject :: GObject -> GenericValue
-treeStoreNew :: [TMType] -> IO TreeStore
-treeStoreSetValue :: TreeStoreClass self => self -> TreeIter -> Int -> GenericValue -> IO ()
-treeStoreRemove :: TreeStoreClass self => self -> TreeIter -> IO Bool
-treeStoreInsert :: TreeStoreClass self => self -> Maybe TreeIter -> Int -> IO TreeIter
-treeStoreInsertBefore :: TreeStoreClass self => self -> TreeIter -> IO TreeIter
-treeStoreInsertAfter :: TreeStoreClass self => self -> TreeIter -> IO TreeIter
-treeStorePrepend :: TreeStoreClass self => self -> Maybe TreeIter -> IO TreeIter
-treeStoreAppend :: TreeStoreClass self => self -> Maybe TreeIter -> IO TreeIter
-treeStoreIsAncestor :: TreeStoreClass self => self -> TreeIter -> TreeIter -> IO Bool
-treeStoreIterDepth :: TreeStoreClass self => self -> TreeIter -> IO Int
-treeStoreClear :: TreeStoreClass self => self -> IO ()
-
-module Graphics.UI.Gtk.TreeList.TreeModelSort
-data TreeModelSort
-instance GObjectClass TreeModelSort
-instance TreeModelClass TreeModelSort
-instance TreeModelSortClass TreeModelSort
-class GObjectClass o => TreeModelSortClass o
-instance TreeModelSortClass TreeModelSort
-castToTreeModelSort :: GObjectClass obj => obj -> TreeModelSort
-toTreeModelSort :: TreeModelSortClass o => o -> TreeModelSort
-treeModelSortNewWithModel :: TreeModelClass childModel => childModel -> IO TreeModelSort
-treeModelSortGetModel :: TreeModelSortClass self => self -> IO TreeModel
-treeModelSortConvertChildPathToPath :: TreeModelSortClass self => self -> TreePath -> IO TreePath
-treeModelSortConvertPathToChildPath :: TreeModelSortClass self => self -> TreePath -> IO TreePath
-treeModelSortConvertChildIterToIter :: TreeModelSortClass self => self -> TreeIter -> IO TreeIter
-treeModelSortConvertIterToChildIter :: TreeModelSortClass self => self -> TreeIter -> IO TreeIter
-treeModelSortResetDefaultSortFunc :: TreeModelSortClass self => self -> IO ()
-treeModelSortClearCache :: TreeModelSortClass self => self -> IO ()
-treeModelSortIterIsValid :: TreeModelSortClass self => self -> TreeIter -> IO Bool
-
-module Graphics.UI.Gtk.Glade
-class GObjectClass o => GladeXMLClass o
-instance GladeXMLClass GladeXML
-data GladeXML
-instance GObjectClass GladeXML
-instance GladeXMLClass GladeXML
-xmlNew :: FilePath -> IO (Maybe GladeXML)
-xmlNewWithRootAndDomain :: FilePath -> Maybe String -> Maybe String -> IO (Maybe GladeXML)
-xmlGetWidget :: WidgetClass widget => GladeXML -> (GObject -> widget) -> String -> IO widget
-xmlGetWidgetRaw :: GladeXML -> String -> IO (Maybe Widget)
-
-module Graphics.UI.Gtk.Layout.Alignment
-data Alignment
-instance AlignmentClass Alignment
-instance BinClass Alignment
-instance ContainerClass Alignment
-instance GObjectClass Alignment
-instance ObjectClass Alignment
-instance WidgetClass Alignment
-class BinClass o => AlignmentClass o
-instance AlignmentClass Alignment
-castToAlignment :: GObjectClass obj => obj -> Alignment
-toAlignment :: AlignmentClass o => o -> Alignment
-alignmentNew :: Float -> Float -> Float -> Float -> IO Alignment
-alignmentSet :: AlignmentClass self => self -> Float -> Float -> Float -> Float -> IO ()
-alignmentSetPadding :: AlignmentClass self => self -> Int -> Int -> Int -> Int -> IO ()
-alignmentGetPadding :: AlignmentClass self => self -> IO (Int, Int, Int, Int)
-alignmentXAlign :: AlignmentClass self => Attr self Float
-alignmentYAlign :: AlignmentClass self => Attr self Float
-alignmentXScale :: AlignmentClass self => Attr self Float
-alignmentYScale :: AlignmentClass self => Attr self Float
-alignmentTopPadding :: AlignmentClass self => Attr self Int
-alignmentBottomPadding :: AlignmentClass self => Attr self Int
-alignmentLeftPadding :: AlignmentClass self => Attr self Int
-alignmentRightPadding :: AlignmentClass self => Attr self Int
-
-module Graphics.UI.Gtk.Layout.AspectFrame
-data AspectFrame
-instance AspectFrameClass AspectFrame
-instance BinClass AspectFrame
-instance ContainerClass AspectFrame
-instance FrameClass AspectFrame
-instance GObjectClass AspectFrame
-instance ObjectClass AspectFrame
-instance WidgetClass AspectFrame
-class FrameClass o => AspectFrameClass o
-instance AspectFrameClass AspectFrame
-castToAspectFrame :: GObjectClass obj => obj -> AspectFrame
-toAspectFrame :: AspectFrameClass o => o -> AspectFrame
-aspectFrameNew :: Float -> Float -> Maybe Float -> IO AspectFrame
-aspectFrameSet :: AspectFrameClass self => self -> Float -> Float -> Maybe Float -> IO ()
-aspectFrameXAlign :: AspectFrameClass self => Attr self Float
-aspectFrameYAlign :: AspectFrameClass self => Attr self Float
-aspectFrameRatio :: AspectFrameClass self => Attr self Float
-aspectFrameObeyChild :: AspectFrameClass self => Attr self Bool
-
-module Graphics.UI.Gtk.Layout.Expander
-data Expander
-instance BinClass Expander
-instance ContainerClass Expander
-instance ExpanderClass Expander
-instance GObjectClass Expander
-instance ObjectClass Expander
-instance WidgetClass Expander
-class BinClass o => ExpanderClass o
-instance ExpanderClass Expander
-castToExpander :: GObjectClass obj => obj -> Expander
-toExpander :: ExpanderClass o => o -> Expander
-expanderNew :: String -> IO Expander
-expanderNewWithMnemonic :: String -> IO Expander
-expanderSetExpanded :: Expander -> Bool -> IO ()
-expanderGetExpanded :: Expander -> IO Bool
-expanderSetSpacing :: Expander -> Int -> IO ()
-expanderGetSpacing :: Expander -> IO Int
-expanderSetLabel :: Expander -> String -> IO ()
-expanderGetLabel :: Expander -> IO String
-expanderSetUseUnderline :: Expander -> Bool -> IO ()
-expanderGetUseUnderline :: Expander -> IO Bool
-expanderSetUseMarkup :: Expander -> Bool -> IO ()
-expanderGetUseMarkup :: Expander -> IO Bool
-expanderSetLabelWidget :: WidgetClass labelWidget => Expander -> labelWidget -> IO ()
-expanderGetLabelWidget :: Expander -> IO Widget
-expanderExpanded :: Attr Expander Bool
-expanderLabel :: Attr Expander String
-expanderUseUnderline :: Attr Expander Bool
-expanderUseMarkup :: Attr Expander Bool
-expanderSpacing :: Attr Expander Int
-expanderLabelWidget :: WidgetClass labelWidget => ReadWriteAttr Expander Widget labelWidget
-onActivate :: Expander -> IO () -> IO (ConnectId Expander)
-afterActivate :: Expander -> IO () -> IO (ConnectId Expander)
-
-module Graphics.UI.Gtk.Layout.HBox
-data HBox
-instance BoxClass HBox
-instance ContainerClass HBox
-instance GObjectClass HBox
-instance HBoxClass HBox
-instance ObjectClass HBox
-instance WidgetClass HBox
-class BoxClass o => HBoxClass o
-instance HBoxClass Combo
-instance HBoxClass FileChooserButton
-instance HBoxClass HBox
-instance HBoxClass Statusbar
-castToHBox :: GObjectClass obj => obj -> HBox
-toHBox :: HBoxClass o => o -> HBox
-hBoxNew :: Bool -> Int -> IO HBox
-
-module Graphics.UI.Gtk.Layout.HButtonBox
-data HButtonBox
-instance BoxClass HButtonBox
-instance ButtonBoxClass HButtonBox
-instance ContainerClass HButtonBox
-instance GObjectClass HButtonBox
-instance HButtonBoxClass HButtonBox
-instance ObjectClass HButtonBox
-instance WidgetClass HButtonBox
-class ButtonBoxClass o => HButtonBoxClass o
-instance HButtonBoxClass HButtonBox
-castToHButtonBox :: GObjectClass obj => obj -> HButtonBox
-toHButtonBox :: HButtonBoxClass o => o -> HButtonBox
-hButtonBoxNew :: IO HButtonBox
-
-module Graphics.UI.Gtk.Layout.HPaned
-data HPaned
-instance ContainerClass HPaned
-instance GObjectClass HPaned
-instance HPanedClass HPaned
-instance ObjectClass HPaned
-instance PanedClass HPaned
-instance WidgetClass HPaned
-class PanedClass o => HPanedClass o
-instance HPanedClass HPaned
-castToHPaned :: GObjectClass obj => obj -> HPaned
-toHPaned :: HPanedClass o => o -> HPaned
-hPanedNew :: IO HPaned
-
-module Graphics.UI.Gtk.Layout.VBox
-data VBox
-instance BoxClass VBox
-instance ContainerClass VBox
-instance GObjectClass VBox
-instance ObjectClass VBox
-instance VBoxClass VBox
-instance WidgetClass VBox
-class BoxClass o => VBoxClass o
-instance VBoxClass ColorSelection
-instance VBoxClass FileChooserWidget
-instance VBoxClass FontSelection
-instance VBoxClass GammaCurve
-instance VBoxClass VBox
-castToVBox :: GObjectClass obj => obj -> VBox
-toVBox :: VBoxClass o => o -> VBox
-vBoxNew :: Bool -> Int -> IO VBox
-
-module Graphics.UI.Gtk.Layout.VButtonBox
-data VButtonBox
-instance BoxClass VButtonBox
-instance ButtonBoxClass VButtonBox
-instance ContainerClass VButtonBox
-instance GObjectClass VButtonBox
-instance ObjectClass VButtonBox
-instance VButtonBoxClass VButtonBox
-instance WidgetClass VButtonBox
-class ButtonBoxClass o => VButtonBoxClass o
-instance VButtonBoxClass VButtonBox
-castToVButtonBox :: GObjectClass obj => obj -> VButtonBox
-toVButtonBox :: VButtonBoxClass o => o -> VButtonBox
-vButtonBoxNew :: IO VButtonBox
-
-module Graphics.UI.Gtk.Layout.VPaned
-data VPaned
-instance ContainerClass VPaned
-instance GObjectClass VPaned
-instance ObjectClass VPaned
-instance PanedClass VPaned
-instance VPanedClass VPaned
-instance WidgetClass VPaned
-class PanedClass o => VPanedClass o
-instance VPanedClass VPaned
-castToVPaned :: GObjectClass obj => obj -> VPaned
-toVPaned :: VPanedClass o => o -> VPaned
-vPanedNew :: IO VPaned
-
-module Graphics.UI.Gtk.MenuComboToolbar.CheckMenuItem
-data CheckMenuItem
-instance BinClass CheckMenuItem
-instance CheckMenuItemClass CheckMenuItem
-instance ContainerClass CheckMenuItem
-instance GObjectClass CheckMenuItem
-instance ItemClass CheckMenuItem
-instance MenuItemClass CheckMenuItem
-instance ObjectClass CheckMenuItem
-instance WidgetClass CheckMenuItem
-class MenuItemClass o => CheckMenuItemClass o
-instance CheckMenuItemClass CheckMenuItem
-instance CheckMenuItemClass RadioMenuItem
-castToCheckMenuItem :: GObjectClass obj => obj -> CheckMenuItem
-toCheckMenuItem :: CheckMenuItemClass o => o -> CheckMenuItem
-checkMenuItemNew :: IO CheckMenuItem
-checkMenuItemNewWithLabel :: String -> IO CheckMenuItem
-checkMenuItemNewWithMnemonic :: String -> IO CheckMenuItem
-checkMenuItemSetActive :: CheckMenuItemClass self => self -> Bool -> IO ()
-checkMenuItemGetActive :: CheckMenuItemClass self => self -> IO Bool
-checkMenuItemToggled :: CheckMenuItemClass self => self -> IO ()
-checkMenuItemSetInconsistent :: CheckMenuItemClass self => self -> Bool -> IO ()
-checkMenuItemGetInconsistent :: CheckMenuItemClass self => self -> IO Bool
-checkMenuItemGetDrawAsRadio :: CheckMenuItemClass self => self -> IO Bool
-checkMenuItemSetDrawAsRadio :: CheckMenuItemClass self => self -> Bool -> IO ()
-checkMenuItemActive :: CheckMenuItemClass self => Attr self Bool
-checkMenuItemInconsistent :: CheckMenuItemClass self => Attr self Bool
-checkMenuItemDrawAsRadio :: CheckMenuItemClass self => Attr self Bool
-
-module Graphics.UI.Gtk.MenuComboToolbar.ComboBox
-data ComboBox
-instance BinClass ComboBox
-instance ComboBoxClass ComboBox
-instance ContainerClass ComboBox
-instance GObjectClass ComboBox
-instance ObjectClass ComboBox
-instance WidgetClass ComboBox
-class BinClass o => ComboBoxClass o
-instance ComboBoxClass ComboBox
-instance ComboBoxClass ComboBoxEntry
-castToComboBox :: GObjectClass obj => obj -> ComboBox
-toComboBox :: ComboBoxClass o => o -> ComboBox
-comboBoxNew :: IO ComboBox
-comboBoxNewText :: IO ComboBox
-comboBoxNewWithModel :: TreeModelClass model => model -> IO ComboBox
-comboBoxSetWrapWidth :: ComboBoxClass self => self -> Int -> IO ()
-comboBoxSetRowSpanColumn :: ComboBoxClass self => self -> Int -> IO ()
-comboBoxSetColumnSpanColumn :: ComboBoxClass self => self -> Int -> IO ()
-comboBoxGetActive :: ComboBoxClass self => self -> IO (Maybe Int)
-comboBoxSetActive :: ComboBoxClass self => self -> Int -> IO ()
-comboBoxGetActiveIter :: ComboBoxClass self => self -> IO (Maybe TreeIter)
-comboBoxSetActiveIter :: ComboBoxClass self => self -> TreeIter -> IO ()
-comboBoxGetModel :: ComboBoxClass self => self -> IO (Maybe TreeModel)
-comboBoxSetModel :: (ComboBoxClass self, TreeModelClass model) => self -> Maybe model -> IO ()
-comboBoxAppendText :: ComboBoxClass self => self -> String -> IO ()
-comboBoxInsertText :: ComboBoxClass self => self -> Int -> String -> IO ()
-comboBoxPrependText :: ComboBoxClass self => self -> String -> IO ()
-comboBoxRemoveText :: ComboBoxClass self => self -> Int -> IO ()
-comboBoxPopup :: ComboBoxClass self => self -> IO ()
-comboBoxPopdown :: ComboBoxClass self => self -> IO ()
-comboBoxGetWrapWidth :: ComboBoxClass self => self -> IO Int
-comboBoxGetRowSpanColumn :: ComboBoxClass self => self -> IO Int
-comboBoxGetColumnSpanColumn :: ComboBoxClass self => self -> IO Int
-comboBoxGetActiveText :: ComboBoxClass self => self -> IO (Maybe String)
-comboBoxSetAddTearoffs :: ComboBoxClass self => self -> Bool -> IO ()
-comboBoxGetAddTearoffs :: ComboBoxClass self => self -> IO Bool
-comboBoxSetFocusOnClick :: ComboBoxClass self => self -> Bool -> IO ()
-comboBoxGetFocusOnClick :: ComboBoxClass self => self -> IO Bool
-comboBoxModel :: (ComboBoxClass self, TreeModelClass model) => ReadWriteAttr self (Maybe TreeModel) (Maybe model)
-comboBoxWrapWidth :: ComboBoxClass self => Attr self Int
-comboBoxRowSpanColumn :: ComboBoxClass self => Attr self Int
-comboBoxColumnSpanColumn :: ComboBoxClass self => Attr self Int
-comboBoxAddTearoffs :: ComboBoxClass self => Attr self Bool
-comboBoxHasFrame :: ComboBoxClass self => Attr self Bool
-comboBoxFocusOnClick :: ComboBoxClass self => Attr self Bool
-onChanged :: ComboBoxClass self => self -> IO () -> IO (ConnectId self)
-afterChanged :: ComboBoxClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.MenuComboToolbar.ComboBoxEntry
-data ComboBoxEntry
-instance BinClass ComboBoxEntry
-instance ComboBoxClass ComboBoxEntry
-instance ComboBoxEntryClass ComboBoxEntry
-instance ContainerClass ComboBoxEntry
-instance GObjectClass ComboBoxEntry
-instance ObjectClass ComboBoxEntry
-instance WidgetClass ComboBoxEntry
-class ComboBoxClass o => ComboBoxEntryClass o
-instance ComboBoxEntryClass ComboBoxEntry
-castToComboBoxEntry :: GObjectClass obj => obj -> ComboBoxEntry
-toComboBoxEntry :: ComboBoxEntryClass o => o -> ComboBoxEntry
-comboBoxEntryNew :: IO ComboBoxEntry
-comboBoxEntryNewWithModel :: TreeModelClass model => model -> Int -> IO ComboBoxEntry
-comboBoxEntryNewText :: IO ComboBoxEntry
-comboBoxEntrySetTextColumn :: ComboBoxEntryClass self => self -> Int -> IO ()
-comboBoxEntryGetTextColumn :: ComboBoxEntryClass self => self -> IO Int
-comboBoxEntryTextColumn :: ComboBoxEntryClass self => Attr self Int
-
-module Graphics.UI.Gtk.MenuComboToolbar.ImageMenuItem
-data ImageMenuItem
-instance BinClass ImageMenuItem
-instance ContainerClass ImageMenuItem
-instance GObjectClass ImageMenuItem
-instance ImageMenuItemClass ImageMenuItem
-instance ItemClass ImageMenuItem
-instance MenuItemClass ImageMenuItem
-instance ObjectClass ImageMenuItem
-instance WidgetClass ImageMenuItem
-class MenuItemClass o => ImageMenuItemClass o
-instance ImageMenuItemClass ImageMenuItem
-castToImageMenuItem :: GObjectClass obj => obj -> ImageMenuItem
-toImageMenuItem :: ImageMenuItemClass o => o -> ImageMenuItem
-imageMenuItemNew :: IO ImageMenuItem
-imageMenuItemNewFromStock :: String -> IO ImageMenuItem
-imageMenuItemNewWithLabel :: String -> IO ImageMenuItem
-imageMenuItemNewWithMnemonic :: String -> IO ImageMenuItem
-imageMenuItemSetImage :: (ImageMenuItemClass self, WidgetClass image) => self -> image -> IO ()
-imageMenuItemGetImage :: ImageMenuItemClass self => self -> IO (Maybe Widget)
-imageMenuItemImage :: (ImageMenuItemClass self, WidgetClass image) => ReadWriteAttr self (Maybe Widget) image
-
-module Graphics.UI.Gtk.MenuComboToolbar.MenuBar
-data MenuBar
-instance ContainerClass MenuBar
-instance GObjectClass MenuBar
-instance MenuBarClass MenuBar
-instance MenuShellClass MenuBar
-instance ObjectClass MenuBar
-instance WidgetClass MenuBar
-class MenuShellClass o => MenuBarClass o
-instance MenuBarClass MenuBar
-castToMenuBar :: GObjectClass obj => obj -> MenuBar
-toMenuBar :: MenuBarClass o => o -> MenuBar
-data PackDirection
-PackDirectionLtr :: PackDirection
-PackDirectionRtl :: PackDirection
-PackDirectionTtb :: PackDirection
-PackDirectionBtt :: PackDirection
-instance Enum PackDirection
-menuBarNew :: IO MenuBar
-menuBarSetPackDirection :: MenuBarClass self => self -> PackDirection -> IO ()
-menuBarGetPackDirection :: MenuBarClass self => self -> IO PackDirection
-menuBarSetChildPackDirection :: MenuBarClass self => self -> PackDirection -> IO ()
-menuBarGetChildPackDirection :: MenuBarClass self => self -> IO PackDirection
-menuBarPackDirection :: MenuBarClass self => Attr self PackDirection
-menuBarChildPackDirection :: MenuBarClass self => Attr self PackDirection
-
-module Graphics.UI.Gtk.MenuComboToolbar.MenuItem
-data MenuItem
-instance BinClass MenuItem
-instance ContainerClass MenuItem
-instance GObjectClass MenuItem
-instance ItemClass MenuItem
-instance MenuItemClass MenuItem
-instance ObjectClass MenuItem
-instance WidgetClass MenuItem
-class ItemClass o => MenuItemClass o
-instance MenuItemClass CheckMenuItem
-instance MenuItemClass ImageMenuItem
-instance MenuItemClass MenuItem
-instance MenuItemClass RadioMenuItem
-instance MenuItemClass SeparatorMenuItem
-instance MenuItemClass TearoffMenuItem
-castToMenuItem :: GObjectClass obj => obj -> MenuItem
-toMenuItem :: MenuItemClass o => o -> MenuItem
-menuItemNew :: IO MenuItem
-menuItemNewWithLabel :: String -> IO MenuItem
-menuItemNewWithMnemonic :: String -> IO MenuItem
-menuItemSetSubmenu :: (MenuItemClass self, MenuClass submenu) => self -> submenu -> IO ()
-menuItemGetSubmenu :: MenuItemClass self => self -> IO (Maybe Widget)
-menuItemRemoveSubmenu :: MenuItemClass self => self -> IO ()
-menuItemSelect :: MenuItemClass self => self -> IO ()
-menuItemDeselect :: MenuItemClass self => self -> IO ()
-menuItemActivate :: MenuItemClass self => self -> IO ()
-menuItemSetRightJustified :: MenuItemClass self => self -> Bool -> IO ()
-menuItemGetRightJustified :: MenuItemClass self => self -> IO Bool
-menuItemSetAccelPath :: MenuItemClass self => self -> Maybe String -> IO ()
-menuItemSubmenu :: (MenuItemClass self, MenuClass submenu) => ReadWriteAttr self (Maybe Widget) submenu
-menuItemRightJustified :: MenuItemClass self => Attr self Bool
-onActivateItem :: MenuItemClass self => self -> IO () -> IO (ConnectId self)
-afterActivateItem :: MenuItemClass self => self -> IO () -> IO (ConnectId self)
-onActivateLeaf :: MenuItemClass self => self -> IO () -> IO (ConnectId self)
-afterActivateLeaf :: MenuItemClass self => self -> IO () -> IO (ConnectId self)
-onSelect :: ItemClass i => i -> IO () -> IO (ConnectId i)
-afterSelect :: ItemClass i => i -> IO () -> IO (ConnectId i)
-onDeselect :: ItemClass i => i -> IO () -> IO (ConnectId i)
-afterDeselect :: ItemClass i => i -> IO () -> IO (ConnectId i)
-onToggle :: ItemClass i => i -> IO () -> IO (ConnectId i)
-afterToggle :: ItemClass i => i -> IO () -> IO (ConnectId i)
-
-module Graphics.UI.Gtk.MenuComboToolbar.MenuShell
-data MenuShell
-instance ContainerClass MenuShell
-instance GObjectClass MenuShell
-instance MenuShellClass MenuShell
-instance ObjectClass MenuShell
-instance WidgetClass MenuShell
-class ContainerClass o => MenuShellClass o
-instance MenuShellClass Menu
-instance MenuShellClass MenuBar
-instance MenuShellClass MenuShell
-castToMenuShell :: GObjectClass obj => obj -> MenuShell
-toMenuShell :: MenuShellClass o => o -> MenuShell
-menuShellAppend :: (MenuShellClass self, MenuItemClass child) => self -> child -> IO ()
-menuShellPrepend :: (MenuShellClass self, MenuItemClass child) => self -> child -> IO ()
-menuShellInsert :: (MenuShellClass self, MenuItemClass child) => self -> child -> Int -> IO ()
-menuShellDeactivate :: MenuShellClass self => self -> IO ()
-menuShellActivateItem :: (MenuShellClass self, MenuItemClass menuItem) => self -> menuItem -> Bool -> IO ()
-menuShellSelectItem :: (MenuShellClass self, MenuItemClass menuItem) => self -> menuItem -> IO ()
-menuShellDeselect :: MenuShellClass self => self -> IO ()
-menuShellSelectFirst :: MenuShellClass self => self -> Bool -> IO ()
-menuShellCancel :: MenuShellClass self => self -> IO ()
-menuShellSetTakeFocus :: MenuShellClass self => self -> Bool -> IO ()
-menuShellGetTakeFocus :: MenuShellClass self => self -> IO Bool
-menuShellTakeFocus :: MenuShellClass self => Attr self Bool
-onActivateCurrent :: MenuShellClass self => self -> (Bool -> IO ()) -> IO (ConnectId self)
-afterActivateCurrent :: MenuShellClass self => self -> (Bool -> IO ()) -> IO (ConnectId self)
-onCancel :: MenuShellClass self => self -> IO () -> IO (ConnectId self)
-afterCancel :: MenuShellClass self => self -> IO () -> IO (ConnectId self)
-onDeactivated :: MenuShellClass self => self -> IO () -> IO (ConnectId self)
-afterDeactivated :: MenuShellClass self => self -> IO () -> IO (ConnectId self)
-data MenuDirectionType
-MenuDirParent :: MenuDirectionType
-MenuDirChild :: MenuDirectionType
-MenuDirNext :: MenuDirectionType
-MenuDirPrev :: MenuDirectionType
-instance Enum MenuDirectionType
-instance Eq MenuDirectionType
-onMoveCurrent :: MenuShellClass self => self -> (MenuDirectionType -> IO ()) -> IO (ConnectId self)
-afterMoveCurrent :: MenuShellClass self => self -> (MenuDirectionType -> IO ()) -> IO (ConnectId self)
-onSelectionDone :: MenuShellClass self => self -> IO () -> IO (ConnectId self)
-afterSelectionDone :: MenuShellClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.MenuComboToolbar.MenuToolButton
-data MenuToolButton
-instance BinClass MenuToolButton
-instance ContainerClass MenuToolButton
-instance GObjectClass MenuToolButton
-instance MenuToolButtonClass MenuToolButton
-instance ObjectClass MenuToolButton
-instance ToolItemClass MenuToolButton
-instance WidgetClass MenuToolButton
-class ToolItemClass o => MenuToolButtonClass o
-instance MenuToolButtonClass MenuToolButton
-castToMenuToolButton :: GObjectClass obj => obj -> MenuToolButton
-toMenuToolButton :: MenuToolButtonClass o => o -> MenuToolButton
-menuToolButtonNew :: WidgetClass iconWidget => Maybe iconWidget -> Maybe String -> IO MenuToolButton
-menuToolButtonNewFromStock :: String -> IO MenuToolButton
-menuToolButtonSetMenu :: (MenuToolButtonClass self, MenuClass menu) => self -> Maybe menu -> IO ()
-menuToolButtonGetMenu :: MenuToolButtonClass self => self -> IO (Maybe Menu)
-menuToolButtonSetArrowTooltip :: MenuToolButtonClass self => self -> Tooltips -> String -> String -> IO ()
-menuToolButtonMenu :: (MenuToolButtonClass self, MenuClass menu) => ReadWriteAttr self (Maybe Menu) (Maybe menu)
-onShowMenu :: MenuToolButtonClass self => self -> IO () -> IO (ConnectId self)
-afterShowMenu :: MenuToolButtonClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.MenuComboToolbar.OptionMenu
-data OptionMenu
-instance BinClass OptionMenu
-instance ButtonClass OptionMenu
-instance ContainerClass OptionMenu
-instance GObjectClass OptionMenu
-instance ObjectClass OptionMenu
-instance OptionMenuClass OptionMenu
-instance WidgetClass OptionMenu
-class ButtonClass o => OptionMenuClass o
-instance OptionMenuClass OptionMenu
-castToOptionMenu :: GObjectClass obj => obj -> OptionMenu
-toOptionMenu :: OptionMenuClass o => o -> OptionMenu
-optionMenuNew :: IO OptionMenu
-optionMenuGetMenu :: OptionMenuClass self => self -> IO Menu
-optionMenuSetMenu :: (OptionMenuClass self, MenuClass menu) => self -> menu -> IO ()
-optionMenuRemoveMenu :: OptionMenuClass self => self -> IO ()
-optionMenuSetHistory :: OptionMenuClass self => self -> Int -> IO ()
-optionMenuGetHistory :: OptionMenuClass self => self -> IO Int
-optionMenuMenu :: (OptionMenuClass self, MenuClass menu) => ReadWriteAttr self Menu menu
-onOMChanged :: OptionMenuClass self => self -> IO () -> IO (ConnectId self)
-afterOMChanged :: OptionMenuClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.MenuComboToolbar.RadioMenuItem
-data RadioMenuItem
-instance BinClass RadioMenuItem
-instance CheckMenuItemClass RadioMenuItem
-instance ContainerClass RadioMenuItem
-instance GObjectClass RadioMenuItem
-instance ItemClass RadioMenuItem
-instance MenuItemClass RadioMenuItem
-instance ObjectClass RadioMenuItem
-instance RadioMenuItemClass RadioMenuItem
-instance WidgetClass RadioMenuItem
-class CheckMenuItemClass o => RadioMenuItemClass o
-instance RadioMenuItemClass RadioMenuItem
-castToRadioMenuItem :: GObjectClass obj => obj -> RadioMenuItem
-toRadioMenuItem :: RadioMenuItemClass o => o -> RadioMenuItem
-radioMenuItemNew :: IO RadioMenuItem
-radioMenuItemNewWithLabel :: String -> IO RadioMenuItem
-radioMenuItemNewWithMnemonic :: String -> IO RadioMenuItem
-radioMenuItemNewFromWidget :: RadioMenuItem -> IO RadioMenuItem
-radioMenuItemNewWithLabelFromWidget :: RadioMenuItem -> String -> IO RadioMenuItem
-radioMenuItemNewWithMnemonicFromWidget :: RadioMenuItem -> String -> IO RadioMenuItem
-
-module Graphics.UI.Gtk.MenuComboToolbar.RadioToolButton
-data RadioToolButton
-instance BinClass RadioToolButton
-instance ContainerClass RadioToolButton
-instance GObjectClass RadioToolButton
-instance ObjectClass RadioToolButton
-instance RadioToolButtonClass RadioToolButton
-instance ToggleToolButtonClass RadioToolButton
-instance ToolButtonClass RadioToolButton
-instance ToolItemClass RadioToolButton
-instance WidgetClass RadioToolButton
-class ToggleToolButtonClass o => RadioToolButtonClass o
-instance RadioToolButtonClass RadioToolButton
-castToRadioToolButton :: GObjectClass obj => obj -> RadioToolButton
-toRadioToolButton :: RadioToolButtonClass o => o -> RadioToolButton
-radioToolButtonNew :: IO RadioToolButton
-radioToolButtonNewFromStock :: String -> IO RadioToolButton
-radioToolButtonNewFromWidget :: RadioToolButtonClass groupMember => groupMember -> IO RadioToolButton
-radioToolButtonNewWithStockFromWidget :: RadioToolButtonClass groupMember => groupMember -> String -> IO RadioToolButton
-radioToolButtonGetGroup :: RadioToolButtonClass self => self -> IO [RadioToolButton]
-radioToolButtonSetGroup :: RadioToolButtonClass self => self -> RadioToolButton -> IO ()
-radioToolButtonGroup :: RadioToolButtonClass self => ReadWriteAttr self [RadioToolButton] RadioToolButton
-
-module Graphics.UI.Gtk.MenuComboToolbar.SeparatorMenuItem
-data SeparatorMenuItem
-instance BinClass SeparatorMenuItem
-instance ContainerClass SeparatorMenuItem
-instance GObjectClass SeparatorMenuItem
-instance ItemClass SeparatorMenuItem
-instance MenuItemClass SeparatorMenuItem
-instance ObjectClass SeparatorMenuItem
-instance SeparatorMenuItemClass SeparatorMenuItem
-instance WidgetClass SeparatorMenuItem
-class MenuItemClass o => SeparatorMenuItemClass o
-instance SeparatorMenuItemClass SeparatorMenuItem
-castToSeparatorMenuItem :: GObjectClass obj => obj -> SeparatorMenuItem
-toSeparatorMenuItem :: SeparatorMenuItemClass o => o -> SeparatorMenuItem
-separatorMenuItemNew :: IO SeparatorMenuItem
-
-module Graphics.UI.Gtk.MenuComboToolbar.SeparatorToolItem
-data SeparatorToolItem
-instance BinClass SeparatorToolItem
-instance ContainerClass SeparatorToolItem
-instance GObjectClass SeparatorToolItem
-instance ObjectClass SeparatorToolItem
-instance SeparatorToolItemClass SeparatorToolItem
-instance ToolItemClass SeparatorToolItem
-instance WidgetClass SeparatorToolItem
-class ToolItemClass o => SeparatorToolItemClass o
-instance SeparatorToolItemClass SeparatorToolItem
-castToSeparatorToolItem :: GObjectClass obj => obj -> SeparatorToolItem
-toSeparatorToolItem :: SeparatorToolItemClass o => o -> SeparatorToolItem
-separatorToolItemNew :: IO SeparatorToolItem
-separatorToolItemSetDraw :: SeparatorToolItemClass self => self -> Bool -> IO ()
-separatorToolItemGetDraw :: SeparatorToolItemClass self => self -> IO Bool
-separatorToolItemDraw :: SeparatorToolItemClass self => Attr self Bool
-
-module Graphics.UI.Gtk.MenuComboToolbar.TearoffMenuItem
-data TearoffMenuItem
-instance BinClass TearoffMenuItem
-instance ContainerClass TearoffMenuItem
-instance GObjectClass TearoffMenuItem
-instance ItemClass TearoffMenuItem
-instance MenuItemClass TearoffMenuItem
-instance ObjectClass TearoffMenuItem
-instance TearoffMenuItemClass TearoffMenuItem
-instance WidgetClass TearoffMenuItem
-class MenuItemClass o => TearoffMenuItemClass o
-instance TearoffMenuItemClass TearoffMenuItem
-castToTearoffMenuItem :: GObjectClass obj => obj -> TearoffMenuItem
-toTearoffMenuItem :: TearoffMenuItemClass o => o -> TearoffMenuItem
-tearoffMenuItemNew :: IO TearoffMenuItem
-
-module Graphics.UI.Gtk.MenuComboToolbar.ToggleToolButton
-data ToggleToolButton
-instance BinClass ToggleToolButton
-instance ContainerClass ToggleToolButton
-instance GObjectClass ToggleToolButton
-instance ObjectClass ToggleToolButton
-instance ToggleToolButtonClass ToggleToolButton
-instance ToolButtonClass ToggleToolButton
-instance ToolItemClass ToggleToolButton
-instance WidgetClass ToggleToolButton
-class ToolButtonClass o => ToggleToolButtonClass o
-instance ToggleToolButtonClass RadioToolButton
-instance ToggleToolButtonClass ToggleToolButton
-castToToggleToolButton :: GObjectClass obj => obj -> ToggleToolButton
-toToggleToolButton :: ToggleToolButtonClass o => o -> ToggleToolButton
-toggleToolButtonNew :: IO ToggleToolButton
-toggleToolButtonNewFromStock :: String -> IO ToggleToolButton
-toggleToolButtonSetActive :: ToggleToolButtonClass self => self -> Bool -> IO ()
-toggleToolButtonGetActive :: ToggleToolButtonClass self => self -> IO Bool
-toggleToolButtonActive :: ToggleToolButtonClass self => Attr self Bool
-onToolButtonToggled :: ToggleToolButtonClass self => self -> IO () -> IO (ConnectId self)
-afterToolButtonToggled :: ToggleToolButtonClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.MenuComboToolbar.ToolButton
-data ToolButton
-instance BinClass ToolButton
-instance ContainerClass ToolButton
-instance GObjectClass ToolButton
-instance ObjectClass ToolButton
-instance ToolButtonClass ToolButton
-instance ToolItemClass ToolButton
-instance WidgetClass ToolButton
-class ToolItemClass o => ToolButtonClass o
-instance ToolButtonClass RadioToolButton
-instance ToolButtonClass ToggleToolButton
-instance ToolButtonClass ToolButton
-castToToolButton :: GObjectClass obj => obj -> ToolButton
-toToolButton :: ToolButtonClass o => o -> ToolButton
-toolButtonNew :: WidgetClass iconWidget => Maybe iconWidget -> Maybe String -> IO ToolButton
-toolButtonNewFromStock :: String -> IO ToolButton
-toolButtonSetLabel :: ToolButtonClass self => self -> Maybe String -> IO ()
-toolButtonGetLabel :: ToolButtonClass self => self -> IO (Maybe String)
-toolButtonSetUseUnderline :: ToolButtonClass self => self -> Bool -> IO ()
-toolButtonGetUseUnderline :: ToolButtonClass self => self -> IO Bool
-toolButtonSetStockId :: ToolButtonClass self => self -> Maybe String -> IO ()
-toolButtonGetStockId :: ToolButtonClass self => self -> IO (Maybe String)
-toolButtonSetIconWidget :: (ToolButtonClass self, WidgetClass iconWidget) => self -> Maybe iconWidget -> IO ()
-toolButtonGetIconWidget :: ToolButtonClass self => self -> IO (Maybe Widget)
-toolButtonSetLabelWidget :: (ToolButtonClass self, WidgetClass labelWidget) => self -> Maybe labelWidget -> IO ()
-toolButtonGetLabelWidget :: ToolButtonClass self => self -> IO (Maybe Widget)
-toolButtonSetIconName :: ToolButtonClass self => self -> String -> IO ()
-toolButtonGetIconName :: ToolButtonClass self => self -> IO String
-toolButtonLabel :: ToolButtonClass self => Attr self (Maybe String)
-toolButtonUseUnderline :: ToolButtonClass self => Attr self Bool
-toolButtonLabelWidget :: (ToolButtonClass self, WidgetClass labelWidget) => ReadWriteAttr self (Maybe Widget) (Maybe labelWidget)
-toolButtonStockId :: ToolButtonClass self => ReadWriteAttr self (Maybe String) (Maybe String)
-toolButtonIconName :: ToolButtonClass self => Attr self String
-toolButtonIconWidget :: (ToolButtonClass self, WidgetClass iconWidget) => ReadWriteAttr self (Maybe Widget) (Maybe iconWidget)
-onToolButtonClicked :: ToolButtonClass self => self -> IO () -> IO (ConnectId self)
-afterToolButtonClicked :: ToolButtonClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.MenuComboToolbar.ToolItem
-data ToolItem
-instance BinClass ToolItem
-instance ContainerClass ToolItem
-instance GObjectClass ToolItem
-instance ObjectClass ToolItem
-instance ToolItemClass ToolItem
-instance WidgetClass ToolItem
-class BinClass o => ToolItemClass o
-instance ToolItemClass MenuToolButton
-instance ToolItemClass RadioToolButton
-instance ToolItemClass SeparatorToolItem
-instance ToolItemClass ToggleToolButton
-instance ToolItemClass ToolButton
-instance ToolItemClass ToolItem
-castToToolItem :: GObjectClass obj => obj -> ToolItem
-toToolItem :: ToolItemClass o => o -> ToolItem
-toolItemNew :: IO ToolItem
-toolItemSetHomogeneous :: ToolItemClass self => self -> Bool -> IO ()
-toolItemGetHomogeneous :: ToolItemClass self => self -> IO Bool
-toolItemSetExpand :: ToolItemClass self => self -> Bool -> IO ()
-toolItemGetExpand :: ToolItemClass self => self -> IO Bool
-toolItemSetTooltip :: ToolItemClass self => self -> Tooltips -> String -> String -> IO ()
-toolItemSetUseDragWindow :: ToolItemClass self => self -> Bool -> IO ()
-toolItemGetUseDragWindow :: ToolItemClass self => self -> IO Bool
-toolItemSetVisibleHorizontal :: ToolItemClass self => self -> Bool -> IO ()
-toolItemGetVisibleHorizontal :: ToolItemClass self => self -> IO Bool
-toolItemSetVisibleVertical :: ToolItemClass self => self -> Bool -> IO ()
-toolItemGetVisibleVertical :: ToolItemClass self => self -> IO Bool
-toolItemSetIsImportant :: ToolItemClass self => self -> Bool -> IO ()
-toolItemGetIsImportant :: ToolItemClass self => self -> IO Bool
-type IconSize = Int
-toolItemGetIconSize :: ToolItemClass self => self -> IO IconSize
-data Orientation
-OrientationHorizontal :: Orientation
-OrientationVertical :: Orientation
-instance Enum Orientation
-instance Eq Orientation
-toolItemGetOrientation :: ToolItemClass self => self -> IO Orientation
-data ToolbarStyle
-ToolbarIcons :: ToolbarStyle
-ToolbarText :: ToolbarStyle
-ToolbarBoth :: ToolbarStyle
-ToolbarBothHoriz :: ToolbarStyle
-instance Enum ToolbarStyle
-instance Eq ToolbarStyle
-toolItemGetToolbarStyle :: ToolItemClass self => self -> IO ToolbarStyle
-data ReliefStyle
-ReliefNormal :: ReliefStyle
-ReliefHalf :: ReliefStyle
-ReliefNone :: ReliefStyle
-instance Enum ReliefStyle
-instance Eq ReliefStyle
-toolItemGetReliefStyle :: ToolItemClass self => self -> IO ReliefStyle
-toolItemRetrieveProxyMenuItem :: ToolItemClass self => self -> IO (Maybe Widget)
-toolItemGetProxyMenuItem :: ToolItemClass self => self -> String -> IO (Maybe Widget)
-toolItemSetProxyMenuItem :: (ToolItemClass self, MenuItemClass menuItem) => self -> String -> menuItem -> IO ()
-toolItemVisibleHorizontal :: ToolItemClass self => Attr self Bool
-toolItemVisibleVertical :: ToolItemClass self => Attr self Bool
-toolItemIsImportant :: ToolItemClass self => Attr self Bool
-toolItemExpand :: ToolItemClass self => Attr self Bool
-toolItemHomogeneous :: ToolItemClass self => Attr self Bool
-toolItemUseDragWindow :: ToolItemClass self => Attr self Bool
-
-module Graphics.UI.Gtk.Misc.Adjustment
-data Adjustment
-instance AdjustmentClass Adjustment
-instance GObjectClass Adjustment
-instance ObjectClass Adjustment
-class ObjectClass o => AdjustmentClass o
-instance AdjustmentClass Adjustment
-castToAdjustment :: GObjectClass obj => obj -> Adjustment
-toAdjustment :: AdjustmentClass o => o -> Adjustment
-adjustmentNew :: Double -> Double -> Double -> Double -> Double -> Double -> IO Adjustment
-adjustmentSetLower :: Adjustment -> Double -> IO ()
-adjustmentGetLower :: Adjustment -> IO Double
-adjustmentSetPageIncrement :: Adjustment -> Double -> IO ()
-adjustmentGetPageIncrement :: Adjustment -> IO Double
-adjustmentSetPageSize :: Adjustment -> Double -> IO ()
-adjustmentGetPageSize :: Adjustment -> IO Double
-adjustmentSetStepIncrement :: Adjustment -> Double -> IO ()
-adjustmentGetStepIncrement :: Adjustment -> IO Double
-adjustmentSetUpper :: Adjustment -> Double -> IO ()
-adjustmentGetUpper :: Adjustment -> IO Double
-adjustmentSetValue :: Adjustment -> Double -> IO ()
-adjustmentGetValue :: Adjustment -> IO Double
-adjustmentClampPage :: Adjustment -> Double -> Double -> IO ()
-adjustmentValue :: Attr Adjustment Double
-adjustmentLower :: Attr Adjustment Double
-adjustmentUpper :: Attr Adjustment Double
-adjustmentStepIncrement :: Attr Adjustment Double
-adjustmentPageIncrement :: Attr Adjustment Double
-adjustmentPageSize :: Attr Adjustment Double
-onAdjChanged :: Adjustment -> IO () -> IO (ConnectId Adjustment)
-afterAdjChanged :: Adjustment -> IO () -> IO (ConnectId Adjustment)
-onValueChanged :: Adjustment -> IO () -> IO (ConnectId Adjustment)
-afterValueChanged :: Adjustment -> IO () -> IO (ConnectId Adjustment)
-
-module Graphics.UI.Gtk.Misc.Arrow
-data Arrow
-instance ArrowClass Arrow
-instance GObjectClass Arrow
-instance MiscClass Arrow
-instance ObjectClass Arrow
-instance WidgetClass Arrow
-class MiscClass o => ArrowClass o
-instance ArrowClass Arrow
-castToArrow :: GObjectClass obj => obj -> Arrow
-toArrow :: ArrowClass o => o -> Arrow
-data ArrowType
-ArrowUp :: ArrowType
-ArrowDown :: ArrowType
-ArrowLeft :: ArrowType
-ArrowRight :: ArrowType
-instance Enum ArrowType
-instance Eq ArrowType
-data ShadowType
-ShadowNone :: ShadowType
-ShadowIn :: ShadowType
-ShadowOut :: ShadowType
-ShadowEtchedIn :: ShadowType
-ShadowEtchedOut :: ShadowType
-instance Enum ShadowType
-instance Eq ShadowType
-arrowNew :: ArrowType -> ShadowType -> IO Arrow
-arrowSet :: ArrowClass self => self -> ArrowType -> ShadowType -> IO ()
-arrowArrowType :: ArrowClass self => Attr self ArrowType
-arrowShadowType :: ArrowClass self => Attr self ShadowType
-
-module Graphics.UI.Gtk.Misc.Calendar
-data Calendar
-instance CalendarClass Calendar
-instance GObjectClass Calendar
-instance ObjectClass Calendar
-instance WidgetClass Calendar
-class WidgetClass o => CalendarClass o
-instance CalendarClass Calendar
-castToCalendar :: GObjectClass obj => obj -> Calendar
-toCalendar :: CalendarClass o => o -> Calendar
-data CalendarDisplayOptions
-CalendarShowHeading :: CalendarDisplayOptions
-CalendarShowDayNames :: CalendarDisplayOptions
-CalendarNoMonthChange :: CalendarDisplayOptions
-CalendarShowWeekNumbers :: CalendarDisplayOptions
-CalendarWeekStartMonday :: CalendarDisplayOptions
-instance Bounded CalendarDisplayOptions
-instance Enum CalendarDisplayOptions
-instance Eq CalendarDisplayOptions
-instance Flags CalendarDisplayOptions
-calendarNew :: IO Calendar
-calendarSelectMonth :: CalendarClass self => self -> Int -> Int -> IO Bool
-calendarSelectDay :: CalendarClass self => self -> Int -> IO ()
-calendarMarkDay :: CalendarClass self => self -> Int -> IO Bool
-calendarUnmarkDay :: CalendarClass self => self -> Int -> IO Bool
-calendarClearMarks :: CalendarClass self => self -> IO ()
-calendarDisplayOptions :: CalendarClass self => self -> [CalendarDisplayOptions] -> IO ()
-calendarSetDisplayOptions :: CalendarClass self => self -> [CalendarDisplayOptions] -> IO ()
-calendarGetDisplayOptions :: CalendarClass self => self -> IO [CalendarDisplayOptions]
-calendarGetDate :: CalendarClass self => self -> IO (Int, Int, Int)
-calendarFreeze :: CalendarClass self => self -> IO a -> IO a
-calendarYear :: CalendarClass self => Attr self Int
-calendarMonth :: CalendarClass self => Attr self Int
-calendarDay :: CalendarClass self => Attr self Int
-calendarShowHeading :: CalendarClass self => Attr self Bool
-calendarShowDayNames :: CalendarClass self => Attr self Bool
-calendarNoMonthChange :: CalendarClass self => Attr self Bool
-calendarShowWeekNumbers :: CalendarClass self => Attr self Bool
-onDaySelected :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-afterDaySelected :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-onDaySelectedDoubleClick :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-afterDaySelectedDoubleClick :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-onMonthChanged :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-afterMonthChanged :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-onNextMonth :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-afterNextMonth :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-onNextYear :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-afterNextYear :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-onPrevMonth :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-afterPrevMonth :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-onPrevYear :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-afterPrevYear :: CalendarClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Misc.DrawingArea
-data DrawingArea
-instance DrawingAreaClass DrawingArea
-instance GObjectClass DrawingArea
-instance ObjectClass DrawingArea
-instance WidgetClass DrawingArea
-class WidgetClass o => DrawingAreaClass o
-instance DrawingAreaClass Curve
-instance DrawingAreaClass DrawingArea
-castToDrawingArea :: GObjectClass obj => obj -> DrawingArea
-toDrawingArea :: DrawingAreaClass o => o -> DrawingArea
-drawingAreaNew :: IO DrawingArea
-drawingAreaGetDrawWindow :: DrawingArea -> IO DrawWindow
-drawingAreaGetSize :: DrawingArea -> IO (Int, Int)
-
-module Graphics.UI.Gtk.Misc.EventBox
-data EventBox
-instance BinClass EventBox
-instance ContainerClass EventBox
-instance EventBoxClass EventBox
-instance GObjectClass EventBox
-instance ObjectClass EventBox
-instance WidgetClass EventBox
-class BinClass o => EventBoxClass o
-instance EventBoxClass EventBox
-castToEventBox :: GObjectClass obj => obj -> EventBox
-toEventBox :: EventBoxClass o => o -> EventBox
-eventBoxNew :: IO EventBox
-eventBoxSetVisibleWindow :: EventBox -> Bool -> IO ()
-eventBoxGetVisibleWindow :: EventBox -> IO Bool
-eventBoxSetAboveChild :: EventBox -> Bool -> IO ()
-eventBoxGetAboveChild :: EventBox -> IO Bool
-eventBoxVisibleWindow :: Attr EventBox Bool
-eventBoxAboveChild :: Attr EventBox Bool
-
-module Graphics.UI.Gtk.Misc.HandleBox
-data HandleBox
-instance BinClass HandleBox
-instance ContainerClass HandleBox
-instance GObjectClass HandleBox
-instance HandleBoxClass HandleBox
-instance ObjectClass HandleBox
-instance WidgetClass HandleBox
-class BinClass o => HandleBoxClass o
-instance HandleBoxClass HandleBox
-castToHandleBox :: GObjectClass obj => obj -> HandleBox
-toHandleBox :: HandleBoxClass o => o -> HandleBox
-handleBoxNew :: IO HandleBox
-data ShadowType
-ShadowNone :: ShadowType
-ShadowIn :: ShadowType
-ShadowOut :: ShadowType
-ShadowEtchedIn :: ShadowType
-ShadowEtchedOut :: ShadowType
-instance Enum ShadowType
-instance Eq ShadowType
-handleBoxSetShadowType :: HandleBoxClass self => self -> ShadowType -> IO ()
-handleBoxGetShadowType :: HandleBoxClass self => self -> IO ShadowType
-data PositionType
-PosLeft :: PositionType
-PosRight :: PositionType
-PosTop :: PositionType
-PosBottom :: PositionType
-instance Enum PositionType
-instance Eq PositionType
-handleBoxSetHandlePosition :: HandleBoxClass self => self -> PositionType -> IO ()
-handleBoxGetHandlePosition :: HandleBoxClass self => self -> IO PositionType
-handleBoxSetSnapEdge :: HandleBoxClass self => self -> PositionType -> IO ()
-handleBoxGetSnapEdge :: HandleBoxClass self => self -> IO PositionType
-handleBoxShadowType :: HandleBoxClass self => Attr self ShadowType
-handleBoxHandlePosition :: HandleBoxClass self => Attr self PositionType
-handleBoxSnapEdge :: HandleBoxClass self => Attr self PositionType
-handleBoxSnapEdgeSet :: HandleBoxClass self => Attr self Bool
-onChildAttached :: HandleBoxClass self => self -> IO () -> IO (ConnectId self)
-afterChildAttached :: HandleBoxClass self => self -> IO () -> IO (ConnectId self)
-onChildDetached :: HandleBoxClass self => self -> IO () -> IO (ConnectId self)
-afterChildDetached :: HandleBoxClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Misc.Tooltips
-data Tooltips
-instance GObjectClass Tooltips
-instance ObjectClass Tooltips
-instance TooltipsClass Tooltips
-class ObjectClass o => TooltipsClass o
-instance TooltipsClass Tooltips
-castToTooltips :: GObjectClass obj => obj -> Tooltips
-toTooltips :: TooltipsClass o => o -> Tooltips
-tooltipsNew :: IO Tooltips
-tooltipsEnable :: TooltipsClass self => self -> IO ()
-tooltipsDisable :: TooltipsClass self => self -> IO ()
-tooltipsSetDelay :: TooltipsClass self => self -> Int -> IO ()
-tooltipsSetTip :: (TooltipsClass self, WidgetClass widget) => self -> widget -> String -> String -> IO ()
-tooltipsDataGet :: WidgetClass w => w -> IO (Maybe (Tooltips, String, String))
-
-module Graphics.UI.Gtk.Misc.Viewport
-data Viewport
-instance BinClass Viewport
-instance ContainerClass Viewport
-instance GObjectClass Viewport
-instance ObjectClass Viewport
-instance ViewportClass Viewport
-instance WidgetClass Viewport
-class BinClass o => ViewportClass o
-instance ViewportClass Viewport
-castToViewport :: GObjectClass obj => obj -> Viewport
-toViewport :: ViewportClass o => o -> Viewport
-viewportNew :: Adjustment -> Adjustment -> IO Viewport
-viewportGetHAdjustment :: ViewportClass self => self -> IO Adjustment
-viewportGetVAdjustment :: ViewportClass self => self -> IO Adjustment
-viewportSetHAdjustment :: ViewportClass self => self -> Adjustment -> IO ()
-viewportSetVAdjustment :: ViewportClass self => self -> Adjustment -> IO ()
-data ShadowType
-ShadowNone :: ShadowType
-ShadowIn :: ShadowType
-ShadowOut :: ShadowType
-ShadowEtchedIn :: ShadowType
-ShadowEtchedOut :: ShadowType
-instance Enum ShadowType
-instance Eq ShadowType
-viewportSetShadowType :: ViewportClass self => self -> ShadowType -> IO ()
-viewportGetShadowType :: ViewportClass self => self -> IO ShadowType
-viewportHAdjustment :: ViewportClass self => Attr self Adjustment
-viewportVAdjustment :: ViewportClass self => Attr self Adjustment
-viewportShadowType :: ViewportClass self => Attr self ShadowType
-
-module Graphics.UI.Gtk.Mogul.WidgetTable
-type WidgetName = String
-widgetLookup :: WidgetClass w => WidgetName -> String -> (ForeignPtr w -> w) -> IO w
-newNamedWidget :: WidgetClass w => WidgetName -> IO w -> IO w
-isValidName :: WidgetName -> IO Bool
-
-module Graphics.UI.Gtk.Mogul.GetWidget
-getMisc :: String -> IO Misc
-getLabel :: String -> IO Label
-getAccelLabel :: String -> IO AccelLabel
-getTipsQuery :: String -> IO TipsQuery
-getArrow :: String -> IO Arrow
-getImage :: String -> IO Image
-getContainer :: String -> IO Container
-getBin :: String -> IO Bin
-getAlignment :: String -> IO Alignment
-getFrame :: String -> IO Frame
-getAspectFrame :: String -> IO AspectFrame
-getButton :: String -> IO Button
-getToggleButton :: String -> IO ToggleButton
-getCheckButton :: String -> IO CheckButton
-getRadioButton :: String -> IO RadioButton
-getOptionMenu :: String -> IO OptionMenu
-getItem :: String -> IO Item
-getMenuItem :: String -> IO MenuItem
-getCheckMenuItem :: String -> IO CheckMenuItem
-getRadioMenuItem :: String -> IO RadioMenuItem
-getTearoffMenuItem :: String -> IO TearoffMenuItem
-getListItem :: String -> IO ListItem
-getWindow :: String -> IO Window
-getDialog :: String -> IO Dialog
-getColorSelectionDialog :: String -> IO ColorSelectionDialog
-getFileSelection :: String -> IO FileSelection
-getFontSelectionDialog :: String -> IO FontSelectionDialog
-getInputDialog :: String -> IO InputDialog
-getMessageDialog :: String -> IO MessageDialog
-getEventBox :: String -> IO EventBox
-getHandleBox :: String -> IO HandleBox
-getScrolledWindow :: String -> IO ScrolledWindow
-getViewport :: String -> IO Viewport
-getBox :: String -> IO Box
-getButtonBox :: String -> IO ButtonBox
-getHButtonBox :: String -> IO HButtonBox
-getVButtonBox :: String -> IO VButtonBox
-getVBox :: String -> IO VBox
-getColorSelection :: String -> IO ColorSelection
-getFontSelection :: String -> IO FontSelection
-getGammaCurve :: String -> IO GammaCurve
-getHBox :: String -> IO HBox
-getCombo :: String -> IO Combo
-getStatusbar :: String -> IO Statusbar
-getCList :: String -> IO CList
-getCTree :: String -> IO CTree
-getFixed :: String -> IO Fixed
-getPaned :: String -> IO Paned
-getHPaned :: String -> IO HPaned
-getVPaned :: String -> IO VPaned
-getLayout :: String -> IO Layout
-getList :: String -> IO List
-getMenuShell :: String -> IO MenuShell
-getMenu :: String -> IO Menu
-getMenuBar :: String -> IO MenuBar
-getNotebook :: String -> IO Notebook
-getTable :: String -> IO Table
-getTextView :: String -> IO TextView
-getToolbar :: String -> IO Toolbar
-getTreeView :: String -> IO TreeView
-getCalendar :: String -> IO Calendar
-getDrawingArea :: String -> IO DrawingArea
-getCurve :: String -> IO Curve
-getEntry :: String -> IO Entry
-getSpinButton :: String -> IO SpinButton
-getRuler :: String -> IO Ruler
-getHRuler :: String -> IO HRuler
-getVRuler :: String -> IO VRuler
-getRange :: String -> IO Range
-getScale :: String -> IO Scale
-getHScale :: String -> IO HScale
-getVScale :: String -> IO VScale
-getScrollbar :: String -> IO Scrollbar
-getHScrollbar :: String -> IO HScrollbar
-getVScrollbar :: String -> IO VScrollbar
-getSeparator :: String -> IO Separator
-getHSeparator :: String -> IO HSeparator
-getVSeparator :: String -> IO VSeparator
-getInvisible :: String -> IO Invisible
-getPreview :: String -> IO Preview
-getProgressBar :: String -> IO ProgressBar
-
-module Graphics.UI.Gtk.MozEmbed
-data MozEmbed
-instance BinClass MozEmbed
-instance ContainerClass MozEmbed
-instance GObjectClass MozEmbed
-instance MozEmbedClass MozEmbed
-instance ObjectClass MozEmbed
-instance WidgetClass MozEmbed
-mozEmbedNew :: IO MozEmbed
-mozEmbedSetCompPath :: String -> IO ()
-mozEmbedDefaultCompPath :: String
-mozEmbedSetProfilePath :: FilePath -> String -> IO ()
-mozEmbedPushStartup :: IO ()
-mozEmbedPopStartup :: IO ()
-mozEmbedLoadUrl :: MozEmbed -> String -> IO ()
-mozEmbedStopLoad :: MozEmbed -> IO ()
-mozEmbedRenderData :: MozEmbed -> String -> String -> String -> IO ()
-mozEmbedOpenStream :: MozEmbed -> String -> String -> IO ()
-mozEmbedAppendData :: MozEmbed -> String -> IO ()
-mozEmbedCloseStream :: MozEmbed -> IO ()
-mozEmbedGoBack :: MozEmbed -> IO ()
-mozEmbedGoForward :: MozEmbed -> IO ()
-mozEmbedCanGoBack :: MozEmbed -> IO Bool
-mozEmbedCanGoForward :: MozEmbed -> IO Bool
-mozEmbedGetTitle :: MozEmbed -> IO String
-mozEmbedGetLocation :: MozEmbed -> IO String
-mozEmbedGetLinkMessage :: MozEmbed -> IO String
-mozEmbedGetJsStatus :: MozEmbed -> IO String
-onOpenURI :: MozEmbed -> (String -> IO Bool) -> IO (ConnectId MozEmbed)
-onKeyDown :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onKeyPress :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onKeyUp :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onMouseDown :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onMouseUp :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onMouseClick :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onMouseDoubleClick :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onMouseOver :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-onMouseOut :: MozEmbed -> (Ptr a -> IO Int) -> IO (ConnectId MozEmbed)
-
-module Graphics.UI.Gtk.Multiline.TextView
-data TextView
-instance ContainerClass TextView
-instance GObjectClass TextView
-instance ObjectClass TextView
-instance TextViewClass TextView
-instance WidgetClass TextView
-class ContainerClass o => TextViewClass o
-instance TextViewClass SourceView
-instance TextViewClass TextView
-data TextChildAnchor
-instance GObjectClass TextChildAnchor
-instance TextChildAnchorClass TextChildAnchor
-class GObjectClass o => TextChildAnchorClass o
-instance TextChildAnchorClass TextChildAnchor
-castToTextView :: GObjectClass obj => obj -> TextView
-toTextView :: TextViewClass o => o -> TextView
-data DeleteType
-DeleteChars :: DeleteType
-DeleteWordEnds :: DeleteType
-DeleteWords :: DeleteType
-DeleteDisplayLines :: DeleteType
-DeleteDisplayLineEnds :: DeleteType
-DeleteParagraphEnds :: DeleteType
-DeleteParagraphs :: DeleteType
-DeleteWhitespace :: DeleteType
-instance Enum DeleteType
-instance Eq DeleteType
-data DirectionType
-DirTabForward :: DirectionType
-DirTabBackward :: DirectionType
-DirUp :: DirectionType
-DirDown :: DirectionType
-DirLeft :: DirectionType
-DirRight :: DirectionType
-instance Enum DirectionType
-instance Eq DirectionType
-data Justification
-JustifyLeft :: Justification
-JustifyRight :: Justification
-JustifyCenter :: Justification
-JustifyFill :: Justification
-instance Enum Justification
-instance Eq Justification
-data MovementStep
-MovementLogicalPositions :: MovementStep
-MovementVisualPositions :: MovementStep
-MovementWords :: MovementStep
-MovementDisplayLines :: MovementStep
-MovementDisplayLineEnds :: MovementStep
-MovementParagraphs :: MovementStep
-MovementParagraphEnds :: MovementStep
-MovementPages :: MovementStep
-MovementBufferEnds :: MovementStep
-MovementHorizontalPages :: MovementStep
-instance Enum MovementStep
-instance Eq MovementStep
-data TextWindowType
-TextWindowPrivate :: TextWindowType
-TextWindowWidget :: TextWindowType
-TextWindowText :: TextWindowType
-TextWindowLeft :: TextWindowType
-TextWindowRight :: TextWindowType
-TextWindowTop :: TextWindowType
-TextWindowBottom :: TextWindowType
-instance Enum TextWindowType
-instance Eq TextWindowType
-data WrapMode
-WrapNone :: WrapMode
-WrapChar :: WrapMode
-WrapWord :: WrapMode
-WrapWordChar :: WrapMode
-instance Enum WrapMode
-instance Eq WrapMode
-textViewNew :: IO TextView
-textViewNewWithBuffer :: TextBufferClass buffer => buffer -> IO TextView
-textViewSetBuffer :: (TextViewClass self, TextBufferClass buffer) => self -> buffer -> IO ()
-textViewGetBuffer :: TextViewClass self => self -> IO TextBuffer
-textViewScrollToMark :: (TextViewClass self, TextMarkClass mark) => self -> mark -> Double -> Maybe (Double, Double) -> IO ()
-textViewScrollToIter :: TextViewClass self => self -> TextIter -> Double -> Maybe (Double, Double) -> IO Bool
-textViewScrollMarkOnscreen :: (TextViewClass self, TextMarkClass mark) => self -> mark -> IO ()
-textViewMoveMarkOnscreen :: (TextViewClass self, TextMarkClass mark) => self -> mark -> IO Bool
-textViewPlaceCursorOnscreen :: TextViewClass self => self -> IO Bool
-textViewGetLineAtY :: TextViewClass self => self -> Int -> IO (TextIter, Int)
-textViewGetLineYrange :: TextViewClass self => self -> TextIter -> IO (Int, Int)
-textViewGetIterAtLocation :: TextViewClass self => self -> Int -> Int -> IO TextIter
-textViewBufferToWindowCoords :: TextViewClass self => self -> TextWindowType -> (Int, Int) -> IO (Int, Int)
-textViewWindowToBufferCoords :: TextViewClass self => self -> TextWindowType -> (Int, Int) -> IO (Int, Int)
-textViewGetWindow :: TextViewClass self => self -> TextWindowType -> IO (Maybe DrawWindow)
-textViewGetWindowType :: TextViewClass self => self -> DrawWindow -> IO TextWindowType
-textViewSetBorderWindowSize :: TextViewClass self => self -> TextWindowType -> Int -> IO ()
-textViewGetBorderWindowSize :: TextViewClass self => self -> TextWindowType -> IO Int
-textViewForwardDisplayLine :: TextViewClass self => self -> TextIter -> IO Bool
-textViewBackwardDisplayLine :: TextViewClass self => self -> TextIter -> IO Bool
-textViewForwardDisplayLineEnd :: TextViewClass self => self -> TextIter -> IO Bool
-textViewBackwardDisplayLineStart :: TextViewClass self => self -> TextIter -> IO Bool
-textViewStartsDisplayLine :: TextViewClass self => self -> TextIter -> IO Bool
-textViewMoveVisually :: TextViewClass self => self -> TextIter -> Int -> IO Bool
-textViewAddChildAtAnchor :: (TextViewClass self, WidgetClass child) => self -> child -> TextChildAnchor -> IO ()
-textChildAnchorNew :: IO TextChildAnchor
-textChildAnchorGetWidgets :: TextChildAnchor -> IO [Widget]
-textChildAnchorGetDeleted :: TextChildAnchor -> IO Bool
-textViewAddChildInWindow :: (TextViewClass self, WidgetClass child) => self -> child -> TextWindowType -> Int -> Int -> IO ()
-textViewMoveChild :: (TextViewClass self, WidgetClass child) => self -> child -> Int -> Int -> IO ()
-textViewSetWrapMode :: TextViewClass self => self -> WrapMode -> IO ()
-textViewGetWrapMode :: TextViewClass self => self -> IO WrapMode
-textViewSetEditable :: TextViewClass self => self -> Bool -> IO ()
-textViewGetEditable :: TextViewClass self => self -> IO Bool
-textViewSetCursorVisible :: TextViewClass self => self -> Bool -> IO ()
-textViewGetCursorVisible :: TextViewClass self => self -> IO Bool
-textViewSetPixelsAboveLines :: TextViewClass self => self -> Int -> IO ()
-textViewGetPixelsAboveLines :: TextViewClass self => self -> IO Int
-textViewSetPixelsBelowLines :: TextViewClass self => self -> Int -> IO ()
-textViewGetPixelsBelowLines :: TextViewClass self => self -> IO Int
-textViewSetPixelsInsideWrap :: TextViewClass self => self -> Int -> IO ()
-textViewGetPixelsInsideWrap :: TextViewClass self => self -> IO Int
-textViewSetJustification :: TextViewClass self => self -> Justification -> IO ()
-textViewGetJustification :: TextViewClass self => self -> IO Justification
-textViewSetLeftMargin :: TextViewClass self => self -> Int -> IO ()
-textViewGetLeftMargin :: TextViewClass self => self -> IO Int
-textViewSetRightMargin :: TextViewClass self => self -> Int -> IO ()
-textViewGetRightMargin :: TextViewClass self => self -> IO Int
-textViewSetIndent :: TextViewClass self => self -> Int -> IO ()
-textViewGetIndent :: TextViewClass self => self -> IO Int
-textViewGetDefaultAttributes :: TextViewClass self => self -> IO TextAttributes
-textViewGetVisibleRect :: TextViewClass self => self -> IO Rectangle
-textViewGetIterLocation :: TextViewClass self => self -> TextIter -> IO Rectangle
-textViewGetIterAtPosition :: TextViewClass self => self -> Int -> Int -> IO (TextIter, Int)
-textViewSetOverwrite :: TextViewClass self => self -> Bool -> IO ()
-textViewGetOverwrite :: TextViewClass self => self -> IO Bool
-textViewSetAcceptsTab :: TextViewClass self => self -> Bool -> IO ()
-textViewGetAcceptsTab :: TextViewClass self => self -> IO Bool
-textViewPixelsAboveLines :: TextViewClass self => Attr self Int
-textViewPixelsBelowLines :: TextViewClass self => Attr self Int
-textViewPixelsInsideWrap :: TextViewClass self => Attr self Int
-textViewEditable :: TextViewClass self => Attr self Bool
-textViewWrapMode :: TextViewClass self => Attr self WrapMode
-textViewJustification :: TextViewClass self => Attr self Justification
-textViewLeftMargin :: TextViewClass self => Attr self Int
-textViewRightMargin :: TextViewClass self => Attr self Int
-textViewIndent :: TextViewClass self => Attr self Int
-textViewCursorVisible :: TextViewClass self => Attr self Bool
-textViewBuffer :: TextViewClass self => Attr self TextBuffer
-textViewOverwrite :: TextViewClass self => Attr self Bool
-textViewAcceptsTab :: TextViewClass self => Attr self Bool
-onCopyClipboard :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-afterCopyClipboard :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-onCutClipboard :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-afterCutClipboard :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-onDeleteFromCursor :: TextViewClass self => self -> (DeleteType -> Int -> IO ()) -> IO (ConnectId self)
-afterDeleteFromCursor :: TextViewClass self => self -> (DeleteType -> Int -> IO ()) -> IO (ConnectId self)
-onInsertAtCursor :: TextViewClass self => self -> (String -> IO ()) -> IO (ConnectId self)
-afterInsertAtCursor :: TextViewClass self => self -> (String -> IO ()) -> IO (ConnectId self)
-onMoveCursor :: TextViewClass self => self -> (MovementStep -> Int -> Bool -> IO ()) -> IO (ConnectId self)
-afterMoveCursor :: TextViewClass self => self -> (MovementStep -> Int -> Bool -> IO ()) -> IO (ConnectId self)
-onMoveFocus :: TextViewClass self => self -> (DirectionType -> IO ()) -> IO (ConnectId self)
-afterMoveFocus :: TextViewClass self => self -> (DirectionType -> IO ()) -> IO (ConnectId self)
-onPageHorizontally :: TextViewClass self => self -> (Int -> Bool -> IO ()) -> IO (ConnectId self)
-afterPageHorizontally :: TextViewClass self => self -> (Int -> Bool -> IO ()) -> IO (ConnectId self)
-onPasteClipboard :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-afterPasteClipboard :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-onPopulatePopup :: TextViewClass self => self -> (Menu -> IO ()) -> IO (ConnectId self)
-afterPopulatePopup :: TextViewClass self => self -> (Menu -> IO ()) -> IO (ConnectId self)
-onSetAnchor :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-afterSetAnchor :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-onSetScrollAdjustments :: TextViewClass self => self -> (Adjustment -> Adjustment -> IO ()) -> IO (ConnectId self)
-afterSetScrollAdjustments :: TextViewClass self => self -> (Adjustment -> Adjustment -> IO ()) -> IO (ConnectId self)
-onToggleOverwrite :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-afterToggleOverwrite :: TextViewClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Ornaments.Frame
-data Frame
-instance BinClass Frame
-instance ContainerClass Frame
-instance FrameClass Frame
-instance GObjectClass Frame
-instance ObjectClass Frame
-instance WidgetClass Frame
-class BinClass o => FrameClass o
-instance FrameClass AspectFrame
-instance FrameClass Frame
-castToFrame :: GObjectClass obj => obj -> Frame
-toFrame :: FrameClass o => o -> Frame
-frameNew :: IO Frame
-frameSetLabel :: FrameClass self => self -> String -> IO ()
-frameGetLabel :: FrameClass self => self -> IO String
-frameSetLabelWidget :: (FrameClass self, WidgetClass labelWidget) => self -> labelWidget -> IO ()
-frameGetLabelWidget :: FrameClass self => self -> IO (Maybe Widget)
-frameSetLabelAlign :: FrameClass self => self -> Float -> Float -> IO ()
-frameGetLabelAlign :: FrameClass self => self -> IO (Float, Float)
-data ShadowType
-ShadowNone :: ShadowType
-ShadowIn :: ShadowType
-ShadowOut :: ShadowType
-ShadowEtchedIn :: ShadowType
-ShadowEtchedOut :: ShadowType
-instance Enum ShadowType
-instance Eq ShadowType
-frameSetShadowType :: FrameClass self => self -> ShadowType -> IO ()
-frameGetShadowType :: FrameClass self => self -> IO ShadowType
-frameLabel :: FrameClass self => Attr self String
-frameLabelXAlign :: FrameClass self => Attr self Float
-frameLabelYAlign :: FrameClass self => Attr self Float
-frameShadowType :: FrameClass self => Attr self ShadowType
-frameLabelWidget :: (FrameClass self, WidgetClass labelWidget) => ReadWriteAttr self (Maybe Widget) labelWidget
-
-module Graphics.UI.Gtk.Ornaments.HSeparator
-data HSeparator
-instance GObjectClass HSeparator
-instance HSeparatorClass HSeparator
-instance ObjectClass HSeparator
-instance SeparatorClass HSeparator
-instance WidgetClass HSeparator
-class SeparatorClass o => HSeparatorClass o
-instance HSeparatorClass HSeparator
-castToHSeparator :: GObjectClass obj => obj -> HSeparator
-toHSeparator :: HSeparatorClass o => o -> HSeparator
-hSeparatorNew :: IO HSeparator
-
-module Graphics.UI.Gtk.Ornaments.VSeparator
-data VSeparator
-instance GObjectClass VSeparator
-instance ObjectClass VSeparator
-instance SeparatorClass VSeparator
-instance VSeparatorClass VSeparator
-instance WidgetClass VSeparator
-class SeparatorClass o => VSeparatorClass o
-instance VSeparatorClass VSeparator
-castToVSeparator :: GObjectClass obj => obj -> VSeparator
-toVSeparator :: VSeparatorClass o => o -> VSeparator
-vSeparatorNew :: IO VSeparator
-
-module Graphics.UI.Gtk.Scrolling.HScrollbar
-data HScrollbar
-instance GObjectClass HScrollbar
-instance HScrollbarClass HScrollbar
-instance ObjectClass HScrollbar
-instance RangeClass HScrollbar
-instance ScrollbarClass HScrollbar
-instance WidgetClass HScrollbar
-class ScrollbarClass o => HScrollbarClass o
-instance HScrollbarClass HScrollbar
-castToHScrollbar :: GObjectClass obj => obj -> HScrollbar
-toHScrollbar :: HScrollbarClass o => o -> HScrollbar
-hScrollbarNew :: Adjustment -> IO HScrollbar
-hScrollbarNewDefaults :: IO HScrollbar
-
-module Graphics.UI.Gtk.Scrolling.ScrolledWindow
-data ScrolledWindow
-instance BinClass ScrolledWindow
-instance ContainerClass ScrolledWindow
-instance GObjectClass ScrolledWindow
-instance ObjectClass ScrolledWindow
-instance ScrolledWindowClass ScrolledWindow
-instance WidgetClass ScrolledWindow
-class BinClass o => ScrolledWindowClass o
-instance ScrolledWindowClass ScrolledWindow
-castToScrolledWindow :: GObjectClass obj => obj -> ScrolledWindow
-toScrolledWindow :: ScrolledWindowClass o => o -> ScrolledWindow
-scrolledWindowNew :: Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow
-scrolledWindowGetHAdjustment :: ScrolledWindowClass self => self -> IO Adjustment
-scrolledWindowGetVAdjustment :: ScrolledWindowClass self => self -> IO Adjustment
-data PolicyType
-PolicyAlways :: PolicyType
-PolicyAutomatic :: PolicyType
-PolicyNever :: PolicyType
-instance Enum PolicyType
-instance Eq PolicyType
-scrolledWindowSetPolicy :: ScrolledWindowClass self => self -> PolicyType -> PolicyType -> IO ()
-scrolledWindowGetPolicy :: ScrolledWindowClass self => self -> IO (PolicyType, PolicyType)
-scrolledWindowAddWithViewport :: (ScrolledWindowClass self, WidgetClass child) => self -> child -> IO ()
-data CornerType
-CornerTopLeft :: CornerType
-CornerBottomLeft :: CornerType
-CornerTopRight :: CornerType
-CornerBottomRight :: CornerType
-instance Enum CornerType
-instance Eq CornerType
-scrolledWindowSetPlacement :: ScrolledWindowClass self => self -> CornerType -> IO ()
-scrolledWindowGetPlacement :: ScrolledWindowClass self => self -> IO CornerType
-data ShadowType
-ShadowNone :: ShadowType
-ShadowIn :: ShadowType
-ShadowOut :: ShadowType
-ShadowEtchedIn :: ShadowType
-ShadowEtchedOut :: ShadowType
-instance Enum ShadowType
-instance Eq ShadowType
-scrolledWindowSetShadowType :: ScrolledWindowClass self => self -> ShadowType -> IO ()
-scrolledWindowGetShadowType :: ScrolledWindowClass self => self -> IO ShadowType
-scrolledWindowSetHAdjustment :: ScrolledWindowClass self => self -> Adjustment -> IO ()
-scrolledWindowSetVAdjustment :: ScrolledWindowClass self => self -> Adjustment -> IO ()
-scrolledWindowGetHScrollbar :: ScrolledWindowClass self => self -> IO (Maybe HScrollbar)
-scrolledWindowGetVScrollbar :: ScrolledWindowClass self => self -> IO (Maybe VScrollbar)
-scrolledWindowHAdjustment :: ScrolledWindowClass self => Attr self Adjustment
-scrolledWindowVAdjustment :: ScrolledWindowClass self => Attr self Adjustment
-scrolledWindowHscrollbarPolicy :: ScrolledWindowClass self => Attr self PolicyType
-scrolledWindowVscrollbarPolicy :: ScrolledWindowClass self => Attr self PolicyType
-scrolledWindowWindowPlacement :: ScrolledWindowClass self => Attr self CornerType
-scrolledWindowShadowType :: ScrolledWindowClass self => Attr self ShadowType
-scrolledWindowPlacement :: ScrolledWindowClass self => Attr self CornerType
-
-module Graphics.UI.Gtk.Scrolling.VScrollbar
-data VScrollbar
-instance GObjectClass VScrollbar
-instance ObjectClass VScrollbar
-instance RangeClass VScrollbar
-instance ScrollbarClass VScrollbar
-instance VScrollbarClass VScrollbar
-instance WidgetClass VScrollbar
-class ScrollbarClass o => VScrollbarClass o
-instance VScrollbarClass VScrollbar
-castToVScrollbar :: GObjectClass obj => obj -> VScrollbar
-toVScrollbar :: VScrollbarClass o => o -> VScrollbar
-vScrollbarNew :: Adjustment -> IO VScrollbar
-vScrollbarNewDefaults :: IO VScrollbar
-
-module Graphics.UI.Gtk.Selectors.ColorButton
-data ColorButton
-instance BinClass ColorButton
-instance ButtonClass ColorButton
-instance ColorButtonClass ColorButton
-instance ContainerClass ColorButton
-instance GObjectClass ColorButton
-instance ObjectClass ColorButton
-instance WidgetClass ColorButton
-class ButtonClass o => ColorButtonClass o
-instance ColorButtonClass ColorButton
-castToColorButton :: GObjectClass obj => obj -> ColorButton
-toColorButton :: ColorButtonClass o => o -> ColorButton
-colorButtonNew :: IO ColorButton
-colorButtonNewWithColor :: Color -> IO ColorButton
-colorButtonSetColor :: ColorButtonClass self => self -> Color -> IO ()
-colorButtonGetColor :: ColorButtonClass self => self -> IO Color
-colorButtonSetAlpha :: ColorButtonClass self => self -> Word16 -> IO ()
-colorButtonGetAlpha :: ColorButtonClass self => self -> IO Word16
-colorButtonSetUseAlpha :: ColorButtonClass self => self -> Bool -> IO ()
-colorButtonGetUseAlpha :: ColorButtonClass self => self -> IO Bool
-colorButtonSetTitle :: ColorButtonClass self => self -> String -> IO ()
-colorButtonGetTitle :: ColorButtonClass self => self -> IO String
-colorButtonUseAlpha :: ColorButtonClass self => Attr self Bool
-colorButtonTitle :: ColorButtonClass self => Attr self String
-colorButtonAlpha :: ColorButtonClass self => Attr self Word16
-onColorSet :: ColorButtonClass self => self -> IO () -> IO (ConnectId self)
-afterColorSet :: ColorButtonClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Selectors.ColorSelection
-data ColorSelection
-instance BoxClass ColorSelection
-instance ColorSelectionClass ColorSelection
-instance ContainerClass ColorSelection
-instance GObjectClass ColorSelection
-instance ObjectClass ColorSelection
-instance VBoxClass ColorSelection
-instance WidgetClass ColorSelection
-class VBoxClass o => ColorSelectionClass o
-instance ColorSelectionClass ColorSelection
-castToColorSelection :: GObjectClass obj => obj -> ColorSelection
-toColorSelection :: ColorSelectionClass o => o -> ColorSelection
-colorSelectionNew :: IO ColorSelection
-colorSelectionGetCurrentAlpha :: ColorSelectionClass self => self -> IO Int
-colorSelectionSetCurrentAlpha :: ColorSelectionClass self => self -> Int -> IO ()
-colorSelectionGetCurrentColor :: ColorSelectionClass self => self -> IO Color
-colorSelectionSetCurrentColor :: ColorSelectionClass self => self -> Color -> IO ()
-colorSelectionGetHasOpacityControl :: ColorSelectionClass self => self -> IO Bool
-colorSelectionSetHasOpacityControl :: ColorSelectionClass self => self -> Bool -> IO ()
-colorSelectionGetHasPalette :: ColorSelectionClass self => self -> IO Bool
-colorSelectionSetHasPalette :: ColorSelectionClass self => self -> Bool -> IO ()
-colorSelectionGetPreviousAlpha :: ColorSelectionClass self => self -> IO Int
-colorSelectionSetPreviousAlpha :: ColorSelectionClass self => self -> Int -> IO ()
-colorSelectionGetPreviousColor :: ColorSelectionClass self => self -> IO Color
-colorSelectionSetPreviousColor :: ColorSelectionClass self => self -> Color -> IO ()
-colorSelectionIsAdjusting :: ColorSelectionClass self => self -> IO Bool
-colorSelectionHasOpacityControl :: ColorSelectionClass self => Attr self Bool
-colorSelectionHasPalette :: ColorSelectionClass self => Attr self Bool
-colorSelectionCurrentAlpha :: ColorSelectionClass self => Attr self Int
-colorSelectionPreviousAlpha :: ColorSelectionClass self => Attr self Int
-
-module Graphics.UI.Gtk.Selectors.ColorSelectionDialog
-data ColorSelectionDialog
-instance BinClass ColorSelectionDialog
-instance ColorSelectionDialogClass ColorSelectionDialog
-instance ContainerClass ColorSelectionDialog
-instance DialogClass ColorSelectionDialog
-instance GObjectClass ColorSelectionDialog
-instance ObjectClass ColorSelectionDialog
-instance WidgetClass ColorSelectionDialog
-instance WindowClass ColorSelectionDialog
-class DialogClass o => ColorSelectionDialogClass o
-instance ColorSelectionDialogClass ColorSelectionDialog
-castToColorSelectionDialog :: GObjectClass obj => obj -> ColorSelectionDialog
-toColorSelectionDialog :: ColorSelectionDialogClass o => o -> ColorSelectionDialog
-colorSelectionDialogNew :: String -> IO ColorSelectionDialog
-
-module Graphics.UI.Gtk.Selectors.FileChooser
-data FileChooser
-instance FileChooserClass FileChooser
-instance GObjectClass FileChooser
-class GObjectClass o => FileChooserClass o
-instance FileChooserClass FileChooser
-instance FileChooserClass FileChooserButton
-instance FileChooserClass FileChooserDialog
-instance FileChooserClass FileChooserWidget
-castToFileChooser :: GObjectClass obj => obj -> FileChooser
-toFileChooser :: FileChooserClass o => o -> FileChooser
-data FileChooserAction
-FileChooserActionOpen :: FileChooserAction
-FileChooserActionSave :: FileChooserAction
-FileChooserActionSelectFolder :: FileChooserAction
-FileChooserActionCreateFolder :: FileChooserAction
-instance Enum FileChooserAction
-data FileChooserError
-FileChooserErrorNonexistent :: FileChooserError
-FileChooserErrorBadFilename :: FileChooserError
-instance Enum FileChooserError
-instance GErrorClass FileChooserError
-data FileChooserConfirmation
-FileChooserConfirmationConfirm :: FileChooserConfirmation
-FileChooserConfirmationAcceptFilename :: FileChooserConfirmation
-FileChooserConfirmationSelectAgain :: FileChooserConfirmation
-instance Enum FileChooserConfirmation
-fileChooserSetAction :: FileChooserClass self => self -> FileChooserAction -> IO ()
-fileChooserGetAction :: FileChooserClass self => self -> IO FileChooserAction
-fileChooserSetLocalOnly :: FileChooserClass self => self -> Bool -> IO ()
-fileChooserGetLocalOnly :: FileChooserClass self => self -> IO Bool
-fileChooserSetSelectMultiple :: FileChooserClass self => self -> Bool -> IO ()
-fileChooserGetSelectMultiple :: FileChooserClass self => self -> IO Bool
-fileChooserSetCurrentName :: FileChooserClass self => self -> FilePath -> IO ()
-fileChooserGetFilename :: FileChooserClass self => self -> IO (Maybe FilePath)
-fileChooserSetFilename :: FileChooserClass self => self -> FilePath -> IO Bool
-fileChooserSelectFilename :: FileChooserClass self => self -> FilePath -> IO Bool
-fileChooserUnselectFilename :: FileChooserClass self => self -> FilePath -> IO ()
-fileChooserSelectAll :: FileChooserClass self => self -> IO ()
-fileChooserUnselectAll :: FileChooserClass self => self -> IO ()
-fileChooserGetFilenames :: FileChooserClass self => self -> IO [FilePath]
-fileChooserSetCurrentFolder :: FileChooserClass self => self -> FilePath -> IO Bool
-fileChooserGetCurrentFolder :: FileChooserClass self => self -> IO (Maybe FilePath)
-fileChooserGetURI :: FileChooserClass self => self -> IO (Maybe String)
-fileChooserSetURI :: FileChooserClass self => self -> String -> IO Bool
-fileChooserSelectURI :: FileChooserClass self => self -> String -> IO Bool
-fileChooserUnselectURI :: FileChooserClass self => self -> String -> IO ()
-fileChooserGetURIs :: FileChooserClass self => self -> IO [String]
-fileChooserSetCurrentFolderURI :: FileChooserClass self => self -> String -> IO Bool
-fileChooserGetCurrentFolderURI :: FileChooserClass self => self -> IO String
-fileChooserSetPreviewWidget :: (FileChooserClass self, WidgetClass previewWidget) => self -> previewWidget -> IO ()
-fileChooserGetPreviewWidget :: FileChooserClass self => self -> IO (Maybe Widget)
-fileChooserSetPreviewWidgetActive :: FileChooserClass self => self -> Bool -> IO ()
-fileChooserGetPreviewWidgetActive :: FileChooserClass self => self -> IO Bool
-fileChooserSetUsePreviewLabel :: FileChooserClass self => self -> Bool -> IO ()
-fileChooserGetUsePreviewLabel :: FileChooserClass self => self -> IO Bool
-fileChooserGetPreviewFilename :: FileChooserClass self => self -> IO (Maybe FilePath)
-fileChooserGetPreviewURI :: FileChooserClass self => self -> IO (Maybe String)
-fileChooserSetExtraWidget :: (FileChooserClass self, WidgetClass extraWidget) => self -> extraWidget -> IO ()
-fileChooserGetExtraWidget :: FileChooserClass self => self -> IO (Maybe Widget)
-fileChooserAddFilter :: FileChooserClass self => self -> FileFilter -> IO ()
-fileChooserRemoveFilter :: FileChooserClass self => self -> FileFilter -> IO ()
-fileChooserListFilters :: FileChooserClass self => self -> IO [FileFilter]
-fileChooserSetFilter :: FileChooserClass self => self -> FileFilter -> IO ()
-fileChooserGetFilter :: FileChooserClass self => self -> IO (Maybe FileFilter)
-fileChooserAddShortcutFolder :: FileChooserClass self => self -> FilePath -> IO ()
-fileChooserRemoveShortcutFolder :: FileChooserClass self => self -> FilePath -> IO ()
-fileChooserListShortcutFolders :: FileChooserClass self => self -> IO [String]
-fileChooserAddShortcutFolderURI :: FileChooserClass self => self -> String -> IO ()
-fileChooserRemoveShortcutFolderURI :: FileChooserClass self => self -> String -> IO ()
-fileChooserListShortcutFolderURIs :: FileChooserClass self => self -> IO [String]
-fileChooserErrorDomain :: GErrorDomain
-fileChooserSetShowHidden :: FileChooserClass self => self -> Bool -> IO ()
-fileChooserGetShowHidden :: FileChooserClass self => self -> IO Bool
-fileChooserSetDoOverwriteConfirmation :: FileChooserClass self => self -> Bool -> IO ()
-fileChooserGetDoOverwriteConfirmation :: FileChooserClass self => self -> IO Bool
-fileChooserUsePreviewLabel :: FileChooserClass self => Attr self Bool
-fileChooserShowHidden :: FileChooserClass self => Attr self Bool
-fileChooserSelectMultiple :: FileChooserClass self => Attr self Bool
-fileChooserPreviewWidgetActive :: FileChooserClass self => Attr self Bool
-fileChooserPreviewWidget :: (FileChooserClass self, WidgetClass previewWidget) => ReadWriteAttr self (Maybe Widget) previewWidget
-fileChooserLocalOnly :: FileChooserClass self => Attr self Bool
-fileChooserFilter :: FileChooserClass self => ReadWriteAttr self (Maybe FileFilter) FileFilter
-fileChooserExtraWidget :: (FileChooserClass self, WidgetClass extraWidget) => ReadWriteAttr self (Maybe Widget) extraWidget
-fileChooserDoOverwriteConfirmation :: FileChooserClass self => Attr self Bool
-fileChooserAction :: FileChooserClass self => Attr self FileChooserAction
-onCurrentFolderChanged :: FileChooserClass self => self -> IO () -> IO (ConnectId self)
-afterCurrentFolderChanged :: FileChooserClass self => self -> IO () -> IO (ConnectId self)
-onFileActivated :: FileChooserClass self => self -> IO () -> IO (ConnectId self)
-afterFileActivated :: FileChooserClass self => self -> IO () -> IO (ConnectId self)
-onUpdatePreview :: FileChooserClass self => self -> IO () -> IO (ConnectId self)
-afterUpdatePreview :: FileChooserClass self => self -> IO () -> IO (ConnectId self)
-onConfirmOverwrite :: FileChooserClass self => self -> IO FileChooserConfirmation -> IO (ConnectId self)
-afterConfirmOverwrite :: FileChooserClass self => self -> IO FileChooserConfirmation -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Selectors.FileChooserButton
-data FileChooserButton
-instance BoxClass FileChooserButton
-instance ContainerClass FileChooserButton
-instance FileChooserButtonClass FileChooserButton
-instance FileChooserClass FileChooserButton
-instance GObjectClass FileChooserButton
-instance HBoxClass FileChooserButton
-instance ObjectClass FileChooserButton
-instance WidgetClass FileChooserButton
-class HBoxClass o => FileChooserButtonClass o
-instance FileChooserButtonClass FileChooserButton
-castToFileChooserButton :: GObjectClass obj => obj -> FileChooserButton
-toFileChooserButton :: FileChooserButtonClass o => o -> FileChooserButton
-fileChooserButtonNew :: String -> FileChooserAction -> IO FileChooserButton
-fileChooserButtonNewWithBackend :: String -> FileChooserAction -> String -> IO FileChooserButton
-fileChooserButtonNewWithDialog :: FileChooserDialogClass dialog => dialog -> IO FileChooserButton
-fileChooserButtonGetTitle :: FileChooserButtonClass self => self -> IO String
-fileChooserButtonSetTitle :: FileChooserButtonClass self => self -> String -> IO ()
-fileChooserButtonGetWidthChars :: FileChooserButtonClass self => self -> IO Int
-fileChooserButtonSetWidthChars :: FileChooserButtonClass self => self -> Int -> IO ()
-fileChooserButtonDialog :: (FileChooserButtonClass self, FileChooserDialogClass fileChooserDialog) => WriteAttr self fileChooserDialog
-fileChooserButtonTitle :: FileChooserButtonClass self => Attr self String
-fileChooserButtonWidthChars :: FileChooserButtonClass self => Attr self Int
-
-module Graphics.UI.Gtk.Selectors.FileChooserWidget
-data FileChooserWidget
-instance BoxClass FileChooserWidget
-instance ContainerClass FileChooserWidget
-instance FileChooserClass FileChooserWidget
-instance FileChooserWidgetClass FileChooserWidget
-instance GObjectClass FileChooserWidget
-instance ObjectClass FileChooserWidget
-instance VBoxClass FileChooserWidget
-instance WidgetClass FileChooserWidget
-class VBoxClass o => FileChooserWidgetClass o
-instance FileChooserWidgetClass FileChooserWidget
-castToFileChooserWidget :: GObjectClass obj => obj -> FileChooserWidget
-toFileChooserWidget :: FileChooserWidgetClass o => o -> FileChooserWidget
-data FileChooserAction
-instance Enum FileChooserAction
-fileChooserWidgetNew :: FileChooserAction -> IO FileChooserWidget
-fileChooserWidgetNewWithBackend :: FileChooserAction -> String -> IO FileChooserWidget
-
-module Graphics.UI.Gtk.Selectors.FileFilter
-data FileFilter
-instance FileFilterClass FileFilter
-instance GObjectClass FileFilter
-instance ObjectClass FileFilter
-class ObjectClass o => FileFilterClass o
-instance FileFilterClass FileFilter
-castToFileFilter :: GObjectClass obj => obj -> FileFilter
-toFileFilter :: FileFilterClass o => o -> FileFilter
-fileFilterNew :: IO FileFilter
-fileFilterSetName :: FileFilter -> String -> IO ()
-fileFilterGetName :: FileFilter -> IO String
-fileFilterAddMimeType :: FileFilter -> String -> IO ()
-fileFilterAddPattern :: FileFilter -> String -> IO ()
-fileFilterAddCustom :: FileFilter -> [FileFilterFlags] -> (Maybe String -> Maybe String -> Maybe String -> Maybe String -> IO Bool) -> IO ()
-fileFilterAddPixbufFormats :: FileFilter -> IO ()
-fileFilterName :: Attr FileFilter String
-
-module Graphics.UI.Gtk.Selectors.FileSelection
-data FileSelection
-instance BinClass FileSelection
-instance ContainerClass FileSelection
-instance DialogClass FileSelection
-instance FileSelectionClass FileSelection
-instance GObjectClass FileSelection
-instance ObjectClass FileSelection
-instance WidgetClass FileSelection
-instance WindowClass FileSelection
-class DialogClass o => FileSelectionClass o
-instance FileSelectionClass FileSelection
-castToFileSelection :: GObjectClass obj => obj -> FileSelection
-toFileSelection :: FileSelectionClass o => o -> FileSelection
-fileSelectionNew :: String -> IO FileSelection
-fileSelectionSetFilename :: FileSelectionClass self => self -> String -> IO ()
-fileSelectionGetFilename :: FileSelectionClass self => self -> IO String
-fileSelectionShowFileopButtons :: FileSelectionClass self => self -> IO ()
-fileSelectionHideFileopButtons :: FileSelectionClass self => self -> IO ()
-fileSelectionGetButtons :: FileSelectionClass fsel => fsel -> IO (Button, Button)
-fileSelectionComplete :: FileSelectionClass self => self -> String -> IO ()
-fileSelectionGetSelections :: FileSelectionClass self => self -> IO [String]
-fileSelectionSetSelectMultiple :: FileSelectionClass self => self -> Bool -> IO ()
-fileSelectionGetSelectMultiple :: FileSelectionClass self => self -> IO Bool
-fileSelectionFilename :: FileSelectionClass self => Attr self String
-fileSelectionShowFileops :: FileSelectionClass self => Attr self Bool
-fileSelectionSelectMultiple :: FileSelectionClass self => Attr self Bool
-
-module Graphics.UI.Gtk.Selectors.FontButton
-data FontButton
-instance BinClass FontButton
-instance ButtonClass FontButton
-instance ContainerClass FontButton
-instance FontButtonClass FontButton
-instance GObjectClass FontButton
-instance ObjectClass FontButton
-instance WidgetClass FontButton
-class ButtonClass o => FontButtonClass o
-instance FontButtonClass FontButton
-castToFontButton :: GObjectClass obj => obj -> FontButton
-toFontButton :: FontButtonClass o => o -> FontButton
-fontButtonNew :: IO FontButton
-fontButtonNewWithFont :: String -> IO FontButton
-fontButtonSetFontName :: FontButtonClass self => self -> String -> IO Bool
-fontButtonGetFontName :: FontButtonClass self => self -> IO String
-fontButtonSetShowStyle :: FontButtonClass self => self -> Bool -> IO ()
-fontButtonGetShowStyle :: FontButtonClass self => self -> IO Bool
-fontButtonSetShowSize :: FontButtonClass self => self -> Bool -> IO ()
-fontButtonGetShowSize :: FontButtonClass self => self -> IO Bool
-fontButtonSetUseFont :: FontButtonClass self => self -> Bool -> IO ()
-fontButtonGetUseFont :: FontButtonClass self => self -> IO Bool
-fontButtonSetUseSize :: FontButtonClass self => self -> Bool -> IO ()
-fontButtonGetUseSize :: FontButtonClass self => self -> IO Bool
-fontButtonSetTitle :: FontButtonClass self => self -> String -> IO ()
-fontButtonGetTitle :: FontButtonClass self => self -> IO String
-fontButtonTitle :: FontButtonClass self => Attr self String
-fontButtonFontName :: FontButtonClass self => Attr self String
-fontButtonUseFont :: FontButtonClass self => Attr self Bool
-fontButtonUseSize :: FontButtonClass self => Attr self Bool
-fontButtonShowStyle :: FontButtonClass self => Attr self Bool
-fontButtonShowSize :: FontButtonClass self => Attr self Bool
-onFontSet :: FontButtonClass self => self -> IO () -> IO (ConnectId self)
-afterFontSet :: FontButtonClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Selectors.FontSelection
-data FontSelection
-instance BoxClass FontSelection
-instance ContainerClass FontSelection
-instance FontSelectionClass FontSelection
-instance GObjectClass FontSelection
-instance ObjectClass FontSelection
-instance VBoxClass FontSelection
-instance WidgetClass FontSelection
-class VBoxClass o => FontSelectionClass o
-instance FontSelectionClass FontSelection
-castToFontSelection :: GObjectClass obj => obj -> FontSelection
-toFontSelection :: FontSelectionClass o => o -> FontSelection
-fontSelectionNew :: IO FontSelection
-fontSelectionGetFontName :: FontSelectionClass self => self -> IO (Maybe String)
-fontSelectionSetFontName :: FontSelectionClass self => self -> String -> IO Bool
-fontSelectionGetPreviewText :: FontSelectionClass self => self -> IO String
-fontSelectionSetPreviewText :: FontSelectionClass self => self -> String -> IO ()
-fontSelectionFontName :: FontSelectionClass self => Attr self String
-fontSelectionPreviewText :: FontSelectionClass self => Attr self String
-
-module Graphics.UI.Gtk.Selectors.FontSelectionDialog
-data FontSelectionDialog
-instance BinClass FontSelectionDialog
-instance ContainerClass FontSelectionDialog
-instance DialogClass FontSelectionDialog
-instance FontSelectionDialogClass FontSelectionDialog
-instance GObjectClass FontSelectionDialog
-instance ObjectClass FontSelectionDialog
-instance WidgetClass FontSelectionDialog
-instance WindowClass FontSelectionDialog
-class DialogClass o => FontSelectionDialogClass o
-instance FontSelectionDialogClass FontSelectionDialog
-castToFontSelectionDialog :: GObjectClass obj => obj -> FontSelectionDialog
-toFontSelectionDialog :: FontSelectionDialogClass o => o -> FontSelectionDialog
-fontSelectionDialogNew :: String -> IO FontSelectionDialog
-fontSelectionDialogGetFontName :: FontSelectionDialogClass self => self -> IO (Maybe String)
-fontSelectionDialogSetFontName :: FontSelectionDialogClass self => self -> String -> IO Bool
-fontSelectionDialogGetPreviewText :: FontSelectionDialogClass self => self -> IO String
-fontSelectionDialogSetPreviewText :: FontSelectionDialogClass self => self -> String -> IO ()
-fontSelectionDialogPreviewText :: FontSelectionDialogClass self => Attr self String
-
-module Graphics.UI.Gtk.SourceView.SourceBuffer
-data SourceBuffer
-instance GObjectClass SourceBuffer
-instance SourceBufferClass SourceBuffer
-instance TextBufferClass SourceBuffer
-class TextBufferClass o => SourceBufferClass o
-instance SourceBufferClass SourceBuffer
-castToSourceBuffer :: GObjectClass obj => obj -> SourceBuffer
-sourceBufferNew :: Maybe SourceTagTable -> IO SourceBuffer
-sourceBufferNewWithLanguage :: SourceLanguage -> IO SourceBuffer
-sourceBufferSetCheckBrackets :: SourceBuffer -> Bool -> IO ()
-sourceBufferGetCheckBrackets :: SourceBuffer -> IO Bool
-sourceBufferSetBracketsMatchStyle :: SourceBuffer -> SourceTagStyle -> IO ()
-sourceBufferSetHighlight :: SourceBuffer -> Bool -> IO ()
-sourceBufferGetHighlight :: SourceBuffer -> IO Bool
-sourceBufferSetMaxUndoLevels :: SourceBuffer -> Int -> IO ()
-sourceBufferGetMaxUndoLevels :: SourceBuffer -> IO Int
-sourceBufferSetLanguage :: SourceBuffer -> SourceLanguage -> IO ()
-sourceBufferGetLanguage :: SourceBuffer -> IO SourceLanguage
-sourceBufferSetEscapeChar :: SourceBuffer -> Char -> IO ()
-sourceBufferGetEscapeChar :: SourceBuffer -> IO Char
-sourceBufferCanUndo :: SourceBuffer -> IO Bool
-sourceBufferCanRedo :: SourceBuffer -> IO Bool
-sourceBufferUndo :: SourceBuffer -> IO ()
-sourceBufferRedo :: SourceBuffer -> IO ()
-sourceBufferBeginNotUndoableAction :: SourceBuffer -> IO ()
-sourceBufferEndNotUndoableAction :: SourceBuffer -> IO ()
-sourceBufferCreateMarker :: SourceBuffer -> String -> String -> TextIter -> IO SourceMarker
-sourceBufferMoveMarker :: SourceBuffer -> SourceMarker -> TextIter -> IO ()
-sourceBufferDeleteMarker :: SourceBuffer -> SourceMarker -> IO ()
-sourceBufferGetMarker :: SourceBuffer -> String -> IO SourceMarker
-sourceBufferGetMarkersInRegion :: SourceBuffer -> TextIter -> TextIter -> IO [SourceMarker]
-sourceBufferGetFirstMarker :: SourceBuffer -> IO SourceMarker
-sourceBufferGetLastMarker :: SourceBuffer -> IO SourceMarker
-sourceBufferGetIterAtMarker :: SourceBuffer -> SourceMarker -> IO TextIter
-sourceBufferGetNextMarker :: SourceBuffer -> TextIter -> IO (Maybe SourceMarker)
-sourceBufferGetPrevMarker :: SourceBuffer -> TextIter -> IO (Maybe SourceMarker)
-
-module Graphics.UI.Gtk.SourceView.SourceIter
-sourceIterForwardSearch :: TextIter -> String -> [SourceSearchFlags] -> Maybe TextIter -> IO (Maybe (TextIter, TextIter))
-sourceIterBackwardSearch :: TextIter -> String -> [SourceSearchFlags] -> Maybe TextIter -> IO (Maybe (TextIter, TextIter))
-sourceIterFindMatchingBracket :: TextIter -> IO Bool
-
-module Graphics.UI.Gtk.SourceView.SourceLanguage
-data SourceLanguage
-instance GObjectClass SourceLanguage
-instance SourceLanguageClass SourceLanguage
-castToSourceLanguage :: GObjectClass obj => obj -> SourceLanguage
-sourceLanguageGetName :: SourceLanguage -> IO String
-sourceLanguageGetSection :: SourceLanguage -> IO String
-sourceLanguageGetTags :: SourceLanguage -> IO [SourceTag]
-sourceLanguageGetEscapeChar :: SourceLanguage -> IO Char
-sourceLanguageGetMimeTypes :: SourceLanguage -> IO [String]
-sourceLanguageSetMimeTypes :: SourceLanguage -> [String] -> IO ()
-sourceLanguageGetStyleScheme :: SourceLanguage -> IO SourceStyleScheme
-sourceLanguageSetStyleScheme :: SourceLanguage -> SourceStyleScheme -> IO ()
-sourceLanguageGetTagStyle :: SourceLanguage -> String -> IO SourceTagStyle
-sourceLanguageSetTagStyle :: SourceLanguage -> String -> SourceTagStyle -> IO ()
-sourceLanguageGetTagDefaultStyle :: SourceLanguage -> String -> IO SourceTagStyle
-
-module Graphics.UI.Gtk.SourceView.SourceView
-data SourceView
-instance ContainerClass SourceView
-instance GObjectClass SourceView
-instance ObjectClass SourceView
-instance SourceViewClass SourceView
-instance TextViewClass SourceView
-instance WidgetClass SourceView
-class TextViewClass o => SourceViewClass o
-instance SourceViewClass SourceView
-castToSourceView :: GObjectClass obj => obj -> SourceView
-sourceViewNew :: IO SourceView
-sourceViewNewWithBuffer :: SourceBuffer -> IO SourceView
-sourceViewSetShowLineNumbers :: SourceViewClass sv => sv -> Bool -> IO ()
-sourceViewGetShowLineNumbers :: SourceViewClass sv => sv -> IO Bool
-sourceViewSetShowLineMarkers :: SourceViewClass sv => sv -> Bool -> IO ()
-sourceViewGetShowLineMarkers :: SourceViewClass sv => sv -> IO Bool
-sourceViewSetTabsWidth :: SourceViewClass sv => sv -> Int -> IO ()
-sourceViewGetTabsWidth :: SourceViewClass sv => sv -> IO Int
-sourceViewSetAutoIndent :: SourceViewClass sv => sv -> Bool -> IO ()
-sourceViewGetAutoIndent :: SourceViewClass sv => sv -> IO Bool
-sourceViewSetInsertSpacesInsteadOfTabs :: SourceViewClass sv => sv -> Bool -> IO ()
-sourceViewGetInsertSpacesInsteadOfTabs :: SourceViewClass sv => sv -> IO Bool
-sourceViewSetShowMargin :: SourceViewClass sv => sv -> Bool -> IO ()
-sourceViewGetShowMargin :: SourceViewClass sv => sv -> IO Bool
-sourceViewSetMargin :: SourceViewClass sv => sv -> Int -> IO ()
-sourceViewGetMargin :: SourceViewClass sv => sv -> IO Int
-sourceViewSetMarkerPixbuf :: SourceViewClass sv => sv -> String -> Pixbuf -> IO ()
-sourceViewGetMarkerPixbuf :: SourceViewClass sv => sv -> String -> IO Pixbuf
-sourceViewSetSmartHomeEnd :: SourceViewClass sv => sv -> Bool -> IO ()
-sourceViewGetSmartHomeEnd :: SourceViewClass sv => sv -> IO Bool
-
-module Graphics.UI.Gtk.SourceView
-
-module Graphics.UI.Gtk.TreeList.CellRendererPixbuf
-data CellRendererPixbuf
-instance CellRendererClass CellRendererPixbuf
-instance CellRendererPixbufClass CellRendererPixbuf
-instance GObjectClass CellRendererPixbuf
-instance ObjectClass CellRendererPixbuf
-class CellRendererClass o => CellRendererPixbufClass o
-instance CellRendererPixbufClass CellRendererPixbuf
-castToCellRendererPixbuf :: GObjectClass obj => obj -> CellRendererPixbuf
-toCellRendererPixbuf :: CellRendererPixbufClass o => o -> CellRendererPixbuf
-cellRendererPixbufNew :: IO CellRendererPixbuf
-
-module Graphics.UI.Gtk.TreeList.CellRendererText
-data CellRendererText
-instance CellRendererClass CellRendererText
-instance CellRendererTextClass CellRendererText
-instance GObjectClass CellRendererText
-instance ObjectClass CellRendererText
-class CellRendererClass o => CellRendererTextClass o
-instance CellRendererTextClass CellRendererText
-castToCellRendererText :: GObjectClass obj => obj -> CellRendererText
-toCellRendererText :: CellRendererTextClass o => o -> CellRendererText
-cellRendererTextNew :: IO CellRendererText
-cellText :: Attribute CellRendererText String
-cellMarkup :: Attribute CellRendererText String
-cellBackground :: Attribute CellRendererText (Maybe String)
-cellForeground :: Attribute CellRendererText (Maybe String)
-cellEditable :: Attribute CellRendererText (Maybe Bool)
-onEdited :: TreeModelClass tm => CellRendererText -> tm -> (TreeIter -> String -> IO ()) -> IO (ConnectId CellRendererText)
-afterEdited :: TreeModelClass tm => CellRendererText -> tm -> (TreeIter -> String -> IO ()) -> IO (ConnectId CellRendererText)
-
-module Graphics.UI.Gtk.TreeList.CellRendererToggle
-data CellRendererToggle
-instance CellRendererClass CellRendererToggle
-instance CellRendererToggleClass CellRendererToggle
-instance GObjectClass CellRendererToggle
-instance ObjectClass CellRendererToggle
-class CellRendererClass o => CellRendererToggleClass o
-instance CellRendererToggleClass CellRendererToggle
-castToCellRendererToggle :: GObjectClass obj => obj -> CellRendererToggle
-toCellRendererToggle :: CellRendererToggleClass o => o -> CellRendererToggle
-cellRendererToggleNew :: IO CellRendererToggle
-cellRendererToggleGetRadio :: CellRendererToggleClass self => self -> IO Bool
-cellRendererToggleSetRadio :: CellRendererToggleClass self => self -> Bool -> IO ()
-cellRendererToggleGetActive :: CellRendererToggleClass self => self -> IO Bool
-cellRendererToggleSetActive :: CellRendererToggleClass self => self -> Bool -> IO ()
-cellActive :: Attribute CellRendererToggle Bool
-cellRadio :: Attribute CellRendererToggle Bool
-
-module Graphics.UI.Gtk.TreeList.CellView
-data CellView
-instance CellViewClass CellView
-instance GObjectClass CellView
-instance ObjectClass CellView
-instance WidgetClass CellView
-class WidgetClass o => CellViewClass o
-instance CellViewClass CellView
-castToCellView :: GObjectClass obj => obj -> CellView
-toCellView :: CellViewClass o => o -> CellView
-cellViewNew :: IO CellView
-cellViewNewWithMarkup :: String -> IO CellView
-cellViewNewWithPixbuf :: Pixbuf -> IO CellView
-cellViewNewWithText :: String -> IO CellView
-cellViewSetModel :: (CellViewClass self, TreeModelClass model) => self -> Maybe model -> IO ()
-cellViewSetDisplayedRow :: CellViewClass self => self -> TreePath -> IO ()
-cellViewGetDisplayedRow :: CellViewClass self => self -> IO (Maybe TreePath)
-cellViewGetSizeOfRow :: CellViewClass self => self -> TreePath -> IO Requisition
-cellViewSetBackgroundColor :: CellViewClass self => self -> Color -> IO ()
-cellViewGetCellRenderers :: CellViewClass self => self -> IO [CellRenderer]
-cellViewDisplayedRow :: CellViewClass self => ReadWriteAttr self (Maybe TreePath) TreePath
-
-module Graphics.UI.Gtk.TreeList.IconView
-data IconView
-instance ContainerClass IconView
-instance GObjectClass IconView
-instance IconViewClass IconView
-instance ObjectClass IconView
-instance WidgetClass IconView
-class ContainerClass o => IconViewClass o
-instance IconViewClass IconView
-castToIconView :: GObjectClass obj => obj -> IconView
-toIconView :: IconViewClass o => o -> IconView
-iconViewNew :: IO IconView
-iconViewNewWithModel :: TreeModelClass model => model -> IO IconView
-iconViewSetModel :: (IconViewClass self, TreeModelClass model) => self -> Maybe model -> IO ()
-iconViewGetModel :: IconViewClass self => self -> IO (Maybe TreeModel)
-iconViewSetTextColumn :: IconViewClass self => self -> Int -> IO ()
-iconViewGetTextColumn :: IconViewClass self => self -> IO Int
-iconViewSetMarkupColumn :: IconViewClass self => self -> Int -> IO ()
-iconViewGetMarkupColumn :: IconViewClass self => self -> IO Int
-iconViewSetPixbufColumn :: IconViewClass self => self -> Int -> IO ()
-iconViewGetPixbufColumn :: IconViewClass self => self -> IO Int
-iconViewGetPathAtPos :: IconViewClass self => self -> Int -> Int -> IO TreePath
-iconViewSelectedForeach :: IconViewClass self => self -> (TreePath -> IO ()) -> IO ()
-iconViewSetSelectionMode :: IconViewClass self => self -> SelectionMode -> IO ()
-iconViewGetSelectionMode :: IconViewClass self => self -> IO SelectionMode
-iconViewSetOrientation :: IconViewClass self => self -> Orientation -> IO ()
-iconViewGetOrientation :: IconViewClass self => self -> IO Orientation
-iconViewSetColumns :: IconViewClass self => self -> Int -> IO ()
-iconViewGetColumns :: IconViewClass self => self -> IO Int
-iconViewSetItemWidth :: IconViewClass self => self -> Int -> IO ()
-iconViewGetItemWidth :: IconViewClass self => self -> IO Int
-iconViewSetSpacing :: IconViewClass self => self -> Int -> IO ()
-iconViewGetSpacing :: IconViewClass self => self -> IO Int
-iconViewSetRowSpacing :: IconViewClass self => self -> Int -> IO ()
-iconViewGetRowSpacing :: IconViewClass self => self -> IO Int
-iconViewSetColumnSpacing :: IconViewClass self => self -> Int -> IO ()
-iconViewGetColumnSpacing :: IconViewClass self => self -> IO Int
-iconViewSetMargin :: IconViewClass self => self -> Int -> IO ()
-iconViewGetMargin :: IconViewClass self => self -> IO Int
-iconViewSelectPath :: IconViewClass self => self -> TreePath -> IO ()
-iconViewUnselectPath :: IconViewClass self => self -> TreePath -> IO ()
-iconViewPathIsSelected :: IconViewClass self => self -> TreePath -> IO Bool
-iconViewGetSelectedItems :: IconViewClass self => self -> IO [TreePath]
-iconViewSelectAll :: IconViewClass self => self -> IO ()
-iconViewUnselectAll :: IconViewClass self => self -> IO ()
-iconViewItemActivated :: IconViewClass self => self -> TreePath -> IO ()
-iconViewSelectionMode :: IconViewClass self => Attr self SelectionMode
-iconViewPixbufColumn :: IconViewClass self => Attr self Int
-iconViewTextColumn :: IconViewClass self => Attr self Int
-iconViewMarkupColumn :: IconViewClass self => Attr self Int
-iconViewModel :: (IconViewClass self, TreeModelClass model) => ReadWriteAttr self (Maybe TreeModel) (Maybe model)
-iconViewColumns :: IconViewClass self => Attr self Int
-iconViewItemWidth :: IconViewClass self => Attr self Int
-iconViewSpacing :: IconViewClass self => Attr self Int
-iconViewRowSpacing :: IconViewClass self => Attr self Int
-iconViewColumnSpacing :: IconViewClass self => Attr self Int
-iconViewMargin :: IconViewClass self => Attr self Int
-iconViewOrientation :: IconViewClass self => Attr self Orientation
-onSelectAll :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-afterSelectAll :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-onUnselectAll :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-afterUnselectAll :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-onSelectCursorItem :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-afterSelectCursorItem :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-onToggleCursorItem :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-afterToggleCursorItem :: IconViewClass self => self -> IO () -> IO (ConnectId self)
-onActivateCursorItem :: IconViewClass self => self -> IO Bool -> IO (ConnectId self)
-afterActivateCursorItem :: IconViewClass self => self -> IO Bool -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.TreeList.TreeSelection
-data TreeSelection
-instance GObjectClass TreeSelection
-instance TreeSelectionClass TreeSelection
-class GObjectClass o => TreeSelectionClass o
-instance TreeSelectionClass TreeSelection
-castToTreeSelection :: GObjectClass obj => obj -> TreeSelection
-toTreeSelection :: TreeSelectionClass o => o -> TreeSelection
-data SelectionMode
-SelectionNone :: SelectionMode
-SelectionSingle :: SelectionMode
-SelectionBrowse :: SelectionMode
-SelectionMultiple :: SelectionMode
-instance Enum SelectionMode
-type TreeSelectionCB = TreePath -> IO Bool
-type TreeSelectionForeachCB = TreeIter -> IO ()
-treeSelectionSetMode :: TreeSelectionClass self => self -> SelectionMode -> IO ()
-treeSelectionGetMode :: TreeSelectionClass self => self -> IO SelectionMode
-treeSelectionSetSelectFunction :: TreeSelectionClass self => self -> TreeSelectionCB -> IO ()
-treeSelectionGetTreeView :: TreeSelectionClass self => self -> IO TreeView
-treeSelectionGetSelected :: TreeSelectionClass self => self -> IO (Maybe TreeIter)
-treeSelectionSelectedForeach :: TreeSelectionClass self => self -> TreeSelectionForeachCB -> IO ()
-treeSelectionGetSelectedRows :: TreeSelectionClass self => self -> IO [TreePath]
-treeSelectionCountSelectedRows :: TreeSelectionClass self => self -> IO Int
-treeSelectionSelectPath :: TreeSelectionClass self => self -> TreePath -> IO ()
-treeSelectionUnselectPath :: TreeSelectionClass self => self -> TreePath -> IO ()
-treeSelectionPathIsSelected :: TreeSelectionClass self => self -> TreePath -> IO Bool
-treeSelectionSelectIter :: TreeSelectionClass self => self -> TreeIter -> IO ()
-treeSelectionUnselectIter :: TreeSelectionClass self => self -> TreeIter -> IO ()
-treeSelectionIterIsSelected :: TreeSelectionClass self => self -> TreeIter -> IO Bool
-treeSelectionSelectAll :: TreeSelectionClass self => self -> IO ()
-treeSelectionUnselectAll :: TreeSelectionClass self => self -> IO ()
-treeSelectionSelectRange :: TreeSelectionClass self => self -> TreePath -> TreePath -> IO ()
-treeSelectionUnselectRange :: TreeSelectionClass self => self -> TreePath -> TreePath -> IO ()
-treeSelectionMode :: TreeSelectionClass self => Attr self SelectionMode
-onSelectionChanged :: TreeSelectionClass self => self -> IO () -> IO (ConnectId self)
-afterSelectionChanged :: TreeSelectionClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.TreeList.TreeViewColumn
-data TreeViewColumn
-instance GObjectClass TreeViewColumn
-instance ObjectClass TreeViewColumn
-instance TreeViewColumnClass TreeViewColumn
-class ObjectClass o => TreeViewColumnClass o
-instance TreeViewColumnClass TreeViewColumn
-castToTreeViewColumn :: GObjectClass obj => obj -> TreeViewColumn
-toTreeViewColumn :: TreeViewColumnClass o => o -> TreeViewColumn
-treeViewColumnNew :: IO TreeViewColumn
-treeViewColumnNewWithAttributes :: CellRendererClass cr => String -> cr -> [(String, Int)] -> IO TreeViewColumn
-treeViewColumnPackStart :: CellRendererClass cell => TreeViewColumn -> cell -> Bool -> IO ()
-treeViewColumnPackEnd :: CellRendererClass cell => TreeViewColumn -> cell -> Bool -> IO ()
-treeViewColumnClear :: TreeViewColumn -> IO ()
-treeViewColumnGetCellRenderers :: TreeViewColumn -> IO [CellRenderer]
-treeViewColumnAddAttribute :: CellRendererClass cellRenderer => TreeViewColumn -> cellRenderer -> String -> Int -> IO ()
-treeViewColumnAddAttributes :: CellRendererClass cr => TreeViewColumn -> cr -> [(String, Int)] -> IO ()
-treeViewColumnSetAttributes :: CellRendererClass cr => TreeViewColumn -> cr -> [(String, Int)] -> IO ()
-treeViewColumnClearAttributes :: CellRendererClass cellRenderer => TreeViewColumn -> cellRenderer -> IO ()
-treeViewColumnSetSpacing :: TreeViewColumn -> Int -> IO ()
-treeViewColumnGetSpacing :: TreeViewColumn -> IO Int
-treeViewColumnSetVisible :: TreeViewColumn -> Bool -> IO ()
-treeViewColumnGetVisible :: TreeViewColumn -> IO Bool
-treeViewColumnSetResizable :: TreeViewColumn -> Bool -> IO ()
-treeViewColumnGetResizable :: TreeViewColumn -> IO Bool
-data TreeViewColumnSizing
-TreeViewColumnGrowOnly :: TreeViewColumnSizing
-TreeViewColumnAutosize :: TreeViewColumnSizing
-TreeViewColumnFixed :: TreeViewColumnSizing
-instance Enum TreeViewColumnSizing
-instance Eq TreeViewColumnSizing
-treeViewColumnSetSizing :: TreeViewColumn -> TreeViewColumnSizing -> IO ()
-treeViewColumnGetSizing :: TreeViewColumn -> IO TreeViewColumnSizing
-treeViewColumnGetWidth :: TreeViewColumn -> IO Int
-treeViewColumnSetFixedWidth :: TreeViewColumn -> Int -> IO ()
-treeViewColumnGetFixedWidth :: TreeViewColumn -> IO Int
-treeViewColumnSetMinWidth :: TreeViewColumn -> Int -> IO ()
-treeViewColumnGetMinWidth :: TreeViewColumn -> IO Int
-treeViewColumnSetMaxWidth :: TreeViewColumn -> Int -> IO ()
-treeViewColumnGetMaxWidth :: TreeViewColumn -> IO Int
-treeViewColumnClicked :: TreeViewColumn -> IO ()
-treeViewColumnSetTitle :: TreeViewColumn -> String -> IO ()
-treeViewColumnGetTitle :: TreeViewColumn -> IO (Maybe String)
-treeViewColumnSetClickable :: TreeViewColumn -> Bool -> IO ()
-treeViewColumnGetClickable :: TreeViewColumn -> IO Bool
-treeViewColumnSetWidget :: WidgetClass widget => TreeViewColumn -> widget -> IO ()
-treeViewColumnGetWidget :: TreeViewColumn -> IO Widget
-treeViewColumnSetAlignment :: TreeViewColumn -> Float -> IO ()
-treeViewColumnGetAlignment :: TreeViewColumn -> IO Float
-treeViewColumnSetReorderable :: TreeViewColumn -> Bool -> IO ()
-treeViewColumnGetReorderable :: TreeViewColumn -> IO Bool
-treeViewColumnSetSortColumnId :: TreeViewColumn -> Int -> IO ()
-treeViewColumnGetSortColumnId :: TreeViewColumn -> IO Int
-treeViewColumnSetSortIndicator :: TreeViewColumn -> Bool -> IO ()
-treeViewColumnGetSortIndicator :: TreeViewColumn -> IO Bool
-treeViewColumnSetSortOrder :: TreeViewColumn -> SortType -> IO ()
-treeViewColumnGetSortOrder :: TreeViewColumn -> IO SortType
-data SortType
-SortAscending :: SortType
-SortDescending :: SortType
-instance Enum SortType
-instance Eq SortType
-treeViewColumnVisible :: Attr TreeViewColumn Bool
-treeViewColumnResizable :: Attr TreeViewColumn Bool
-treeViewColumnWidth :: ReadAttr TreeViewColumn Int
-treeViewColumnSpacing :: Attr TreeViewColumn Int
-treeViewColumnSizing :: Attr TreeViewColumn TreeViewColumnSizing
-treeViewColumnFixedWidth :: Attr TreeViewColumn Int
-treeViewColumnMinWidth :: Attr TreeViewColumn Int
-treeViewColumnMaxWidth :: Attr TreeViewColumn Int
-treeViewColumnTitle :: ReadWriteAttr TreeViewColumn (Maybe String) String
-treeViewColumnClickable :: Attr TreeViewColumn Bool
-treeViewColumnWidget :: WidgetClass widget => ReadWriteAttr TreeViewColumn Widget widget
-treeViewColumnAlignment :: Attr TreeViewColumn Float
-treeViewColumnReorderable :: Attr TreeViewColumn Bool
-treeViewColumnSortIndicator :: Attr TreeViewColumn Bool
-treeViewColumnSortOrder :: Attr TreeViewColumn SortType
-treeViewColumnSortColumnId :: Attr TreeViewColumn Int
-onColClicked :: TreeViewColumnClass self => self -> IO () -> IO (ConnectId self)
-afterColClicked :: TreeViewColumnClass self => self -> IO () -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.TreeList.TreeView
-data TreeView
-instance ContainerClass TreeView
-instance GObjectClass TreeView
-instance ObjectClass TreeView
-instance TreeViewClass TreeView
-instance WidgetClass TreeView
-class ContainerClass o => TreeViewClass o
-instance TreeViewClass TreeView
-castToTreeView :: GObjectClass obj => obj -> TreeView
-toTreeView :: TreeViewClass o => o -> TreeView
-type Point = (Int, Int)
-treeViewNew :: IO TreeView
-treeViewNewWithModel :: TreeModelClass model => model -> IO TreeView
-treeViewGetModel :: TreeViewClass self => self -> IO (Maybe TreeModel)
-treeViewSetModel :: (TreeViewClass self, TreeModelClass model) => self -> model -> IO ()
-treeViewGetSelection :: TreeViewClass self => self -> IO TreeSelection
-treeViewGetHAdjustment :: TreeViewClass self => self -> IO (Maybe Adjustment)
-treeViewSetHAdjustment :: TreeViewClass self => self -> Maybe Adjustment -> IO ()
-treeViewGetVAdjustment :: TreeViewClass self => self -> IO (Maybe Adjustment)
-treeViewSetVAdjustment :: TreeViewClass self => self -> Maybe Adjustment -> IO ()
-treeViewGetHeadersVisible :: TreeViewClass self => self -> IO Bool
-treeViewSetHeadersVisible :: TreeViewClass self => self -> Bool -> IO ()
-treeViewColumnsAutosize :: TreeViewClass self => self -> IO ()
-treeViewSetHeadersClickable :: TreeViewClass self => self -> Bool -> IO ()
-treeViewGetRulesHint :: TreeViewClass self => self -> IO Bool
-treeViewSetRulesHint :: TreeViewClass self => self -> Bool -> IO ()
-treeViewAppendColumn :: TreeViewClass self => self -> TreeViewColumn -> IO Int
-treeViewRemoveColumn :: TreeViewClass self => self -> TreeViewColumn -> IO Int
-treeViewInsertColumn :: TreeViewClass self => self -> TreeViewColumn -> Int -> IO Int
-treeViewInsertColumnWithAttributes :: (TreeViewClass self, CellRendererClass cr) => self -> Int -> String -> cr -> [(String, Int)] -> IO ()
-treeViewGetColumn :: TreeViewClass self => self -> Int -> IO (Maybe TreeViewColumn)
-treeViewGetColumns :: TreeViewClass self => self -> IO [TreeViewColumn]
-treeViewMoveColumnAfter :: TreeViewClass self => self -> TreeViewColumn -> TreeViewColumn -> IO ()
-treeViewMoveColumnFirst :: TreeViewClass self => self -> TreeViewColumn -> IO ()
-treeViewSetExpanderColumn :: TreeViewClass self => self -> Maybe TreeViewColumn -> IO ()
-treeViewGetExpanderColumn :: TreeViewClass self => self -> IO TreeViewColumn
-treeViewSetColumnDragFunction :: TreeViewClass self => self -> Maybe (TreeViewColumn -> Maybe TreeViewColumn -> Maybe TreeViewColumn -> IO Bool) -> IO ()
-treeViewScrollToPoint :: TreeViewClass self => self -> Int -> Int -> IO ()
-treeViewScrollToCell :: TreeViewClass self => self -> TreePath -> TreeViewColumn -> Maybe (Float, Float) -> IO ()
-treeViewSetCursor :: TreeViewClass self => self -> TreePath -> Maybe (TreeViewColumn, Bool) -> IO ()
-treeViewSetCursorOnCell :: (TreeViewClass self, CellRendererClass focusCell) => self -> TreePath -> TreeViewColumn -> focusCell -> Bool -> IO ()
-treeViewGetCursor :: TreeViewClass self => self -> IO (TreePath, Maybe TreeViewColumn)
-treeViewRowActivated :: TreeViewClass self => self -> TreePath -> TreeViewColumn -> IO ()
-treeViewExpandAll :: TreeViewClass self => self -> IO ()
-treeViewCollapseAll :: TreeViewClass self => self -> IO ()
-treeViewExpandToPath :: TreeViewClass self => self -> TreePath -> IO ()
-treeViewExpandRow :: TreeViewClass self => self -> TreePath -> Bool -> IO Bool
-treeViewCollapseRow :: TreeViewClass self => self -> TreePath -> IO Bool
-treeViewMapExpandedRows :: TreeViewClass self => self -> (TreePath -> IO ()) -> IO ()
-treeViewRowExpanded :: TreeViewClass self => self -> TreePath -> IO Bool
-treeViewGetReorderable :: TreeViewClass self => self -> IO Bool
-treeViewSetReorderable :: TreeViewClass self => self -> Bool -> IO ()
-treeViewGetPathAtPos :: TreeViewClass self => self -> Point -> IO (Maybe (TreePath, TreeViewColumn, Point))
-treeViewGetCellArea :: TreeViewClass self => self -> Maybe TreePath -> TreeViewColumn -> IO Rectangle
-treeViewGetBackgroundArea :: TreeViewClass self => self -> Maybe TreePath -> TreeViewColumn -> IO Rectangle
-treeViewGetVisibleRect :: TreeViewClass self => self -> IO Rectangle
-treeViewWidgetToTreeCoords :: TreeViewClass self => self -> Point -> IO Point
-treeViewTreeToWidgetCoords :: TreeViewClass self => self -> Point -> IO Point
-treeViewCreateRowDragIcon :: TreeViewClass self => self -> TreePath -> IO Pixmap
-treeViewGetEnableSearch :: TreeViewClass self => self -> IO Bool
-treeViewSetEnableSearch :: TreeViewClass self => self -> Bool -> IO ()
-treeViewGetSearchColumn :: TreeViewClass self => self -> IO Int
-treeViewSetSearchColumn :: TreeViewClass self => self -> Int -> IO ()
-treeViewSetSearchEqualFunc :: TreeViewClass self => self -> (Int -> String -> TreeIter -> IO Bool) -> IO ()
-treeViewGetFixedHeightMode :: TreeViewClass self => self -> IO Bool
-treeViewSetFixedHeightMode :: TreeViewClass self => self -> Bool -> IO ()
-treeViewGetHoverSelection :: TreeViewClass self => self -> IO Bool
-treeViewSetHoverSelection :: TreeViewClass self => self -> Bool -> IO ()
-treeViewGetHoverExpand :: TreeViewClass self => self -> IO Bool
-treeViewSetHoverExpand :: TreeViewClass self => self -> Bool -> IO ()
-treeViewModel :: (TreeViewClass self, TreeModelClass model) => ReadWriteAttr self (Maybe TreeModel) model
-treeViewHAdjustment :: TreeViewClass self => Attr self (Maybe Adjustment)
-treeViewVAdjustment :: TreeViewClass self => Attr self (Maybe Adjustment)
-treeViewHeadersVisible :: TreeViewClass self => Attr self Bool
-treeViewHeadersClickable :: TreeViewClass self => Attr self Bool
-treeViewExpanderColumn :: TreeViewClass self => ReadWriteAttr self TreeViewColumn (Maybe TreeViewColumn)
-treeViewReorderable :: TreeViewClass self => Attr self Bool
-treeViewRulesHint :: TreeViewClass self => Attr self Bool
-treeViewEnableSearch :: TreeViewClass self => Attr self Bool
-treeViewSearchColumn :: TreeViewClass self => Attr self Int
-treeViewFixedHeightMode :: TreeViewClass self => Attr self Bool
-treeViewHoverSelection :: TreeViewClass self => Attr self Bool
-treeViewHoverExpand :: TreeViewClass self => Attr self Bool
-onColumnsChanged :: TreeViewClass self => self -> IO () -> IO (ConnectId self)
-afterColumnsChanged :: TreeViewClass self => self -> IO () -> IO (ConnectId self)
-onCursorChanged :: TreeViewClass self => self -> IO () -> IO (ConnectId self)
-afterCursorChanged :: TreeViewClass self => self -> IO () -> IO (ConnectId self)
-onRowActivated :: TreeViewClass self => self -> (TreePath -> TreeViewColumn -> IO ()) -> IO (ConnectId self)
-afterRowActivated :: TreeViewClass self => self -> (TreePath -> TreeViewColumn -> IO ()) -> IO (ConnectId self)
-onRowCollapsed :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO ()) -> IO (ConnectId self)
-afterRowCollapsed :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO ()) -> IO (ConnectId self)
-onRowExpanded :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO ()) -> IO (ConnectId self)
-afterRowExpanded :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO ()) -> IO (ConnectId self)
-onStartInteractiveSearch :: TreeViewClass self => self -> IO () -> IO (ConnectId self)
-afterStartInteractiveSearch :: TreeViewClass self => self -> IO () -> IO (ConnectId self)
-onTestCollapseRow :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO Bool) -> IO (ConnectId self)
-afterTestCollapseRow :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO Bool) -> IO (ConnectId self)
-onTestExpandRow :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO Bool) -> IO (ConnectId self)
-afterTestExpandRow :: TreeViewClass self => self -> (TreeIter -> TreePath -> IO Bool) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Windows.AboutDialog
-data AboutDialog
-instance AboutDialogClass AboutDialog
-instance BinClass AboutDialog
-instance ContainerClass AboutDialog
-instance DialogClass AboutDialog
-instance GObjectClass AboutDialog
-instance ObjectClass AboutDialog
-instance WidgetClass AboutDialog
-instance WindowClass AboutDialog
-class DialogClass o => AboutDialogClass o
-instance AboutDialogClass AboutDialog
-castToAboutDialog :: GObjectClass obj => obj -> AboutDialog
-toAboutDialog :: AboutDialogClass o => o -> AboutDialog
-aboutDialogNew :: IO AboutDialog
-aboutDialogGetName :: AboutDialogClass self => self -> IO String
-aboutDialogSetName :: AboutDialogClass self => self -> String -> IO ()
-aboutDialogGetVersion :: AboutDialogClass self => self -> IO String
-aboutDialogSetVersion :: AboutDialogClass self => self -> String -> IO ()
-aboutDialogGetCopyright :: AboutDialogClass self => self -> IO String
-aboutDialogSetCopyright :: AboutDialogClass self => self -> String -> IO ()
-aboutDialogGetComments :: AboutDialogClass self => self -> IO String
-aboutDialogSetComments :: AboutDialogClass self => self -> String -> IO ()
-aboutDialogGetLicense :: AboutDialogClass self => self -> IO (Maybe String)
-aboutDialogSetLicense :: AboutDialogClass self => self -> Maybe String -> IO ()
-aboutDialogGetWebsite :: AboutDialogClass self => self -> IO String
-aboutDialogSetWebsite :: AboutDialogClass self => self -> String -> IO ()
-aboutDialogGetWebsiteLabel :: AboutDialogClass self => self -> IO String
-aboutDialogSetWebsiteLabel :: AboutDialogClass self => self -> String -> IO ()
-aboutDialogSetAuthors :: AboutDialogClass self => self -> [String] -> IO ()
-aboutDialogGetAuthors :: AboutDialogClass self => self -> IO [String]
-aboutDialogSetArtists :: AboutDialogClass self => self -> [String] -> IO ()
-aboutDialogGetArtists :: AboutDialogClass self => self -> IO [String]
-aboutDialogSetDocumenters :: AboutDialogClass self => self -> [String] -> IO ()
-aboutDialogGetDocumenters :: AboutDialogClass self => self -> IO [String]
-aboutDialogGetTranslatorCredits :: AboutDialogClass self => self -> IO String
-aboutDialogSetTranslatorCredits :: AboutDialogClass self => self -> String -> IO ()
-aboutDialogGetLogo :: AboutDialogClass self => self -> IO Pixbuf
-aboutDialogSetLogo :: AboutDialogClass self => self -> Maybe Pixbuf -> IO ()
-aboutDialogGetLogoIconName :: AboutDialogClass self => self -> IO String
-aboutDialogSetLogoIconName :: AboutDialogClass self => self -> Maybe String -> IO ()
-aboutDialogSetEmailHook :: (String -> IO ()) -> IO ()
-aboutDialogSetUrlHook :: (String -> IO ()) -> IO ()
-aboutDialogGetWrapLicense :: AboutDialogClass self => self -> IO Bool
-aboutDialogSetWrapLicense :: AboutDialogClass self => self -> Bool -> IO ()
-aboutDialogName :: AboutDialogClass self => Attr self String
-aboutDialogVersion :: AboutDialogClass self => Attr self String
-aboutDialogCopyright :: AboutDialogClass self => Attr self String
-aboutDialogComments :: AboutDialogClass self => Attr self String
-aboutDialogLicense :: AboutDialogClass self => Attr self (Maybe String)
-aboutDialogWebsite :: AboutDialogClass self => Attr self String
-aboutDialogWebsiteLabel :: AboutDialogClass self => Attr self String
-aboutDialogAuthors :: AboutDialogClass self => Attr self [String]
-aboutDialogDocumenters :: AboutDialogClass self => Attr self [String]
-aboutDialogArtists :: AboutDialogClass self => Attr self [String]
-aboutDialogTranslatorCredits :: AboutDialogClass self => Attr self String
-aboutDialogLogo :: AboutDialogClass self => ReadWriteAttr self Pixbuf (Maybe Pixbuf)
-aboutDialogLogoIconName :: AboutDialogClass self => ReadWriteAttr self String (Maybe String)
-aboutDialogWrapLicense :: AboutDialogClass self => Attr self Bool
-
-module Graphics.UI.Gtk.Windows.Dialog
-data Dialog
-instance BinClass Dialog
-instance ContainerClass Dialog
-instance DialogClass Dialog
-instance GObjectClass Dialog
-instance ObjectClass Dialog
-instance WidgetClass Dialog
-instance WindowClass Dialog
-class WindowClass o => DialogClass o
-instance DialogClass AboutDialog
-instance DialogClass ColorSelectionDialog
-instance DialogClass Dialog
-instance DialogClass FileChooserDialog
-instance DialogClass FileSelection
-instance DialogClass FontSelectionDialog
-instance DialogClass InputDialog
-instance DialogClass MessageDialog
-castToDialog :: GObjectClass obj => obj -> Dialog
-toDialog :: DialogClass o => o -> Dialog
-dialogNew :: IO Dialog
-dialogGetUpper :: DialogClass dc => dc -> IO VBox
-dialogGetActionArea :: DialogClass dc => dc -> IO HBox
-dialogRun :: DialogClass self => self -> IO ResponseId
-dialogResponse :: DialogClass self => self -> ResponseId -> IO ()
-data ResponseId
-ResponseNone :: ResponseId
-ResponseReject :: ResponseId
-ResponseAccept :: ResponseId
-ResponseDeleteEvent :: ResponseId
-ResponseOk :: ResponseId
-ResponseCancel :: ResponseId
-ResponseClose :: ResponseId
-ResponseYes :: ResponseId
-ResponseNo :: ResponseId
-ResponseApply :: ResponseId
-ResponseHelp :: ResponseId
-ResponseUser :: Int -> ResponseId
-instance Show ResponseId
-dialogAddButton :: DialogClass self => self -> String -> ResponseId -> IO Button
-dialogAddActionWidget :: (DialogClass self, WidgetClass child) => self -> child -> ResponseId -> IO ()
-dialogGetHasSeparator :: DialogClass self => self -> IO Bool
-dialogSetDefaultResponse :: DialogClass self => self -> ResponseId -> IO ()
-dialogSetHasSeparator :: DialogClass self => self -> Bool -> IO ()
-dialogSetResponseSensitive :: DialogClass self => self -> ResponseId -> Bool -> IO ()
-dialogHasSeparator :: DialogClass self => Attr self Bool
-onResponse :: DialogClass self => self -> (ResponseId -> IO ()) -> IO (ConnectId self)
-afterResponse :: DialogClass self => self -> (ResponseId -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Windows.Window
-data Window
-instance BinClass Window
-instance ContainerClass Window
-instance GObjectClass Window
-instance ObjectClass Window
-instance WidgetClass Window
-instance WindowClass Window
-class BinClass o => WindowClass o
-instance WindowClass AboutDialog
-instance WindowClass ColorSelectionDialog
-instance WindowClass Dialog
-instance WindowClass FileChooserDialog
-instance WindowClass FileSelection
-instance WindowClass FontSelectionDialog
-instance WindowClass InputDialog
-instance WindowClass MessageDialog
-instance WindowClass Plug
-instance WindowClass Window
-castToWindow :: GObjectClass obj => obj -> Window
-toWindow :: WindowClass o => o -> Window
-data WindowType
-WindowToplevel :: WindowType
-WindowPopup :: WindowType
-instance Enum WindowType
-instance Eq WindowType
-data WindowEdge
-WindowEdgeNorthWest :: WindowEdge
-WindowEdgeNorth :: WindowEdge
-WindowEdgeNorthEast :: WindowEdge
-WindowEdgeWest :: WindowEdge
-WindowEdgeEast :: WindowEdge
-WindowEdgeSouthWest :: WindowEdge
-WindowEdgeSouth :: WindowEdge
-WindowEdgeSouthEast :: WindowEdge
-instance Enum WindowEdge
-data WindowTypeHint
-WindowTypeHintNormal :: WindowTypeHint
-WindowTypeHintDialog :: WindowTypeHint
-WindowTypeHintMenu :: WindowTypeHint
-WindowTypeHintToolbar :: WindowTypeHint
-WindowTypeHintSplashscreen :: WindowTypeHint
-WindowTypeHintUtility :: WindowTypeHint
-WindowTypeHintDock :: WindowTypeHint
-WindowTypeHintDesktop :: WindowTypeHint
-instance Enum WindowTypeHint
-data Gravity
-GravityNorthWest :: Gravity
-GravityNorth :: Gravity
-GravityNorthEast :: Gravity
-GravityWest :: Gravity
-GravityCenter :: Gravity
-GravityEast :: Gravity
-GravitySouthWest :: Gravity
-GravitySouth :: Gravity
-GravitySouthEast :: Gravity
-GravityStatic :: Gravity
-instance Enum Gravity
-windowNew :: IO Window
-windowSetTitle :: WindowClass self => self -> String -> IO ()
-windowGetTitle :: WindowClass self => self -> IO String
-windowSetResizable :: WindowClass self => self -> Bool -> IO ()
-windowGetResizable :: WindowClass self => self -> IO Bool
-windowActivateFocus :: WindowClass self => self -> IO Bool
-windowActivateDefault :: WindowClass self => self -> IO Bool
-windowSetModal :: WindowClass self => self -> Bool -> IO ()
-windowGetModal :: WindowClass self => self -> IO Bool
-windowSetDefaultSize :: WindowClass self => self -> Int -> Int -> IO ()
-windowGetDefaultSize :: WindowClass self => self -> IO (Int, Int)
-windowSetPolicy :: WindowClass self => self -> Bool -> Bool -> Bool -> IO ()
-windowSetPosition :: WindowClass self => self -> WindowPosition -> IO ()
-data WindowPosition
-WinPosNone :: WindowPosition
-WinPosCenter :: WindowPosition
-WinPosMouse :: WindowPosition
-WinPosCenterAlways :: WindowPosition
-WinPosCenterOnParent :: WindowPosition
-instance Enum WindowPosition
-instance Eq WindowPosition
-windowSetTransientFor :: (WindowClass self, WindowClass parent) => self -> parent -> IO ()
-windowGetTransientFor :: WindowClass self => self -> IO (Maybe Window)
-windowSetDestroyWithParent :: WindowClass self => self -> Bool -> IO ()
-windowGetDestroyWithParent :: WindowClass self => self -> IO Bool
-windowIsActive :: WindowClass self => self -> IO Bool
-windowHasToplevelFocus :: WindowClass self => self -> IO Bool
-windowPresent :: WindowClass self => self -> IO ()
-windowDeiconify :: WindowClass self => self -> IO ()
-windowIconify :: WindowClass self => self -> IO ()
-windowMaximize :: WindowClass self => self -> IO ()
-windowUnmaximize :: WindowClass self => self -> IO ()
-windowFullscreen :: WindowClass self => self -> IO ()
-windowUnfullscreen :: WindowClass self => self -> IO ()
-windowSetKeepAbove :: WindowClass self => self -> Bool -> IO ()
-windowSetKeepBelow :: WindowClass self => self -> Bool -> IO ()
-windowSetSkipTaskbarHint :: WindowClass self => self -> Bool -> IO ()
-windowGetSkipTaskbarHint :: WindowClass self => self -> IO Bool
-windowSetSkipPagerHint :: WindowClass self => self -> Bool -> IO ()
-windowGetSkipPagerHint :: WindowClass self => self -> IO Bool
-windowSetAcceptFocus :: WindowClass self => self -> Bool -> IO ()
-windowGetAcceptFocus :: WindowClass self => self -> IO Bool
-windowSetFocusOnMap :: WindowClass self => self -> Bool -> IO ()
-windowGetFocusOnMap :: WindowClass self => self -> IO Bool
-windowSetDecorated :: WindowClass self => self -> Bool -> IO ()
-windowGetDecorated :: WindowClass self => self -> IO Bool
-windowSetFrameDimensions :: WindowClass self => self -> Int -> Int -> Int -> Int -> IO ()
-windowSetRole :: WindowClass self => self -> String -> IO ()
-windowGetRole :: WindowClass self => self -> IO (Maybe String)
-windowStick :: WindowClass self => self -> IO ()
-windowUnstick :: WindowClass self => self -> IO ()
-windowAddAccelGroup :: WindowClass self => self -> AccelGroup -> IO ()
-windowRemoveAccelGroup :: WindowClass self => self -> AccelGroup -> IO ()
-windowSetIcon :: WindowClass self => self -> Pixbuf -> IO ()
-windowSetIconName :: WindowClass self => self -> String -> IO ()
-windowGetIconName :: WindowClass self => self -> IO String
-windowSetDefaultIconName :: String -> IO ()
-windowSetGravity :: WindowClass self => self -> Gravity -> IO ()
-windowGetGravity :: WindowClass self => self -> IO Gravity
-windowSetScreen :: WindowClass self => self -> Screen -> IO ()
-windowGetScreen :: WindowClass self => self -> IO Screen
-windowBeginResizeDrag :: WindowClass self => self -> WindowEdge -> Int -> Int -> Int -> Word32 -> IO ()
-windowBeginMoveDrag :: WindowClass self => self -> Int -> Int -> Int -> Word32 -> IO ()
-windowSetTypeHint :: WindowClass self => self -> WindowTypeHint -> IO ()
-windowGetTypeHint :: WindowClass self => self -> IO WindowTypeHint
-windowGetIcon :: WindowClass self => self -> IO Pixbuf
-windowGetPosition :: WindowClass self => self -> IO (Int, Int)
-windowGetSize :: WindowClass self => self -> IO (Int, Int)
-windowMove :: WindowClass self => self -> Int -> Int -> IO ()
-windowResize :: WindowClass self => self -> Int -> Int -> IO ()
-windowSetIconFromFile :: WindowClass self => self -> FilePath -> IO Bool
-windowSetAutoStartupNotification :: Bool -> IO ()
-windowPresentWithTime :: WindowClass self => self -> Word32 -> IO ()
-windowSetUrgencyHint :: WindowClass self => self -> Bool -> IO ()
-windowGetUrgencyHint :: WindowClass self => self -> IO Bool
-windowTitle :: WindowClass self => Attr self String
-windowType :: WindowClass self => Attr self WindowType
-windowAllowShrink :: WindowClass self => Attr self Bool
-windowAllowGrow :: WindowClass self => Attr self Bool
-windowResizable :: WindowClass self => Attr self Bool
-windowModal :: WindowClass self => Attr self Bool
-windowWindowPosition :: WindowClass self => Attr self WindowPosition
-windowDefaultWidth :: WindowClass self => Attr self Int
-windowDefaultHeight :: WindowClass self => Attr self Int
-windowDestroyWithParent :: WindowClass self => Attr self Bool
-windowIcon :: WindowClass self => Attr self Pixbuf
-windowScreen :: WindowClass self => Attr self Screen
-windowTypeHint :: WindowClass self => Attr self WindowTypeHint
-windowSkipTaskbarHint :: WindowClass self => Attr self Bool
-windowSkipPagerHint :: WindowClass self => Attr self Bool
-windowUrgencyHint :: WindowClass self => Attr self Bool
-windowAcceptFocus :: WindowClass self => Attr self Bool
-windowFocusOnMap :: WindowClass self => Attr self Bool
-windowDecorated :: WindowClass self => Attr self Bool
-windowGravity :: WindowClass self => Attr self Gravity
-windowTransientFor :: (WindowClass self, WindowClass parent) => ReadWriteAttr self (Maybe Window) parent
-onFrameEvent :: WindowClass self => self -> (Event -> IO Bool) -> IO (ConnectId self)
-afterFrameEvent :: WindowClass self => self -> (Event -> IO Bool) -> IO (ConnectId self)
-onSetFocus :: (WindowClass self, WidgetClass foc) => self -> (foc -> IO ()) -> IO (ConnectId self)
-afterSetFocus :: (WindowClass self, WidgetClass foc) => self -> (foc -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Selectors.FileChooserDialog
-data FileChooserDialog
-instance BinClass FileChooserDialog
-instance ContainerClass FileChooserDialog
-instance DialogClass FileChooserDialog
-instance FileChooserClass FileChooserDialog
-instance FileChooserDialogClass FileChooserDialog
-instance GObjectClass FileChooserDialog
-instance ObjectClass FileChooserDialog
-instance WidgetClass FileChooserDialog
-instance WindowClass FileChooserDialog
-class DialogClass o => FileChooserDialogClass o
-instance FileChooserDialogClass FileChooserDialog
-castToFileChooserDialog :: GObjectClass obj => obj -> FileChooserDialog
-toFileChooserDialog :: FileChooserDialogClass o => o -> FileChooserDialog
-fileChooserDialogNew :: Maybe String -> Maybe Window -> FileChooserAction -> [(String, ResponseId)] -> IO FileChooserDialog
-fileChooserDialogNewWithBackend :: Maybe String -> Maybe Window -> FileChooserAction -> [(String, ResponseId)] -> String -> IO FileChooserDialog
-
-module Graphics.UI.Gtk.Abstract.Misc
-data Misc
-instance GObjectClass Misc
-instance MiscClass Misc
-instance ObjectClass Misc
-instance WidgetClass Misc
-class WidgetClass o => MiscClass o
-instance MiscClass AccelLabel
-instance MiscClass Arrow
-instance MiscClass Image
-instance MiscClass Label
-instance MiscClass Misc
-instance MiscClass TipsQuery
-castToMisc :: GObjectClass obj => obj -> Misc
-toMisc :: MiscClass o => o -> Misc
-miscSetAlignment :: MiscClass self => self -> Float -> Float -> IO ()
-miscGetAlignment :: MiscClass self => self -> IO (Double, Double)
-miscSetPadding :: MiscClass self => self -> Int -> Int -> IO ()
-miscGetPadding :: MiscClass self => self -> IO (Int, Int)
-miscXalign :: MiscClass self => Attr self Float
-miscYalign :: MiscClass self => Attr self Float
-miscXpad :: MiscClass self => Attr self Int
-miscYpad :: MiscClass self => Attr self Int
-
-module Graphics.UI.Gtk.Abstract.Paned
-data Paned
-instance ContainerClass Paned
-instance GObjectClass Paned
-instance ObjectClass Paned
-instance PanedClass Paned
-instance WidgetClass Paned
-class ContainerClass o => PanedClass o
-instance PanedClass HPaned
-instance PanedClass Paned
-instance PanedClass VPaned
-castToPaned :: GObjectClass obj => obj -> Paned
-toPaned :: PanedClass o => o -> Paned
-panedAdd1 :: (PanedClass self, WidgetClass child) => self -> child -> IO ()
-panedAdd2 :: (PanedClass self, WidgetClass child) => self -> child -> IO ()
-panedPack1 :: (PanedClass self, WidgetClass child) => self -> child -> Bool -> Bool -> IO ()
-panedPack2 :: (PanedClass self, WidgetClass child) => self -> child -> Bool -> Bool -> IO ()
-panedSetPosition :: PanedClass self => self -> Int -> IO ()
-panedGetPosition :: PanedClass self => self -> IO Int
-panedGetChild1 :: PanedClass self => self -> IO (Maybe Widget)
-panedGetChild2 :: PanedClass self => self -> IO (Maybe Widget)
-panedPosition :: PanedClass self => Attr self Int
-panedPositionSet :: PanedClass self => Attr self Bool
-panedMinPosition :: PanedClass self => ReadAttr self Int
-panedMaxPosition :: PanedClass self => ReadAttr self Int
-panedChildResize :: (PanedClass self, WidgetClass child) => child -> Attr self Bool
-panedChildShrink :: (PanedClass self, WidgetClass child) => child -> Attr self Bool
-onCycleChildFocus :: PanedClass self => self -> (Bool -> IO Bool) -> IO (ConnectId self)
-afterCycleChildFocus :: PanedClass self => self -> (Bool -> IO Bool) -> IO (ConnectId self)
-onToggleHandleFocus :: PanedClass self => self -> IO Bool -> IO (ConnectId self)
-afterToggleHandleFocus :: PanedClass self => self -> IO Bool -> IO (ConnectId self)
-onMoveHandle :: PanedClass self => self -> (ScrollType -> IO Bool) -> IO (ConnectId self)
-afterMoveHandle :: PanedClass self => self -> (ScrollType -> IO Bool) -> IO (ConnectId self)
-onCycleHandleFocus :: PanedClass self => self -> (Bool -> IO Bool) -> IO (ConnectId self)
-afterCycleHandleFocus :: PanedClass self => self -> (Bool -> IO Bool) -> IO (ConnectId self)
-onAcceptPosition :: PanedClass self => self -> IO Bool -> IO (ConnectId self)
-afterAcceptPosition :: PanedClass self => self -> IO Bool -> IO (ConnectId self)
-onCancelPosition :: PanedClass self => self -> IO Bool -> IO (ConnectId self)
-afterCancelPosition :: PanedClass self => self -> IO Bool -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Layout.Fixed
-data Fixed
-instance ContainerClass Fixed
-instance FixedClass Fixed
-instance GObjectClass Fixed
-instance ObjectClass Fixed
-instance WidgetClass Fixed
-class ContainerClass o => FixedClass o
-instance FixedClass Fixed
-castToFixed :: GObjectClass obj => obj -> Fixed
-toFixed :: FixedClass o => o -> Fixed
-fixedNew :: IO Fixed
-fixedPut :: (FixedClass self, WidgetClass widget) => self -> widget -> (Int, Int) -> IO ()
-fixedMove :: (FixedClass self, WidgetClass widget) => self -> widget -> (Int, Int) -> IO ()
-fixedSetHasWindow :: FixedClass self => self -> Bool -> IO ()
-fixedGetHasWindow :: FixedClass self => self -> IO Bool
-fixedHasWindow :: FixedClass self => Attr self Bool
-fixedChildX :: (FixedClass self, WidgetClass child) => child -> Attr self Int
-fixedChildY :: (FixedClass self, WidgetClass child) => child -> Attr self Int
-
-module Graphics.UI.Gtk.Layout.Layout
-data Layout
-instance ContainerClass Layout
-instance GObjectClass Layout
-instance LayoutClass Layout
-instance ObjectClass Layout
-instance WidgetClass Layout
-class ContainerClass o => LayoutClass o
-instance LayoutClass Layout
-castToLayout :: GObjectClass obj => obj -> Layout
-toLayout :: LayoutClass o => o -> Layout
-layoutNew :: Maybe Adjustment -> Maybe Adjustment -> IO Layout
-layoutPut :: (LayoutClass self, WidgetClass childWidget) => self -> childWidget -> Int -> Int -> IO ()
-layoutMove :: (LayoutClass self, WidgetClass childWidget) => self -> childWidget -> Int -> Int -> IO ()
-layoutSetSize :: LayoutClass self => self -> Int -> Int -> IO ()
-layoutGetSize :: LayoutClass self => self -> IO (Int, Int)
-layoutGetHAdjustment :: LayoutClass self => self -> IO Adjustment
-layoutGetVAdjustment :: LayoutClass self => self -> IO Adjustment
-layoutSetHAdjustment :: LayoutClass self => self -> Adjustment -> IO ()
-layoutSetVAdjustment :: LayoutClass self => self -> Adjustment -> IO ()
-layoutGetDrawWindow :: Layout -> IO DrawWindow
-layoutHAdjustment :: LayoutClass self => Attr self Adjustment
-layoutVAdjustment :: LayoutClass self => Attr self Adjustment
-layoutWidth :: LayoutClass self => Attr self Int
-layoutHeight :: LayoutClass self => Attr self Int
-layoutChildX :: (LayoutClass self, WidgetClass child) => child -> Attr self Int
-layoutChildY :: (LayoutClass self, WidgetClass child) => child -> Attr self Int
-onSetScrollAdjustments :: LayoutClass self => self -> (Adjustment -> Adjustment -> IO ()) -> IO (ConnectId self)
-afterSetScrollAdjustments :: LayoutClass self => self -> (Adjustment -> Adjustment -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Layout.Notebook
-data Notebook
-instance ContainerClass Notebook
-instance GObjectClass Notebook
-instance NotebookClass Notebook
-instance ObjectClass Notebook
-instance WidgetClass Notebook
-class ContainerClass o => NotebookClass o
-instance NotebookClass Notebook
-castToNotebook :: GObjectClass obj => obj -> Notebook
-toNotebook :: NotebookClass o => o -> Notebook
-notebookNew :: IO Notebook
-notebookAppendPage :: (NotebookClass self, WidgetClass child) => self -> child -> String -> IO Int
-notebookAppendPageMenu :: (NotebookClass self, WidgetClass child, WidgetClass tabLabel, WidgetClass menuLabel) => self -> child -> tabLabel -> menuLabel -> IO Int
-notebookPrependPage :: (NotebookClass self, WidgetClass child) => self -> child -> String -> IO Int
-notebookPrependPageMenu :: (NotebookClass self, WidgetClass child, WidgetClass tabLabel, WidgetClass menuLabel) => self -> child -> tabLabel -> menuLabel -> IO Int
-notebookInsertPage :: (NotebookClass self, WidgetClass child) => self -> child -> String -> Int -> IO Int
-notebookInsertPageMenu :: (NotebookClass self, WidgetClass child, WidgetClass tabLabel, WidgetClass menuLabel) => self -> child -> tabLabel -> menuLabel -> Int -> IO Int
-notebookRemovePage :: NotebookClass self => self -> Int -> IO ()
-notebookPageNum :: (NotebookClass self, WidgetClass w) => self -> w -> IO (Maybe Int)
-notebookSetCurrentPage :: NotebookClass self => self -> Int -> IO ()
-notebookNextPage :: NotebookClass self => self -> IO ()
-notebookPrevPage :: NotebookClass self => self -> IO ()
-notebookReorderChild :: (NotebookClass self, WidgetClass child) => self -> child -> Int -> IO ()
-data PositionType
-PosLeft :: PositionType
-PosRight :: PositionType
-PosTop :: PositionType
-PosBottom :: PositionType
-instance Enum PositionType
-instance Eq PositionType
-notebookSetTabPos :: NotebookClass self => self -> PositionType -> IO ()
-notebookGetTabPos :: NotebookClass self => self -> IO PositionType
-notebookSetShowTabs :: NotebookClass self => self -> Bool -> IO ()
-notebookGetShowTabs :: NotebookClass self => self -> IO Bool
-notebookSetShowBorder :: NotebookClass self => self -> Bool -> IO ()
-notebookGetShowBorder :: NotebookClass self => self -> IO Bool
-notebookSetScrollable :: NotebookClass self => self -> Bool -> IO ()
-notebookGetScrollable :: NotebookClass self => self -> IO Bool
-notebookSetTabBorder :: NotebookClass self => self -> Int -> IO ()
-notebookSetTabHBorder :: NotebookClass self => self -> Int -> IO ()
-notebookSetTabVBorder :: NotebookClass self => self -> Int -> IO ()
-notebookSetPopup :: NotebookClass self => self -> Bool -> IO ()
-notebookGetCurrentPage :: NotebookClass self => self -> IO Int
-notebookSetMenuLabel :: (NotebookClass self, WidgetClass child, WidgetClass menuLabel) => self -> child -> Maybe menuLabel -> IO ()
-notebookGetMenuLabel :: (NotebookClass self, WidgetClass child) => self -> child -> IO (Maybe Widget)
-notebookSetMenuLabelText :: (NotebookClass self, WidgetClass child) => self -> child -> String -> IO ()
-notebookGetMenuLabelText :: (NotebookClass self, WidgetClass child) => self -> child -> IO (Maybe String)
-notebookGetNthPage :: NotebookClass self => self -> Int -> IO (Maybe Widget)
-notebookGetNPages :: NotebookClass self => self -> IO Int
-notebookGetTabLabel :: (NotebookClass self, WidgetClass child) => self -> child -> IO (Maybe Widget)
-notebookGetTabLabelText :: (NotebookClass self, WidgetClass child) => self -> child -> IO (Maybe String)
-data Packing
-PackRepel :: Packing
-PackGrow :: Packing
-PackNatural :: Packing
-instance Enum Packing
-instance Eq Packing
-data PackType
-PackStart :: PackType
-PackEnd :: PackType
-instance Enum PackType
-instance Eq PackType
-notebookQueryTabLabelPacking :: (NotebookClass self, WidgetClass child) => self -> child -> IO (Packing, PackType)
-notebookSetTabLabelPacking :: (NotebookClass self, WidgetClass child) => self -> child -> Packing -> PackType -> IO ()
-notebookSetHomogeneousTabs :: NotebookClass self => self -> Bool -> IO ()
-notebookSetTabLabel :: (NotebookClass self, WidgetClass child, WidgetClass tabLabel) => self -> child -> tabLabel -> IO ()
-notebookSetTabLabelText :: (NotebookClass self, WidgetClass child) => self -> child -> String -> IO ()
-notebookPage :: NotebookClass self => Attr self Int
-notebookTabPos :: NotebookClass self => Attr self PositionType
-notebookTabBorder :: NotebookClass self => WriteAttr self Int
-notebookTabHborder :: NotebookClass self => Attr self Int
-notebookTabVborder :: NotebookClass self => Attr self Int
-notebookShowTabs :: NotebookClass self => Attr self Bool
-notebookShowBorder :: NotebookClass self => Attr self Bool
-notebookScrollable :: NotebookClass self => Attr self Bool
-notebookEnablePopup :: NotebookClass self => Attr self Bool
-notebookHomogeneous :: NotebookClass self => Attr self Bool
-notebookCurrentPage :: NotebookClass self => Attr self Int
-notebookChildTabLabel :: (NotebookClass self, WidgetClass child) => child -> Attr self String
-notebookChildMenuLabel :: (NotebookClass self, WidgetClass child) => child -> Attr self String
-notebookChildPosition :: (NotebookClass self, WidgetClass child) => child -> Attr self Int
-notebookChildTabPacking :: (NotebookClass self, WidgetClass child) => child -> Attr self Packing
-notebookChildTabPackType :: (NotebookClass self, WidgetClass child) => child -> Attr self PackType
-onSwitchPage :: NotebookClass nb => nb -> (Int -> IO ()) -> IO (ConnectId nb)
-afterSwitchPage :: NotebookClass nb => nb -> (Int -> IO ()) -> IO (ConnectId nb)
-
-module Graphics.UI.Gtk.Layout.Table
-data Table
-instance ContainerClass Table
-instance GObjectClass Table
-instance ObjectClass Table
-instance TableClass Table
-instance WidgetClass Table
-class ContainerClass o => TableClass o
-instance TableClass Table
-castToTable :: GObjectClass obj => obj -> Table
-toTable :: TableClass o => o -> Table
-tableNew :: Int -> Int -> Bool -> IO Table
-tableResize :: TableClass self => self -> Int -> Int -> IO ()
-data AttachOptions
-Expand :: AttachOptions
-Shrink :: AttachOptions
-Fill :: AttachOptions
-instance Bounded AttachOptions
-instance Enum AttachOptions
-instance Eq AttachOptions
-instance Flags AttachOptions
-tableAttach :: (TableClass self, WidgetClass child) => self -> child -> Int -> Int -> Int -> Int -> [AttachOptions] -> [AttachOptions] -> Int -> Int -> IO ()
-tableAttachDefaults :: (TableClass self, WidgetClass widget) => self -> widget -> Int -> Int -> Int -> Int -> IO ()
-tableSetRowSpacing :: TableClass self => self -> Int -> Int -> IO ()
-tableGetRowSpacing :: TableClass self => self -> Int -> IO Int
-tableSetColSpacing :: TableClass self => self -> Int -> Int -> IO ()
-tableGetColSpacing :: TableClass self => self -> Int -> IO Int
-tableSetRowSpacings :: TableClass self => self -> Int -> IO ()
-tableGetDefaultRowSpacing :: TableClass self => self -> IO Int
-tableSetColSpacings :: TableClass self => self -> Int -> IO ()
-tableGetDefaultColSpacing :: TableClass self => self -> IO Int
-tableSetHomogeneous :: TableClass self => self -> Bool -> IO ()
-tableGetHomogeneous :: TableClass self => self -> IO Bool
-tableNRows :: TableClass self => Attr self Int
-tableNColumns :: TableClass self => Attr self Int
-tableRowSpacing :: TableClass self => Attr self Int
-tableColumnSpacing :: TableClass self => Attr self Int
-tableHomogeneous :: TableClass self => Attr self Bool
-tableChildLeftAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
-tableChildRightAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
-tableChildTopAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
-tableChildBottomAttach :: (TableClass self, WidgetClass child) => child -> Attr self Int
-tableChildXOptions :: (TableClass self, WidgetClass child) => child -> Attr self [AttachOptions]
-tableChildYOptions :: (TableClass self, WidgetClass child) => child -> Attr self [AttachOptions]
-tableChildXPadding :: (TableClass self, WidgetClass child) => child -> Attr self Int
-tableChildYPadding :: (TableClass self, WidgetClass child) => child -> Attr self Int
-
-module Graphics.UI.Gtk.MenuComboToolbar.Menu
-data Menu
-instance ContainerClass Menu
-instance GObjectClass Menu
-instance MenuClass Menu
-instance MenuShellClass Menu
-instance ObjectClass Menu
-instance WidgetClass Menu
-class MenuShellClass o => MenuClass o
-instance MenuClass Menu
-castToMenu :: GObjectClass obj => obj -> Menu
-toMenu :: MenuClass o => o -> Menu
-menuNew :: IO Menu
-menuReorderChild :: (MenuClass self, MenuItemClass child) => self -> child -> Int -> IO ()
-menuPopup :: MenuClass self => self -> Event -> IO ()
-menuSetAccelGroup :: MenuClass self => self -> AccelGroup -> IO ()
-menuGetAccelGroup :: MenuClass self => self -> IO AccelGroup
-menuSetAccelPath :: MenuClass self => self -> String -> IO ()
-menuSetTitle :: MenuClass self => self -> String -> IO ()
-menuGetTitle :: MenuClass self => self -> IO (Maybe String)
-menuPopdown :: MenuClass self => self -> IO ()
-menuReposition :: MenuClass self => self -> IO ()
-menuGetActive :: MenuClass self => self -> IO MenuItem
-menuSetActive :: MenuClass self => self -> Int -> IO ()
-menuSetTearoffState :: MenuClass self => self -> Bool -> IO ()
-menuGetTearoffState :: MenuClass self => self -> IO Bool
-menuAttachToWidget :: (MenuClass self, WidgetClass attachWidget) => self -> attachWidget -> IO ()
-menuDetach :: MenuClass self => self -> IO ()
-menuGetAttachWidget :: MenuClass self => self -> IO (Maybe Widget)
-menuSetScreen :: MenuClass self => self -> Maybe Screen -> IO ()
-menuSetMonitor :: MenuClass self => self -> Int -> IO ()
-menuAttach :: (MenuClass self, MenuItemClass child) => self -> child -> Int -> Int -> Int -> Int -> IO ()
-menuGetForAttachWidget :: WidgetClass widget => widget -> IO [Menu]
-menuTearoffState :: MenuClass self => Attr self Bool
-menuAccelGroup :: MenuClass self => Attr self AccelGroup
-menuActive :: MenuClass self => ReadWriteAttr self MenuItem Int
-menuTitle :: MenuClass self => ReadWriteAttr self (Maybe String) String
-menuChildLeftAttach :: (MenuClass self, WidgetClass child) => child -> Attr self Int
-menuChildRightAttach :: (MenuClass self, WidgetClass child) => child -> Attr self Int
-menuChildTopAttach :: (MenuClass self, WidgetClass child) => child -> Attr self Int
-menuChildBottomAttach :: (MenuClass self, WidgetClass child) => child -> Attr self Int
-
-module Graphics.UI.Gtk.MenuComboToolbar.Toolbar
-data Toolbar
-instance ContainerClass Toolbar
-instance GObjectClass Toolbar
-instance ObjectClass Toolbar
-instance ToolbarClass Toolbar
-instance WidgetClass Toolbar
-class ContainerClass o => ToolbarClass o
-instance ToolbarClass Toolbar
-castToToolbar :: GObjectClass obj => obj -> Toolbar
-toToolbar :: ToolbarClass o => o -> Toolbar
-data Orientation
-OrientationHorizontal :: Orientation
-OrientationVertical :: Orientation
-instance Enum Orientation
-instance Eq Orientation
-data ToolbarStyle
-ToolbarIcons :: ToolbarStyle
-ToolbarText :: ToolbarStyle
-ToolbarBoth :: ToolbarStyle
-ToolbarBothHoriz :: ToolbarStyle
-instance Enum ToolbarStyle
-instance Eq ToolbarStyle
-toolbarNew :: IO Toolbar
-toolbarInsertNewButton :: ToolbarClass self => self -> Int -> String -> Maybe (String, String) -> IO Button
-toolbarAppendNewButton :: ToolbarClass self => self -> String -> Maybe (String, String) -> IO Button
-toolbarPrependNewButton :: ToolbarClass self => self -> String -> Maybe (String, String) -> IO Button
-toolbarInsertNewToggleButton :: ToolbarClass self => self -> Int -> String -> Maybe (String, String) -> IO ToggleButton
-toolbarAppendNewToggleButton :: ToolbarClass self => self -> String -> Maybe (String, String) -> IO ToggleButton
-toolbarPrependNewToggleButton :: ToolbarClass self => self -> String -> Maybe (String, String) -> IO ToggleButton
-toolbarInsertNewRadioButton :: (ToolbarClass self, RadioButtonClass rb) => self -> Int -> String -> Maybe (String, String) -> Maybe rb -> IO RadioButton
-toolbarAppendNewRadioButton :: (ToolbarClass self, RadioButtonClass rb) => self -> String -> Maybe (String, String) -> Maybe rb -> IO RadioButton
-toolbarPrependNewRadioButton :: (ToolbarClass self, RadioButtonClass rb) => self -> String -> Maybe (String, String) -> Maybe rb -> IO RadioButton
-toolbarInsertNewWidget :: (ToolbarClass self, WidgetClass w) => self -> Int -> w -> Maybe (String, String) -> IO ()
-toolbarAppendNewWidget :: (ToolbarClass self, WidgetClass w) => self -> w -> Maybe (String, String) -> IO ()
-toolbarPrependNewWidget :: (ToolbarClass self, WidgetClass w) => self -> w -> Maybe (String, String) -> IO ()
-toolbarSetOrientation :: ToolbarClass self => self -> Orientation -> IO ()
-toolbarGetOrientation :: ToolbarClass self => self -> IO Orientation
-toolbarSetStyle :: ToolbarClass self => self -> ToolbarStyle -> IO ()
-toolbarGetStyle :: ToolbarClass self => self -> IO ToolbarStyle
-toolbarUnsetStyle :: ToolbarClass self => self -> IO ()
-toolbarSetTooltips :: ToolbarClass self => self -> Bool -> IO ()
-toolbarGetTooltips :: ToolbarClass self => self -> IO Bool
-type IconSize = Int
-iconSizeInvalid :: IconSize
-iconSizeSmallToolbar :: IconSize
-iconSizeLargeToolbar :: IconSize
-toolbarSetIconSize :: ToolbarClass self => self -> IconSize -> IO ()
-toolbarGetIconSize :: ToolbarClass self => self -> IO IconSize
-toolbarInsert :: (ToolbarClass self, ToolItemClass item) => self -> item -> Int -> IO ()
-toolbarGetItemIndex :: (ToolbarClass self, ToolItemClass item) => self -> item -> IO Int
-toolbarGetNItems :: ToolbarClass self => self -> IO Int
-toolbarGetNthItem :: ToolbarClass self => self -> Int -> IO (Maybe ToolItem)
-toolbarGetDropIndex :: ToolbarClass self => self -> (Int, Int) -> IO Int
-toolbarSetDropHighlightItem :: (ToolbarClass self, ToolItemClass toolItem) => self -> Maybe toolItem -> Int -> IO ()
-toolbarSetShowArrow :: ToolbarClass self => self -> Bool -> IO ()
-toolbarGetShowArrow :: ToolbarClass self => self -> IO Bool
-data ReliefStyle
-ReliefNormal :: ReliefStyle
-ReliefHalf :: ReliefStyle
-ReliefNone :: ReliefStyle
-instance Enum ReliefStyle
-instance Eq ReliefStyle
-toolbarGetReliefStyle :: ToolbarClass self => self -> IO ReliefStyle
-toolbarOrientation :: ToolbarClass self => Attr self Orientation
-toolbarShowArrow :: ToolbarClass self => Attr self Bool
-toolbarTooltips :: ToolbarClass self => Attr self Bool
-toolbarStyle :: ToolbarClass self => Attr self ToolbarStyle
-toolbarChildExpand :: (ToolbarClass self, WidgetClass child) => child -> Attr self Bool
-toolbarChildHomogeneous :: (ToolbarClass self, WidgetClass child) => child -> Attr self Bool
-onOrientationChanged :: ToolbarClass self => self -> (Orientation -> IO ()) -> IO (ConnectId self)
-afterOrientationChanged :: ToolbarClass self => self -> (Orientation -> IO ()) -> IO (ConnectId self)
-onStyleChanged :: ToolbarClass self => self -> (ToolbarStyle -> IO ()) -> IO (ConnectId self)
-afterStyleChanged :: ToolbarClass self => self -> (ToolbarStyle -> IO ()) -> IO (ConnectId self)
-onPopupContextMenu :: ToolbarClass self => self -> (Int -> Int -> Int -> IO Bool) -> IO (ConnectId self)
-afterPopupContextMenu :: ToolbarClass self => self -> (Int -> Int -> Int -> IO Bool) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.Abstract.Container
-data Container
-instance ContainerClass Container
-instance GObjectClass Container
-instance ObjectClass Container
-instance WidgetClass Container
-class WidgetClass o => ContainerClass o
-instance ContainerClass AboutDialog
-instance ContainerClass Alignment
-instance ContainerClass AspectFrame
-instance ContainerClass Bin
-instance ContainerClass Box
-instance ContainerClass Button
-instance ContainerClass ButtonBox
-instance ContainerClass CList
-instance ContainerClass CTree
-instance ContainerClass CheckButton
-instance ContainerClass CheckMenuItem
-instance ContainerClass ColorButton
-instance ContainerClass ColorSelection
-instance ContainerClass ColorSelectionDialog
-instance ContainerClass Combo
-instance ContainerClass ComboBox
-instance ContainerClass ComboBoxEntry
-instance ContainerClass Container
-instance ContainerClass Dialog
-instance ContainerClass EventBox
-instance ContainerClass Expander
-instance ContainerClass FileChooserButton
-instance ContainerClass FileChooserDialog
-instance ContainerClass FileChooserWidget
-instance ContainerClass FileSelection
-instance ContainerClass Fixed
-instance ContainerClass FontButton
-instance ContainerClass FontSelection
-instance ContainerClass FontSelectionDialog
-instance ContainerClass Frame
-instance ContainerClass GammaCurve
-instance ContainerClass HBox
-instance ContainerClass HButtonBox
-instance ContainerClass HPaned
-instance ContainerClass HandleBox
-instance ContainerClass IconView
-instance ContainerClass ImageMenuItem
-instance ContainerClass InputDialog
-instance ContainerClass Item
-instance ContainerClass Layout
-instance ContainerClass List
-instance ContainerClass ListItem
-instance ContainerClass Menu
-instance ContainerClass MenuBar
-instance ContainerClass MenuItem
-instance ContainerClass MenuShell
-instance ContainerClass MenuToolButton
-instance ContainerClass MessageDialog
-instance ContainerClass MozEmbed
-instance ContainerClass Notebook
-instance ContainerClass OptionMenu
-instance ContainerClass Paned
-instance ContainerClass Plug
-instance ContainerClass RadioButton
-instance ContainerClass RadioMenuItem
-instance ContainerClass RadioToolButton
-instance ContainerClass ScrolledWindow
-instance ContainerClass SeparatorMenuItem
-instance ContainerClass SeparatorToolItem
-instance ContainerClass Socket
-instance ContainerClass SourceView
-instance ContainerClass Statusbar
-instance ContainerClass Table
-instance ContainerClass TearoffMenuItem
-instance ContainerClass TextView
-instance ContainerClass ToggleButton
-instance ContainerClass ToggleToolButton
-instance ContainerClass ToolButton
-instance ContainerClass ToolItem
-instance ContainerClass Toolbar
-instance ContainerClass TreeView
-instance ContainerClass VBox
-instance ContainerClass VButtonBox
-instance ContainerClass VPaned
-instance ContainerClass Viewport
-instance ContainerClass Window
-castToContainer :: GObjectClass obj => obj -> Container
-toContainer :: ContainerClass o => o -> Container
-type ContainerForeachCB = Widget -> IO ()
-data ResizeMode
-ResizeParent :: ResizeMode
-ResizeQueue :: ResizeMode
-ResizeImmediate :: ResizeMode
-instance Enum ResizeMode
-instance Eq ResizeMode
-containerAdd :: (ContainerClass self, WidgetClass widget) => self -> widget -> IO ()
-containerRemove :: (ContainerClass self, WidgetClass widget) => self -> widget -> IO ()
-containerForeach :: ContainerClass self => self -> ContainerForeachCB -> IO ()
-containerForall :: ContainerClass self => self -> ContainerForeachCB -> IO ()
-containerGetChildren :: ContainerClass self => self -> IO [Widget]
-data DirectionType
-DirTabForward :: DirectionType
-DirTabBackward :: DirectionType
-DirUp :: DirectionType
-DirDown :: DirectionType
-DirLeft :: DirectionType
-DirRight :: DirectionType
-instance Enum DirectionType
-instance Eq DirectionType
-containerSetFocusChild :: (ContainerClass self, WidgetClass child) => self -> child -> IO ()
-containerSetFocusChain :: ContainerClass self => self -> [Widget] -> IO ()
-containerGetFocusChain :: ContainerClass self => self -> IO (Maybe [Widget])
-containerUnsetFocusChain :: ContainerClass self => self -> IO ()
-containerSetFocusVAdjustment :: ContainerClass self => self -> Adjustment -> IO ()
-containerGetFocusVAdjustment :: ContainerClass self => self -> IO (Maybe Adjustment)
-containerSetFocusHAdjustment :: ContainerClass self => self -> Adjustment -> IO ()
-containerGetFocusHAdjustment :: ContainerClass self => self -> IO (Maybe Adjustment)
-containerResizeChildren :: ContainerClass self => self -> IO ()
-containerSetBorderWidth :: ContainerClass self => self -> Int -> IO ()
-containerGetBorderWidth :: ContainerClass self => self -> IO Int
-containerGetResizeMode :: ContainerClass self => self -> IO ResizeMode
-containerSetResizeMode :: ContainerClass self => self -> ResizeMode -> IO ()
-containerResizeMode :: ContainerClass self => Attr self ResizeMode
-containerBorderWidth :: ContainerClass self => Attr self Int
-containerChild :: (ContainerClass self, WidgetClass widget) => WriteAttr self widget
-containerFocusHAdjustment :: ContainerClass self => ReadWriteAttr self (Maybe Adjustment) Adjustment
-containerFocusVAdjustment :: ContainerClass self => ReadWriteAttr self (Maybe Adjustment) Adjustment
-onAdd :: ContainerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-afterAdd :: ContainerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-onCheckResize :: ContainerClass self => self -> IO () -> IO (ConnectId self)
-afterCheckResize :: ContainerClass self => self -> IO () -> IO (ConnectId self)
-onFocus :: ContainerClass con => con -> (DirectionType -> IO DirectionType) -> IO (ConnectId con)
-afterFocus :: ContainerClass con => con -> (DirectionType -> IO DirectionType) -> IO (ConnectId con)
-onRemove :: ContainerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-afterRemove :: ContainerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-onSetFocusChild :: ContainerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-afterSetFocusChild :: ContainerClass self => self -> (Widget -> IO ()) -> IO (ConnectId self)
-
-module Graphics.UI.Gtk.MenuComboToolbar.Combo
-data Combo
-instance BoxClass Combo
-instance ComboClass Combo
-instance ContainerClass Combo
-instance GObjectClass Combo
-instance HBoxClass Combo
-instance ObjectClass Combo
-instance WidgetClass Combo
-class HBoxClass o => ComboClass o
-instance ComboClass Combo
-castToCombo :: GObjectClass obj => obj -> Combo
-toCombo :: ComboClass o => o -> Combo
-comboNew :: IO Combo
-comboSetPopdownStrings :: ComboClass self => self -> [String] -> IO ()
-comboSetValueInList :: ComboClass self => self -> Bool -> Bool -> IO ()
-comboSetUseArrows :: ComboClass self => self -> Bool -> IO ()
-comboSetUseArrowsAlways :: ComboClass self => self -> Bool -> IO ()
-comboSetCaseSensitive :: ComboClass self => self -> Bool -> IO ()
-comboDisableActivate :: ComboClass self => self -> IO ()
-comboEnableArrowKeys :: ComboClass self => Attr self Bool
-comboEnableArrowsAlways :: ComboClass self => Attr self Bool
-comboCaseSensitive :: ComboClass self => Attr self Bool
-comboAllowEmpty :: ComboClass self => Attr self Bool
-comboValueInList :: ComboClass self => Attr self Bool
-
-module Graphics.UI.Gtk.Abstract.ButtonBox
-data ButtonBox
-instance BoxClass ButtonBox
-instance ButtonBoxClass ButtonBox
-instance ContainerClass ButtonBox
-instance GObjectClass ButtonBox
-instance ObjectClass ButtonBox
-instance WidgetClass ButtonBox
-class BoxClass o => ButtonBoxClass o
-instance ButtonBoxClass ButtonBox
-instance ButtonBoxClass HButtonBox
-instance ButtonBoxClass VButtonBox
-castToButtonBox :: GObjectClass obj => obj -> ButtonBox
-toButtonBox :: ButtonBoxClass o => o -> ButtonBox
-data ButtonBoxStyle
-ButtonboxDefaultStyle :: ButtonBoxStyle
-ButtonboxSpread :: ButtonBoxStyle
-ButtonboxEdge :: ButtonBoxStyle
-ButtonboxStart :: ButtonBoxStyle
-ButtonboxEnd :: ButtonBoxStyle
-instance Enum ButtonBoxStyle
-instance Eq ButtonBoxStyle
-buttonBoxGetLayout :: ButtonBoxClass self => self -> IO ButtonBoxStyle
-buttonBoxSetLayout :: ButtonBoxClass self => self -> ButtonBoxStyle -> IO ()
-buttonBoxSetChildSecondary :: (ButtonBoxClass self, WidgetClass child) => self -> child -> Bool -> IO ()
-buttonBoxGetChildSecondary :: (ButtonBoxClass self, WidgetClass child) => self -> child -> IO Bool
-buttonBoxLayoutStyle :: ButtonBoxClass self => Attr self ButtonBoxStyle
-buttonBoxChildSecondary :: (ButtonBoxClass self, WidgetClass child) => child -> Attr self Bool
-
-module Graphics.UI.Gtk.Abstract.Box
-data Box
-instance BoxClass Box
-instance ContainerClass Box
-instance GObjectClass Box
-instance ObjectClass Box
-instance WidgetClass Box
-class ContainerClass o => BoxClass o
-instance BoxClass Box
-instance BoxClass ButtonBox
-instance BoxClass ColorSelection
-instance BoxClass Combo
-instance BoxClass FileChooserButton
-instance BoxClass FileChooserWidget
-instance BoxClass FontSelection
-instance BoxClass GammaCurve
-instance BoxClass HBox
-instance BoxClass HButtonBox
-instance BoxClass Statusbar
-instance BoxClass VBox
-instance BoxClass VButtonBox
-castToBox :: GObjectClass obj => obj -> Box
-toBox :: BoxClass o => o -> Box
-data Packing
-PackRepel :: Packing
-PackGrow :: Packing
-PackNatural :: Packing
-instance Enum Packing
-instance Eq Packing
-boxPackStart :: (BoxClass self, WidgetClass child) => self -> child -> Packing -> Int -> IO ()
-boxPackEnd :: (BoxClass self, WidgetClass child) => self -> child -> Packing -> Int -> IO ()
-boxPackStartDefaults :: (BoxClass self, WidgetClass widget) => self -> widget -> IO ()
-boxPackEndDefaults :: (BoxClass self, WidgetClass widget) => self -> widget -> IO ()
-boxGetHomogeneous :: BoxClass self => self -> IO Bool
-boxSetHomogeneous :: BoxClass self => self -> Bool -> IO ()
-boxGetSpacing :: BoxClass self => self -> IO Int
-boxSetSpacing :: BoxClass self => self -> Int -> IO ()
-boxReorderChild :: (BoxClass self, WidgetClass child) => self -> child -> Int -> IO ()
-boxQueryChildPacking :: (BoxClass self, WidgetClass child) => self -> child -> IO (Packing, Int, PackType)
-boxSetChildPacking :: (BoxClass self, WidgetClass child) => self -> child -> Packing -> Int -> PackType -> IO ()
-boxSpacing :: BoxClass self => Attr self Int
-boxHomogeneous :: BoxClass self => Attr self Bool
-boxChildPacking :: (BoxClass self, WidgetClass child) => child -> Attr self Packing
-boxChildPadding :: (BoxClass self, WidgetClass child) => child -> Attr self Int
-boxChildPackType :: (BoxClass self, WidgetClass child) => child -> Attr self PackType
-boxChildPosition :: (BoxClass self, WidgetClass child) => child -> Attr self Int
-
-module Graphics.UI.Gtk.Abstract.Bin
-data Bin
-instance BinClass Bin
-instance ContainerClass Bin
-instance GObjectClass Bin
-instance ObjectClass Bin
-instance WidgetClass Bin
-class ContainerClass o => BinClass o
-instance BinClass AboutDialog
-instance BinClass Alignment
-instance BinClass AspectFrame
-instance BinClass Bin
-instance BinClass Button
-instance BinClass CheckButton
-instance BinClass CheckMenuItem
-instance BinClass ColorButton
-instance BinClass ColorSelectionDialog
-instance BinClass ComboBox
-instance BinClass ComboBoxEntry
-instance BinClass Dialog
-instance BinClass EventBox
-instance BinClass Expander
-instance BinClass FileChooserDialog
-instance BinClass FileSelection
-instance BinClass FontButton
-instance BinClass FontSelectionDialog
-instance BinClass Frame
-instance BinClass HandleBox
-instance BinClass ImageMenuItem
-instance BinClass InputDialog
-instance BinClass Item
-instance BinClass ListItem
-instance BinClass MenuItem
-instance BinClass MenuToolButton
-instance BinClass MessageDialog
-instance BinClass MozEmbed
-instance BinClass OptionMenu
-instance BinClass Plug
-instance BinClass RadioButton
-instance BinClass RadioMenuItem
-instance BinClass RadioToolButton
-instance BinClass ScrolledWindow
-instance BinClass SeparatorMenuItem
-instance BinClass SeparatorToolItem
-instance BinClass TearoffMenuItem
-instance BinClass ToggleButton
-instance BinClass ToggleToolButton
-instance BinClass ToolButton
-instance BinClass ToolItem
-instance BinClass Viewport
-instance BinClass Window
-castToBin :: GObjectClass obj => obj -> Bin
-toBin :: BinClass o => o -> Bin
-binGetChild :: BinClass self => self -> IO (Maybe Widget)
-
-module Graphics.Rendering.Cairo.Matrix
-data Matrix
-Matrix :: Double -> Double -> Double -> Double -> Double -> Double -> Matrix
-instance Eq Matrix
-instance Num Matrix
-instance Show Matrix
-instance Storable Matrix
-type MatrixPtr = Ptr Matrix
-identity :: Matrix
-translate :: Double -> Double -> Matrix -> Matrix
-scale :: Double -> Double -> Matrix -> Matrix
-rotate :: Double -> Matrix -> Matrix
-transformDistance :: Matrix -> (Double, Double) -> (Double, Double)
-transformPoint :: Matrix -> (Double, Double) -> (Double, Double)
-scalarMultiply :: Double -> Matrix -> Matrix
-adjoint :: Matrix -> Matrix
-invert :: Matrix -> Matrix
-
-module Graphics.Rendering.Cairo
-renderWith :: MonadIO m => Surface -> Render a -> m a
-save :: Render ()
-restore :: Render ()
-status :: Render Status
-withTargetSurface :: (Surface -> Render a) -> Render a
-setSourceRGB :: Double -> Double -> Double -> Render ()
-setSourceRGBA :: Double -> Double -> Double -> Double -> Render ()
-setSource :: Pattern -> Render ()
-setSourceSurface :: Surface -> Double -> Double -> Render ()
-getSource :: Render Pattern
-setAntialias :: Antialias -> Render ()
-setDash :: [Double] -> Double -> Render ()
-setFillRule :: FillRule -> Render ()
-getFillRule :: Render FillRule
-setLineCap :: LineCap -> Render ()
-getLineCap :: Render LineCap
-setLineJoin :: LineJoin -> Render ()
-getLineJoin :: Render LineJoin
-setLineWidth :: Double -> Render ()
-getLineWidth :: Render Double
-setMiterLimit :: Double -> Render ()
-getMiterLimit :: Render Double
-setOperator :: Operator -> Render ()
-getOperator :: Render Operator
-setTolerance :: Double -> Render ()
-getTolerance :: Render Double
-clip :: Render ()
-clipPreserve :: Render ()
-resetClip :: Render ()
-fill :: Render ()
-fillPreserve :: Render ()
-fillExtents :: Render (Double, Double, Double, Double)
-inFill :: Double -> Double -> Render Bool
-mask :: Pattern -> Render ()
-maskSurface :: Surface -> Double -> Double -> Render ()
-paint :: Render ()
-paintWithAlpha :: Double -> Render ()
-stroke :: Render ()
-strokePreserve :: Render ()
-strokeExtents :: Render (Double, Double, Double, Double)
-inStroke :: Double -> Double -> Render Bool
-copyPage :: Render ()
-showPage :: Render ()
-getCurrentPoint :: Render (Double, Double)
-newPath :: Render ()
-closePath :: Render ()
-arc :: Double -> Double -> Double -> Double -> Double -> Render ()
-arcNegative :: Double -> Double -> Double -> Double -> Double -> Render ()
-curveTo :: Double -> Double -> Double -> Double -> Double -> Double -> Render ()
-lineTo :: Double -> Double -> Render ()
-moveTo :: Double -> Double -> Render ()
-rectangle :: Double -> Double -> Double -> Double -> Render ()
-textPath :: String -> Render ()
-relCurveTo :: Double -> Double -> Double -> Double -> Double -> Double -> Render ()
-relLineTo :: Double -> Double -> Render ()
-relMoveTo :: Double -> Double -> Render ()
-withRGBPattern :: Double -> Double -> Double -> (Pattern -> Render a) -> Render a
-withRGBAPattern :: Double -> Double -> Double -> Double -> (Pattern -> Render a) -> Render a
-withPatternForSurface :: Surface -> (Pattern -> Render a) -> Render a
-withLinearPattern :: Double -> Double -> Double -> Double -> (Pattern -> Render a) -> Render a
-withRadialPattern :: Double -> Double -> Double -> Double -> Double -> Double -> (Pattern -> Render a) -> Render a
-patternAddColorStopRGB :: Pattern -> Double -> Double -> Double -> Double -> Render ()
-patternAddColorStopRGBA :: Pattern -> Double -> Double -> Double -> Double -> Double -> Render ()
-patternSetMatrix :: Pattern -> Matrix -> Render ()
-patternGetMatrix :: Pattern -> Render Matrix
-patternSetExtend :: Pattern -> Extend -> Render ()
-patternGetExtend :: Pattern -> Render Extend
-patternSetFilter :: Pattern -> Filter -> Render ()
-patternGetFilter :: Pattern -> Render Filter
-translate :: Double -> Double -> Render ()
-scale :: Double -> Double -> Render ()
-rotate :: Double -> Render ()
-transform :: Matrix -> Render ()
-setMatrix :: Matrix -> Render ()
-getMatrix :: Render Matrix
-identityMatrix :: Render ()
-userToDevice :: Double -> Double -> Render (Double, Double)
-userToDeviceDistance :: Double -> Double -> Render (Double, Double)
-deviceToUser :: Double -> Double -> Render (Double, Double)
-deviceToUserDistance :: Double -> Double -> Render (Double, Double)
-selectFontFace :: String -> FontSlant -> FontWeight -> Render ()
-setFontSize :: Double -> Render ()
-setFontMatrix :: Matrix -> Render ()
-getFontMatrix :: Render Matrix
-showText :: String -> Render ()
-fontExtents :: Render FontExtents
-textExtents :: String -> Render TextExtents
-fontOptionsCreate :: Render FontOptions
-fontOptionsCopy :: FontOptions -> Render FontOptions
-fontOptionsMerge :: FontOptions -> FontOptions -> Render ()
-fontOptionsHash :: FontOptions -> Render Int
-fontOptionsEqual :: FontOptions -> FontOptions -> Render Bool
-fontOptionsSetAntialias :: FontOptions -> Antialias -> Render ()
-fontOptionsGetAntialias :: FontOptions -> Render Antialias
-fontOptionsSetSubpixelOrder :: FontOptions -> SubpixelOrder -> Render ()
-fontOptionsGetSubpixelOrder :: FontOptions -> Render SubpixelOrder
-fontOptionsSetHintStyle :: FontOptions -> HintStyle -> Render ()
-fontOptionsGetHintStyle :: FontOptions -> Render HintStyle
-fontOptionsSetHintMetrics :: FontOptions -> HintMetrics -> Render ()
-fontOptionsGetHintMetrics :: FontOptions -> Render HintMetrics
-withSimilarSurface :: Surface -> Content -> Int -> Int -> (Surface -> IO a) -> IO a
-renderWithSimilarSurface :: Content -> Int -> Int -> (Surface -> Render a) -> Render a
-surfaceGetFontOptions :: Surface -> Render FontOptions
-surfaceMarkDirty :: Surface -> Render ()
-surfaceMarkDirtyRectangle :: Surface -> Int -> Int -> Int -> Int -> Render ()
-surfaceSetDeviceOffset :: Surface -> Double -> Double -> Render ()
-withImageSurface :: Format -> Int -> Int -> (Surface -> IO a) -> IO a
-imageSurfaceGetWidth :: Surface -> Render Int
-imageSurfaceGetHeight :: Surface -> Render Int
-withImageSurfaceFromPNG :: FilePath -> (Surface -> IO a) -> IO a
-surfaceWriteToPNG :: Surface -> FilePath -> IO ()
-version :: Int
-versionString :: String
-data Matrix
-instance Eq Matrix
-instance Num Matrix
-instance Show Matrix
-instance Storable Matrix
-data Surface
-data Pattern
-data Status
-StatusSuccess :: Status
-StatusNoMemory :: Status
-StatusInvalidRestore :: Status
-StatusInvalidPopGroup :: Status
-StatusNoCurrentPoint :: Status
-StatusInvalidMatrix :: Status
-StatusInvalidStatus :: Status
-StatusNullPointer :: Status
-StatusInvalidString :: Status
-StatusInvalidPathData :: Status
-StatusReadError :: Status
-StatusWriteError :: Status
-StatusSurfaceFinished :: Status
-StatusSurfaceTypeMismatch :: Status
-StatusPatternTypeMismatch :: Status
-StatusInvalidContent :: Status
-StatusInvalidFormat :: Status
-StatusInvalidVisual :: Status
-StatusFileNotFound :: Status
-StatusInvalidDash :: Status
-instance Enum Status
-instance Eq Status
-data Operator
-OperatorClear :: Operator
-OperatorSource :: Operator
-OperatorOver :: Operator
-OperatorIn :: Operator
-OperatorOut :: Operator
-OperatorAtop :: Operator
-OperatorDest :: Operator
-OperatorDestOver :: Operator
-OperatorDestIn :: Operator
-OperatorDestOut :: Operator
-OperatorDestAtop :: Operator
-OperatorXor :: Operator
-OperatorAdd :: Operator
-OperatorSaturate :: Operator
-instance Enum Operator
-data Antialias
-AntialiasDefault :: Antialias
-AntialiasNone :: Antialias
-AntialiasGray :: Antialias
-AntialiasSubpixel :: Antialias
-instance Enum Antialias
-data FillRule
-FillRuleWinding :: FillRule
-FillRuleEvenOdd :: FillRule
-instance Enum FillRule
-data LineCap
-LineCapButt :: LineCap
-LineCapRound :: LineCap
-LineCapSquare :: LineCap
-instance Enum LineCap
-data LineJoin
-LineJoinMiter :: LineJoin
-LineJoinRound :: LineJoin
-LineJoinBevel :: LineJoin
-instance Enum LineJoin
-data ScaledFont
-data FontFace
-data Glyph
-data TextExtents
-TextExtents :: Double -> Double -> Double -> Double -> Double -> Double -> TextExtents
-textExtentsXbearing :: TextExtents -> Double
-textExtentsYbearing :: TextExtents -> Double
-textExtentsWidth :: TextExtents -> Double
-textExtentsHeight :: TextExtents -> Double
-textExtentsXadvance :: TextExtents -> Double
-textExtentsYadvance :: TextExtents -> Double
-instance Storable TextExtents
-data FontExtents
-FontExtents :: Double -> Double -> Double -> Double -> Double -> FontExtents
-fontExtentsAscent :: FontExtents -> Double
-fontExtentsDescent :: FontExtents -> Double
-fontExtentsHeight :: FontExtents -> Double
-fontExtentsMaxXadvance :: FontExtents -> Double
-fontExtentsMaxYadvance :: FontExtents -> Double
-instance Storable FontExtents
-data FontSlant
-FontSlantNormal :: FontSlant
-FontSlantItalic :: FontSlant
-FontSlantOblique :: FontSlant
-instance Enum FontSlant
-data FontWeight
-FontWeightNormal :: FontWeight
-FontWeightBold :: FontWeight
-instance Enum FontWeight
-data SubpixelOrder
-SubpixelOrderDefault :: SubpixelOrder
-SubpixelOrderRgb :: SubpixelOrder
-SubpixelOrderBgr :: SubpixelOrder
-SubpixelOrderVrgb :: SubpixelOrder
-SubpixelOrderVbgr :: SubpixelOrder
-instance Enum SubpixelOrder
-data HintStyle
-HintStyleDefault :: HintStyle
-HintStyleNone :: HintStyle
-HintStyleSlight :: HintStyle
-HintStyleMedium :: HintStyle
-HintStyleFull :: HintStyle
-instance Enum HintStyle
-data HintMetrics
-HintMetricsDefault :: HintMetrics
-HintMetricsOff :: HintMetrics
-HintMetricsOn :: HintMetrics
-instance Enum HintMetrics
-data FontOptions
-data Path
-data Content
-ContentColor :: Content
-ContentAlpha :: Content
-ContentColorAlpha :: Content
-instance Enum Content
-data Format
-FormatARGB32 :: Format
-FormatRGB24 :: Format
-FormatA8 :: Format
-FormatA1 :: Format
-instance Enum Format
-data Extend
-ExtendNone :: Extend
-ExtendRepeat :: Extend
-ExtendReflect :: Extend
-instance Enum Extend
-data Filter
-FilterFast :: Filter
-FilterGood :: Filter
-FilterBest :: Filter
-FilterNearest :: Filter
-FilterBilinear :: Filter
-FilterGaussian :: Filter
-instance Enum Filter
-
-module Graphics.UI.Gtk.Cairo
-cairoFontMapNew :: IO FontMap
-cairoFontMapSetResolution :: Double -> FontMap -> IO ()
-cairoFontMapGetResolution :: FontMap -> IO Double
-cairoCreateContext :: Maybe FontMap -> IO PangoContext
-cairoContextSetResolution :: PangoContext -> Double -> IO ()
-cairoContextGetResolution :: PangoContext -> IO Double
-cairoContextSetFontOptions :: PangoContext -> FontOptions -> IO ()
-cairoContextGetFontOptions :: PangoContext -> IO FontOptions
-renderWithDrawable :: DrawableClass drawable => drawable -> Render a -> IO a
-setSourceColor :: Color -> Render ()
-setSourcePixbuf :: Pixbuf -> Double -> Double -> Render ()
-region :: Region -> Render ()
-updateContext :: PangoContext -> Render ()
-createLayout :: String -> Render PangoLayout
-updateLayout :: PangoLayout -> Render ()
-showGlyphString :: GlyphItem -> Render ()
-showLayoutLine :: LayoutLine -> Render ()
-showLayout :: PangoLayout -> Render ()
-glyphStringPath :: GlyphItem -> Render ()
-layoutLinePath :: LayoutLine -> Render ()
-layoutPath :: PangoLayout -> Render ()
-
-module Graphics.UI.Gtk
-
-module Graphics.UI.Gtk.Mogul.NewWidget
-newTextBuffer :: Maybe TextTagTable -> IO TextBuffer
-newLabel :: Maybe String -> IO Label
-newNamedLabel :: WidgetName -> Maybe String -> IO Label
-newAccelLabel :: String -> IO AccelLabel
-newNamedAccelLabel :: WidgetName -> String -> IO AccelLabel
-newArrow :: ArrowType -> ShadowType -> IO Arrow
-newNamedArrow :: WidgetName -> ArrowType -> ShadowType -> IO Arrow
-newImageFromFile :: FilePath -> IO Image
-newNamedImageFromFile :: WidgetName -> FilePath -> IO Image
-newAlignment :: Float -> Float -> Float -> Float -> IO Alignment
-newNamedAlignment :: WidgetName -> Float -> Float -> Float -> Float -> IO Alignment
-newFrame :: IO Frame
-newNamedFrame :: WidgetName -> IO Frame
-newAspectFrame :: Float -> Float -> Maybe Float -> IO AspectFrame
-newNamedAspectFrame :: WidgetName -> Float -> Float -> Maybe Float -> IO AspectFrame
-newButton :: IO Button
-newNamedButton :: WidgetName -> IO Button
-newButtonWithLabel :: String -> IO Button
-newNamedButtonWithLabel :: WidgetName -> String -> IO Button
-newButtonWithMnemonic :: String -> IO Button
-newNamedButtonWithMnemonic :: WidgetName -> String -> IO Button
-newButtonFromStock :: String -> IO Button
-newNamedButtonFromStock :: WidgetName -> String -> IO Button
-newToggleButton :: IO ToggleButton
-newNamedToggleButton :: WidgetName -> IO ToggleButton
-newToggleButtonWithLabel :: String -> IO ToggleButton
-newNamedToggleButtonWithLabel :: WidgetName -> String -> IO ToggleButton
-newCheckButton :: IO CheckButton
-newNamedCheckButton :: WidgetName -> IO CheckButton
-newCheckButtonWithLabel :: String -> IO CheckButton
-newNamedCheckButtonWithLabel :: WidgetName -> String -> IO CheckButton
-newCheckButtonWithMnemonic :: String -> IO CheckButton
-newNamedCheckButtonWithMnemonic :: WidgetName -> String -> IO CheckButton
-newRadioButton :: IO RadioButton
-newNamedRadioButton :: WidgetName -> IO RadioButton
-newRadioButtonWithLabel :: String -> IO RadioButton
-newNamedRadioButtonWithLabel :: WidgetName -> String -> IO RadioButton
-newRadioButtonJoinGroup :: RadioButton -> IO RadioButton
-newNamedRadioButtonJoinGroup :: WidgetName -> RadioButton -> IO RadioButton
-newRadioButtonJoinGroupWithLabel :: RadioButton -> String -> IO RadioButton
-newNamedRadioButtonJoinGroupWithLabel :: WidgetName -> RadioButton -> String -> IO RadioButton
-newOptionMenu :: IO OptionMenu
-newNamedOptionMenu :: WidgetName -> IO OptionMenu
-newMenuItem :: IO MenuItem
-newNamedMenuItem :: WidgetName -> IO MenuItem
-newMenuItemWithLabel :: String -> IO MenuItem
-newNamedMenuItemWithLabel :: WidgetName -> String -> IO MenuItem
-newCheckMenuItem :: IO CheckMenuItem
-newNamedCheckMenuItem :: WidgetName -> IO CheckMenuItem
-newCheckMenuItemWithLabel :: String -> IO CheckMenuItem
-newNamedCheckMenuItemWithLabel :: WidgetName -> String -> IO CheckMenuItem
-newRadioMenuItem :: IO RadioMenuItem
-newNamedRadioMenuItem :: WidgetName -> IO RadioMenuItem
-newRadioMenuItemWithLabel :: String -> IO RadioMenuItem
-newNamedRadioMenuItemWithLabel :: WidgetName -> String -> IO RadioMenuItem
-newRadioMenuItemJoinGroup :: RadioMenuItem -> IO RadioMenuItem
-newNamedRadioMenuItemJoinGroup :: WidgetName -> RadioMenuItem -> IO RadioMenuItem
-newRadioMenuItemJoinGroupWithLabel :: RadioMenuItem -> String -> IO RadioMenuItem
-newNamedRadioMenuItemJoinGroupWithLabel :: WidgetName -> RadioMenuItem -> String -> IO RadioMenuItem
-newTearoffMenuItem :: IO TearoffMenuItem
-newNamedTearoffMenuItem :: WidgetName -> IO TearoffMenuItem
-newWindow :: IO Window
-newNamedWindow :: WidgetName -> IO Window
-newDialog :: IO Dialog
-newNamedDialog :: WidgetName -> IO Dialog
-newEventBox :: IO EventBox
-newNamedEventBox :: WidgetName -> IO EventBox
-newHandleBox :: IO HandleBox
-newNamedHandleBox :: WidgetName -> IO HandleBox
-newScrolledWindow :: Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow
-newNamedScrolledWindow :: WidgetName -> Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow
-newViewport :: Adjustment -> Adjustment -> IO Viewport
-newNamedViewport :: WidgetName -> Adjustment -> Adjustment -> IO Viewport
-newVBox :: Bool -> Int -> IO VBox
-newNamedVBox :: WidgetName -> Bool -> Int -> IO VBox
-newHBox :: Bool -> Int -> IO HBox
-newNamedHBox :: WidgetName -> Bool -> Int -> IO HBox
-newCombo :: IO Combo
-newNamedCombo :: WidgetName -> IO Combo
-newStatusbar :: IO Statusbar
-newNamedStatusbar :: WidgetName -> IO Statusbar
-newHPaned :: IO HPaned
-newNamedHPaned :: WidgetName -> IO HPaned
-newVPaned :: IO VPaned
-newNamedVPaned :: WidgetName -> IO VPaned
-newLayout :: Maybe Adjustment -> Maybe Adjustment -> IO Layout
-newNamedLayout :: WidgetName -> Maybe Adjustment -> Maybe Adjustment -> IO Layout
-newMenu :: IO Menu
-newNamedMenu :: WidgetName -> IO Menu
-newMenuBar :: IO MenuBar
-newNamedMenuBar :: WidgetName -> IO MenuBar
-newNotebook :: IO Notebook
-newNamedNotebook :: WidgetName -> IO Notebook
-newTable :: Int -> Int -> Bool -> IO Table
-newNamedTable :: WidgetName -> Int -> Int -> Bool -> IO Table
-newTextView :: IO TextView
-newNamedTextView :: WidgetName -> IO TextView
-newToolbar :: IO Toolbar
-newNamedToolbar :: WidgetName -> IO Toolbar
-newCalendar :: IO Calendar
-newNamedCalendar :: WidgetName -> IO Calendar
-newEntry :: IO Entry
-newNamedEntry :: WidgetName -> IO Entry
-newSpinButton :: Adjustment -> Double -> Int -> IO SpinButton
-newNamedSpinButton :: String -> Adjustment -> Double -> Int -> IO SpinButton
-newSpinButtonWithRange :: Double -> Double -> Double -> IO SpinButton
-newNamedSpinButtonWithRange :: WidgetName -> Double -> Double -> Double -> IO SpinButton
-newHScale :: Adjustment -> IO HScale
-newNamedHScale :: WidgetName -> Adjustment -> IO HScale
-newVScale :: Adjustment -> IO VScale
-newNamedVScale :: WidgetName -> Adjustment -> IO VScale
-newHScrollbar :: Adjustment -> IO HScrollbar
-newNamedHScrollbar :: WidgetName -> Adjustment -> IO HScrollbar
-newVScrollbar :: Adjustment -> IO VScrollbar
-newNamedVScrollbar :: WidgetName -> Adjustment -> IO VScrollbar
-newHSeparator :: IO HSeparator
-newNamedHSeparator :: WidgetName -> IO HSeparator
-newVSeparator :: IO VSeparator
-newNamedVSeparator :: WidgetName -> IO VSeparator
-newProgressBar :: IO ProgressBar
-newNamedProgressBar :: WidgetName -> IO ProgressBar
-newAdjustment :: Double -> Double -> Double -> Double -> Double -> Double -> IO Adjustment
-newTooltips :: IO Tooltips
-newTreeView :: TreeModelClass tm => tm -> IO TreeView
-newNamedTreeView :: TreeModelClass tm => WidgetName -> tm -> IO TreeView
-newTreeViewWithModel :: TreeModelClass tm => tm -> IO TreeView
-newNamedTreeViewWithModel :: TreeModelClass tm => WidgetName -> tm -> IO TreeView
-newTreeViewColumn :: IO TreeViewColumn
-newIconFactory :: IO IconFactory
-
-module Graphics.UI.Gtk.Mogul.MDialog
-assureDialog :: String -> (Dialog -> IO ()) -> (Dialog -> IO ()) -> IO ()
-
-module Graphics.UI.Gtk.Mogul.TreeList
-data ListSkel
-emptyListSkel :: IO ListSkel
-listSkelAddAttribute :: CellRendererClass cr => ListSkel -> Attribute cr argTy -> IO (Association cr, TreeIter -> IO argTy, TreeIter -> argTy -> IO ())
-newListStore :: ListSkel -> IO ListStore
-data TreeSkel
-emptyTreeSkel :: IO TreeSkel
-treeSkelAddAttribute :: CellRendererClass r => TreeSkel -> Attribute r argTy -> IO (Association r, TreeIter -> IO argTy, TreeIter -> argTy -> IO ())
-newTreeStore :: TreeSkel -> IO TreeStore
-data Association cr
-data Renderer cr
-treeViewColumnNewText :: TreeViewColumn -> Bool -> Bool -> IO (Renderer CellRendererText)
-treeViewColumnNewPixbuf :: TreeViewColumn -> Bool -> Bool -> IO (Renderer CellRendererPixbuf)
-treeViewColumnNewToggle :: TreeViewColumn -> Bool -> Bool -> IO (Renderer CellRendererToggle)
-treeViewColumnAssociate :: CellRendererClass r => Renderer r -> [Association r] -> IO ()
-cellRendererSetAttribute :: CellRendererClass cr => Renderer cr -> Attribute cr val -> val -> IO ()
-cellRendererGetAttribute :: CellRendererClass cr => Renderer cr -> Attribute cr val -> IO val
-onEdited :: TreeModelClass tm => Renderer CellRendererText -> tm -> (TreeIter -> String -> IO ()) -> IO (ConnectId CellRendererText)
-afterEdited :: TreeModelClass tm => Renderer CellRendererText -> tm -> (TreeIter -> String -> IO ()) -> IO (ConnectId CellRendererText)
-
-module Graphics.UI.Gtk.Mogul
-
rmfile ./src/Web/res/gtk.txt
hunk ./src/Web/res/noresults.inc 1
-
- Your search returned no results:
-
- Make sure you are using the search engine properly, it only searches for Haskell functions
- Try a smaller substring, for example, if you searched for mapConcat , try searching for either map or concat individually.
-
-
rmfile ./src/Web/res/noresults.inc
hunk ./src/Web/res/prefix.inc 1
-
-
-
-
- $ - Hoogle
-
-
-
-
-
-
-
-
-
-
-
-
rmfile ./src/Web/res/prefix.inc
hunk ./src/Web/res/prefix_gtk.inc 1
-
-
-
-
- $ - Hoogle
-
-
-
-
-
-
-
-
-
-
-
-
rmfile ./src/Web/res/prefix_gtk.inc
hunk ./src/Web/res/suffix.inc 1
-
-
-
-
rmfile ./src/Web/res/suffix.inc
rmdir ./src/Web/res
}