{-# LANGUAGE OverloadedStrings #-}
-- | Build time configuration used during code generation.
module GI.Vte.Config ( overrides ) where

import qualified Data.Text as T
import Data.Text (Text)

-- | Overrides used when generating these bindings.
overrides :: Text
overrides :: Text
overrides = [Text] -> Text
T.unlines
 [ Text
"namespace Vte"
 , Text
""
 , Text
"# This function is deprecated, does nothing, and the introspection"
 , Text
"# data is wrong."
 , Text
"ignore Terminal.event_check_gregex_simple"
 , Text
""
 , Text
"# Wrong introspection data."
 , Text
"ignore Terminal.event_check_regex_simple"
 , Text
""
 , Text
"# The return value is nullable, but it is not properly annotated as such"
 , Text
"# https://github.com/haskell-gi/haskell-gi/issues/179"
 , Text
"set-attr Vte/Terminal/get_current_directory_uri/@return-value nullable 1"
 , Text
""
 , Text
"# The return value is nullable, but it is not properly annotated as such"
 , Text
"# https://github.com/haskell-gi/haskell-gi/issues/185"
 , Text
"set-attr Vte/Terminal/get_window_title/@return-value nullable 1"
 , Text
""
 , Text
"# The return value is nullable, but it is not properly annotated as such"
 , Text
"set-attr Vte/Terminal/match_check_event/@return-value nullable 1"
 , Text
""
 , Text
"# The return value is nullable, but it is not properly annotated as such"
 , Text
"set-attr Vte/Terminal/hyperlink_check_event/@return-value nullable 1"
 , Text
""
 , Text
"# The introspection data for vte_terminal_spawn_async and"
 , Text
"# vte_pty_spawn_async is wrong"
 , Text
""
 , Text
"set-attr Vte/Terminal/spawn_async/@parameters/child_setup scope async"
 , Text
"delete-attr Vte/Terminal/spawn_async/@parameters/child_setup_data scope"
 , Text
"delete-attr Vte/Terminal/spawn_async/@parameters/child_setup_data closure"
 , Text
"delete-attr Vte/Terminal/spawn_async/@parameters/child_setup_data_destroy scope"
 , Text
"delete-attr Vte/Terminal/spawn_async/@parameters/child_setup_data_destroy destroy"
 , Text
"delete-attr Vte/Terminal/spawn_async/@parameters/user_data closure"
 , Text
""
 , Text
"set-attr Vte/Pty/spawn_async/@parameters/child_setup scope async"
 , Text
"delete-attr Vte/Pty/spawn_async/@parameters/child_setup_data scope"
 , Text
"delete-attr Vte/Pty/spawn_async/@parameters/child_setup_data closure"
 , Text
"delete-attr Vte/Pty/spawn_async/@parameters/child_setup_data_destroy scope"
 , Text
"delete-attr Vte/Pty/spawn_async/@parameters/child_setup_data_destroy destroy"
 , Text
"delete-attr Vte/Pty/spawn_async/@parameters/user_data closure"]