#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Enums
(
BookmarkFileError(..) ,
catchBookmarkFileError ,
handleBookmarkFileError ,
ChecksumType(..) ,
ConvertError(..) ,
catchConvertError ,
handleConvertError ,
DateDMY(..) ,
DateMonth(..) ,
DateWeekday(..) ,
ErrorType(..) ,
FileError(..) ,
catchFileError ,
handleFileError ,
IOChannelError(..) ,
catchIOChannelError ,
handleIOChannelError ,
IOError(..) ,
IOStatus(..) ,
KeyFileError(..) ,
catchKeyFileError ,
handleKeyFileError ,
LogWriterOutput(..) ,
MarkupError(..) ,
catchMarkupError ,
handleMarkupError ,
NormalizeMode(..) ,
NumberParserError(..) ,
catchNumberParserError ,
handleNumberParserError ,
OnceStatus(..) ,
OptionArg(..) ,
OptionError(..) ,
catchOptionError ,
handleOptionError ,
RegexError(..) ,
catchRegexError ,
handleRegexError ,
SeekType(..) ,
ShellError(..) ,
catchShellError ,
handleShellError ,
SliceConfig(..) ,
SpawnError(..) ,
catchSpawnError ,
handleSpawnError ,
TestFileType(..) ,
TestLogType(..) ,
TestResult(..) ,
ThreadError(..) ,
catchThreadError ,
handleThreadError ,
TimeType(..) ,
TokenType(..) ,
TraverseType(..) ,
UnicodeBreakType(..) ,
UnicodeScript(..) ,
UnicodeType(..) ,
UserDirectory(..) ,
VariantClass(..) ,
VariantParseError(..) ,
catchVariantParseError ,
handleVariantParseError ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
data VariantParseError =
VariantParseErrorFailed
| VariantParseErrorBasicTypeExpected
| VariantParseErrorCannotInferType
| VariantParseErrorDefiniteTypeExpected
| VariantParseErrorInputNotAtEnd
| VariantParseErrorInvalidCharacter
| VariantParseErrorInvalidFormatString
| VariantParseErrorInvalidObjectPath
| VariantParseErrorInvalidSignature
| VariantParseErrorInvalidTypeString
| VariantParseErrorNoCommonType
| VariantParseErrorNumberOutOfRange
| VariantParseErrorNumberTooBig
| VariantParseErrorTypeError
| VariantParseErrorUnexpectedToken
| VariantParseErrorUnknownKeyword
| VariantParseErrorUnterminatedStringConstant
| VariantParseErrorValueExpected
| AnotherVariantParseError Int
deriving (Int -> VariantParseError -> ShowS
[VariantParseError] -> ShowS
VariantParseError -> String
(Int -> VariantParseError -> ShowS)
-> (VariantParseError -> String)
-> ([VariantParseError] -> ShowS)
-> Show VariantParseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VariantParseError] -> ShowS
$cshowList :: [VariantParseError] -> ShowS
show :: VariantParseError -> String
$cshow :: VariantParseError -> String
showsPrec :: Int -> VariantParseError -> ShowS
$cshowsPrec :: Int -> VariantParseError -> ShowS
Show, VariantParseError -> VariantParseError -> Bool
(VariantParseError -> VariantParseError -> Bool)
-> (VariantParseError -> VariantParseError -> Bool)
-> Eq VariantParseError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariantParseError -> VariantParseError -> Bool
$c/= :: VariantParseError -> VariantParseError -> Bool
== :: VariantParseError -> VariantParseError -> Bool
$c== :: VariantParseError -> VariantParseError -> Bool
Eq)
instance P.Enum VariantParseError where
fromEnum :: VariantParseError -> Int
fromEnum VariantParseErrorFailed = 0
fromEnum VariantParseErrorBasicTypeExpected = 1
fromEnum VariantParseErrorCannotInferType = 2
fromEnum VariantParseErrorDefiniteTypeExpected = 3
fromEnum VariantParseErrorInputNotAtEnd = 4
fromEnum VariantParseErrorInvalidCharacter = 5
fromEnum VariantParseErrorInvalidFormatString = 6
fromEnum VariantParseErrorInvalidObjectPath = 7
fromEnum VariantParseErrorInvalidSignature = 8
fromEnum VariantParseErrorInvalidTypeString = 9
fromEnum VariantParseErrorNoCommonType = 10
fromEnum VariantParseErrorNumberOutOfRange = 11
fromEnum VariantParseErrorNumberTooBig = 12
fromEnum VariantParseErrorTypeError = 13
fromEnum VariantParseErrorUnexpectedToken = 14
fromEnum VariantParseErrorUnknownKeyword = 15
fromEnum VariantParseErrorUnterminatedStringConstant = 16
fromEnum VariantParseErrorValueExpected = 17
fromEnum (AnotherVariantParseError k :: Int
k) = Int
k
toEnum :: Int -> VariantParseError
toEnum 0 = VariantParseError
VariantParseErrorFailed
toEnum 1 = VariantParseError
VariantParseErrorBasicTypeExpected
toEnum 2 = VariantParseError
VariantParseErrorCannotInferType
toEnum 3 = VariantParseError
VariantParseErrorDefiniteTypeExpected
toEnum 4 = VariantParseError
VariantParseErrorInputNotAtEnd
toEnum 5 = VariantParseError
VariantParseErrorInvalidCharacter
toEnum 6 = VariantParseError
VariantParseErrorInvalidFormatString
toEnum 7 = VariantParseError
VariantParseErrorInvalidObjectPath
toEnum 8 = VariantParseError
VariantParseErrorInvalidSignature
toEnum 9 = VariantParseError
VariantParseErrorInvalidTypeString
toEnum 10 = VariantParseError
VariantParseErrorNoCommonType
toEnum 11 = VariantParseError
VariantParseErrorNumberOutOfRange
toEnum 12 = VariantParseError
VariantParseErrorNumberTooBig
toEnum 13 = VariantParseError
VariantParseErrorTypeError
toEnum 14 = VariantParseError
VariantParseErrorUnexpectedToken
toEnum 15 = VariantParseError
VariantParseErrorUnknownKeyword
toEnum 16 = VariantParseError
VariantParseErrorUnterminatedStringConstant
toEnum 17 = VariantParseError
VariantParseErrorValueExpected
toEnum k :: Int
k = Int -> VariantParseError
AnotherVariantParseError Int
k
instance P.Ord VariantParseError where
compare :: VariantParseError -> VariantParseError -> Ordering
compare a :: VariantParseError
a b :: VariantParseError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (VariantParseError -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantParseError
a) (VariantParseError -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantParseError
b)
instance GErrorClass VariantParseError where
gerrorClassDomain :: VariantParseError -> Text
gerrorClassDomain _ = "g-variant-parse-error-quark"
catchVariantParseError ::
IO a ->
(VariantParseError -> GErrorMessage -> IO a) ->
IO a
catchVariantParseError :: IO a -> (VariantParseError -> Text -> IO a) -> IO a
catchVariantParseError = IO a -> (VariantParseError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleVariantParseError ::
(VariantParseError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleVariantParseError :: (VariantParseError -> Text -> IO a) -> IO a -> IO a
handleVariantParseError = (VariantParseError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data VariantClass =
VariantClassBoolean
| VariantClassByte
| VariantClassInt16
| VariantClassUint16
| VariantClassInt32
| VariantClassUint32
| VariantClassInt64
| VariantClassUint64
| VariantClassHandle
| VariantClassDouble
| VariantClassString
| VariantClassObjectPath
| VariantClassSignature
| VariantClassVariant
| VariantClassMaybe
| VariantClassArray
| VariantClassTuple
| VariantClassDictEntry
| AnotherVariantClass Int
deriving (Int -> VariantClass -> ShowS
[VariantClass] -> ShowS
VariantClass -> String
(Int -> VariantClass -> ShowS)
-> (VariantClass -> String)
-> ([VariantClass] -> ShowS)
-> Show VariantClass
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VariantClass] -> ShowS
$cshowList :: [VariantClass] -> ShowS
show :: VariantClass -> String
$cshow :: VariantClass -> String
showsPrec :: Int -> VariantClass -> ShowS
$cshowsPrec :: Int -> VariantClass -> ShowS
Show, VariantClass -> VariantClass -> Bool
(VariantClass -> VariantClass -> Bool)
-> (VariantClass -> VariantClass -> Bool) -> Eq VariantClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariantClass -> VariantClass -> Bool
$c/= :: VariantClass -> VariantClass -> Bool
== :: VariantClass -> VariantClass -> Bool
$c== :: VariantClass -> VariantClass -> Bool
Eq)
instance P.Enum VariantClass where
fromEnum :: VariantClass -> Int
fromEnum VariantClassBoolean = 98
fromEnum VariantClassByte = 121
fromEnum VariantClassInt16 = 110
fromEnum VariantClassUint16 = 113
fromEnum VariantClassInt32 = 105
fromEnum VariantClassUint32 = 117
fromEnum VariantClassInt64 = 120
fromEnum VariantClassUint64 = 116
fromEnum VariantClassHandle = 104
fromEnum VariantClassDouble = 100
fromEnum VariantClassString = 115
fromEnum VariantClassObjectPath = 111
fromEnum VariantClassSignature = 103
fromEnum VariantClassVariant = 118
fromEnum VariantClassMaybe = 109
fromEnum VariantClassArray = 97
fromEnum VariantClassTuple = 40
fromEnum VariantClassDictEntry = 123
fromEnum (AnotherVariantClass k :: Int
k) = Int
k
toEnum :: Int -> VariantClass
toEnum 98 = VariantClass
VariantClassBoolean
toEnum 121 = VariantClass
VariantClassByte
toEnum 110 = VariantClass
VariantClassInt16
toEnum 113 = VariantClass
VariantClassUint16
toEnum 105 = VariantClass
VariantClassInt32
toEnum 117 = VariantClass
VariantClassUint32
toEnum 120 = VariantClass
VariantClassInt64
toEnum 116 = VariantClass
VariantClassUint64
toEnum 104 = VariantClass
VariantClassHandle
toEnum 100 = VariantClass
VariantClassDouble
toEnum 115 = VariantClass
VariantClassString
toEnum 111 = VariantClass
VariantClassObjectPath
toEnum 103 = VariantClass
VariantClassSignature
toEnum 118 = VariantClass
VariantClassVariant
toEnum 109 = VariantClass
VariantClassMaybe
toEnum 97 = VariantClass
VariantClassArray
toEnum 40 = VariantClass
VariantClassTuple
toEnum 123 = VariantClass
VariantClassDictEntry
toEnum k :: Int
k = Int -> VariantClass
AnotherVariantClass Int
k
instance P.Ord VariantClass where
compare :: VariantClass -> VariantClass -> Ordering
compare a :: VariantClass
a b :: VariantClass
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (VariantClass -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantClass
a) (VariantClass -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantClass
b)
data UserDirectory =
UserDirectoryDirectoryDesktop
| UserDirectoryDirectoryDocuments
| UserDirectoryDirectoryDownload
| UserDirectoryDirectoryMusic
| UserDirectoryDirectoryPictures
| UserDirectoryDirectoryPublicShare
| UserDirectoryDirectoryTemplates
| UserDirectoryDirectoryVideos
| UserDirectoryNDirectories
| AnotherUserDirectory Int
deriving (Int -> UserDirectory -> ShowS
[UserDirectory] -> ShowS
UserDirectory -> String
(Int -> UserDirectory -> ShowS)
-> (UserDirectory -> String)
-> ([UserDirectory] -> ShowS)
-> Show UserDirectory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserDirectory] -> ShowS
$cshowList :: [UserDirectory] -> ShowS
show :: UserDirectory -> String
$cshow :: UserDirectory -> String
showsPrec :: Int -> UserDirectory -> ShowS
$cshowsPrec :: Int -> UserDirectory -> ShowS
Show, UserDirectory -> UserDirectory -> Bool
(UserDirectory -> UserDirectory -> Bool)
-> (UserDirectory -> UserDirectory -> Bool) -> Eq UserDirectory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserDirectory -> UserDirectory -> Bool
$c/= :: UserDirectory -> UserDirectory -> Bool
== :: UserDirectory -> UserDirectory -> Bool
$c== :: UserDirectory -> UserDirectory -> Bool
Eq)
instance P.Enum UserDirectory where
fromEnum :: UserDirectory -> Int
fromEnum UserDirectoryDirectoryDesktop = 0
fromEnum UserDirectoryDirectoryDocuments = 1
fromEnum UserDirectoryDirectoryDownload = 2
fromEnum UserDirectoryDirectoryMusic = 3
fromEnum UserDirectoryDirectoryPictures = 4
fromEnum UserDirectoryDirectoryPublicShare = 5
fromEnum UserDirectoryDirectoryTemplates = 6
fromEnum UserDirectoryDirectoryVideos = 7
fromEnum UserDirectoryNDirectories = 8
fromEnum (AnotherUserDirectory k :: Int
k) = Int
k
toEnum :: Int -> UserDirectory
toEnum 0 = UserDirectory
UserDirectoryDirectoryDesktop
toEnum 1 = UserDirectory
UserDirectoryDirectoryDocuments
toEnum 2 = UserDirectory
UserDirectoryDirectoryDownload
toEnum 3 = UserDirectory
UserDirectoryDirectoryMusic
toEnum 4 = UserDirectory
UserDirectoryDirectoryPictures
toEnum 5 = UserDirectory
UserDirectoryDirectoryPublicShare
toEnum 6 = UserDirectory
UserDirectoryDirectoryTemplates
toEnum 7 = UserDirectory
UserDirectoryDirectoryVideos
toEnum 8 = UserDirectory
UserDirectoryNDirectories
toEnum k :: Int
k = Int -> UserDirectory
AnotherUserDirectory Int
k
instance P.Ord UserDirectory where
compare :: UserDirectory -> UserDirectory -> Ordering
compare a :: UserDirectory
a b :: UserDirectory
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UserDirectory -> Int
forall a. Enum a => a -> Int
P.fromEnum UserDirectory
a) (UserDirectory -> Int
forall a. Enum a => a -> Int
P.fromEnum UserDirectory
b)
data UnicodeType =
UnicodeTypeControl
| UnicodeTypeFormat
| UnicodeTypeUnassigned
| UnicodeTypePrivateUse
| UnicodeTypeSurrogate
| UnicodeTypeLowercaseLetter
| UnicodeTypeModifierLetter
| UnicodeTypeOtherLetter
| UnicodeTypeTitlecaseLetter
| UnicodeTypeUppercaseLetter
| UnicodeTypeSpacingMark
| UnicodeTypeEnclosingMark
| UnicodeTypeNonSpacingMark
| UnicodeTypeDecimalNumber
| UnicodeTypeLetterNumber
| UnicodeTypeOtherNumber
| UnicodeTypeConnectPunctuation
| UnicodeTypeDashPunctuation
| UnicodeTypeClosePunctuation
| UnicodeTypeFinalPunctuation
| UnicodeTypeInitialPunctuation
| UnicodeTypeOtherPunctuation
| UnicodeTypeOpenPunctuation
| UnicodeTypeCurrencySymbol
| UnicodeTypeModifierSymbol
| UnicodeTypeMathSymbol
| UnicodeTypeOtherSymbol
| UnicodeTypeLineSeparator
| UnicodeTypeParagraphSeparator
| UnicodeTypeSpaceSeparator
| AnotherUnicodeType Int
deriving (Int -> UnicodeType -> ShowS
[UnicodeType] -> ShowS
UnicodeType -> String
(Int -> UnicodeType -> ShowS)
-> (UnicodeType -> String)
-> ([UnicodeType] -> ShowS)
-> Show UnicodeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnicodeType] -> ShowS
$cshowList :: [UnicodeType] -> ShowS
show :: UnicodeType -> String
$cshow :: UnicodeType -> String
showsPrec :: Int -> UnicodeType -> ShowS
$cshowsPrec :: Int -> UnicodeType -> ShowS
Show, UnicodeType -> UnicodeType -> Bool
(UnicodeType -> UnicodeType -> Bool)
-> (UnicodeType -> UnicodeType -> Bool) -> Eq UnicodeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnicodeType -> UnicodeType -> Bool
$c/= :: UnicodeType -> UnicodeType -> Bool
== :: UnicodeType -> UnicodeType -> Bool
$c== :: UnicodeType -> UnicodeType -> Bool
Eq)
instance P.Enum UnicodeType where
fromEnum :: UnicodeType -> Int
fromEnum UnicodeTypeControl = 0
fromEnum UnicodeTypeFormat = 1
fromEnum UnicodeTypeUnassigned = 2
fromEnum UnicodeTypePrivateUse = 3
fromEnum UnicodeTypeSurrogate = 4
fromEnum UnicodeTypeLowercaseLetter = 5
fromEnum UnicodeTypeModifierLetter = 6
fromEnum UnicodeTypeOtherLetter = 7
fromEnum UnicodeTypeTitlecaseLetter = 8
fromEnum UnicodeTypeUppercaseLetter = 9
fromEnum UnicodeTypeSpacingMark = 10
fromEnum UnicodeTypeEnclosingMark = 11
fromEnum UnicodeTypeNonSpacingMark = 12
fromEnum UnicodeTypeDecimalNumber = 13
fromEnum UnicodeTypeLetterNumber = 14
fromEnum UnicodeTypeOtherNumber = 15
fromEnum UnicodeTypeConnectPunctuation = 16
fromEnum UnicodeTypeDashPunctuation = 17
fromEnum UnicodeTypeClosePunctuation = 18
fromEnum UnicodeTypeFinalPunctuation = 19
fromEnum UnicodeTypeInitialPunctuation = 20
fromEnum UnicodeTypeOtherPunctuation = 21
fromEnum UnicodeTypeOpenPunctuation = 22
fromEnum UnicodeTypeCurrencySymbol = 23
fromEnum UnicodeTypeModifierSymbol = 24
fromEnum UnicodeTypeMathSymbol = 25
fromEnum UnicodeTypeOtherSymbol = 26
fromEnum UnicodeTypeLineSeparator = 27
fromEnum UnicodeTypeParagraphSeparator = 28
fromEnum UnicodeTypeSpaceSeparator = 29
fromEnum (AnotherUnicodeType k :: Int
k) = Int
k
toEnum :: Int -> UnicodeType
toEnum 0 = UnicodeType
UnicodeTypeControl
toEnum 1 = UnicodeType
UnicodeTypeFormat
toEnum 2 = UnicodeType
UnicodeTypeUnassigned
toEnum 3 = UnicodeType
UnicodeTypePrivateUse
toEnum 4 = UnicodeType
UnicodeTypeSurrogate
toEnum 5 = UnicodeType
UnicodeTypeLowercaseLetter
toEnum 6 = UnicodeType
UnicodeTypeModifierLetter
toEnum 7 = UnicodeType
UnicodeTypeOtherLetter
toEnum 8 = UnicodeType
UnicodeTypeTitlecaseLetter
toEnum 9 = UnicodeType
UnicodeTypeUppercaseLetter
toEnum 10 = UnicodeType
UnicodeTypeSpacingMark
toEnum 11 = UnicodeType
UnicodeTypeEnclosingMark
toEnum 12 = UnicodeType
UnicodeTypeNonSpacingMark
toEnum 13 = UnicodeType
UnicodeTypeDecimalNumber
toEnum 14 = UnicodeType
UnicodeTypeLetterNumber
toEnum 15 = UnicodeType
UnicodeTypeOtherNumber
toEnum 16 = UnicodeType
UnicodeTypeConnectPunctuation
toEnum 17 = UnicodeType
UnicodeTypeDashPunctuation
toEnum 18 = UnicodeType
UnicodeTypeClosePunctuation
toEnum 19 = UnicodeType
UnicodeTypeFinalPunctuation
toEnum 20 = UnicodeType
UnicodeTypeInitialPunctuation
toEnum 21 = UnicodeType
UnicodeTypeOtherPunctuation
toEnum 22 = UnicodeType
UnicodeTypeOpenPunctuation
toEnum 23 = UnicodeType
UnicodeTypeCurrencySymbol
toEnum 24 = UnicodeType
UnicodeTypeModifierSymbol
toEnum 25 = UnicodeType
UnicodeTypeMathSymbol
toEnum 26 = UnicodeType
UnicodeTypeOtherSymbol
toEnum 27 = UnicodeType
UnicodeTypeLineSeparator
toEnum 28 = UnicodeType
UnicodeTypeParagraphSeparator
toEnum 29 = UnicodeType
UnicodeTypeSpaceSeparator
toEnum k :: Int
k = Int -> UnicodeType
AnotherUnicodeType Int
k
instance P.Ord UnicodeType where
compare :: UnicodeType -> UnicodeType -> Ordering
compare a :: UnicodeType
a b :: UnicodeType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UnicodeType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeType
a) (UnicodeType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeType
b)
data UnicodeScript =
UnicodeScriptInvalidCode
| UnicodeScriptCommon
| UnicodeScriptInherited
| UnicodeScriptArabic
| UnicodeScriptArmenian
| UnicodeScriptBengali
| UnicodeScriptBopomofo
| UnicodeScriptCherokee
| UnicodeScriptCoptic
| UnicodeScriptCyrillic
| UnicodeScriptDeseret
| UnicodeScriptDevanagari
| UnicodeScriptEthiopic
| UnicodeScriptGeorgian
| UnicodeScriptGothic
| UnicodeScriptGreek
| UnicodeScriptGujarati
| UnicodeScriptGurmukhi
| UnicodeScriptHan
| UnicodeScriptHangul
| UnicodeScriptHebrew
| UnicodeScriptHiragana
| UnicodeScriptKannada
| UnicodeScriptKatakana
| UnicodeScriptKhmer
| UnicodeScriptLao
| UnicodeScriptLatin
| UnicodeScriptMalayalam
| UnicodeScriptMongolian
| UnicodeScriptMyanmar
| UnicodeScriptOgham
| UnicodeScriptOldItalic
| UnicodeScriptOriya
| UnicodeScriptRunic
| UnicodeScriptSinhala
| UnicodeScriptSyriac
| UnicodeScriptTamil
| UnicodeScriptTelugu
| UnicodeScriptThaana
| UnicodeScriptThai
| UnicodeScriptTibetan
| UnicodeScriptCanadianAboriginal
| UnicodeScriptYi
| UnicodeScriptTagalog
| UnicodeScriptHanunoo
| UnicodeScriptBuhid
| UnicodeScriptTagbanwa
| UnicodeScriptBraille
| UnicodeScriptCypriot
| UnicodeScriptLimbu
| UnicodeScriptOsmanya
| UnicodeScriptShavian
| UnicodeScriptLinearB
| UnicodeScriptTaiLe
| UnicodeScriptUgaritic
| UnicodeScriptNewTaiLue
| UnicodeScriptBuginese
| UnicodeScriptGlagolitic
| UnicodeScriptTifinagh
| UnicodeScriptSylotiNagri
| UnicodeScriptOldPersian
| UnicodeScriptKharoshthi
| UnicodeScriptUnknown
| UnicodeScriptBalinese
| UnicodeScriptCuneiform
| UnicodeScriptPhoenician
| UnicodeScriptPhagsPa
| UnicodeScriptNko
| UnicodeScriptKayahLi
| UnicodeScriptLepcha
| UnicodeScriptRejang
| UnicodeScriptSundanese
| UnicodeScriptSaurashtra
| UnicodeScriptCham
| UnicodeScriptOlChiki
| UnicodeScriptVai
| UnicodeScriptCarian
| UnicodeScriptLycian
| UnicodeScriptLydian
| UnicodeScriptAvestan
| UnicodeScriptBamum
| UnicodeScriptEgyptianHieroglyphs
| UnicodeScriptImperialAramaic
| UnicodeScriptInscriptionalPahlavi
| UnicodeScriptInscriptionalParthian
| UnicodeScriptJavanese
| UnicodeScriptKaithi
| UnicodeScriptLisu
| UnicodeScriptMeeteiMayek
| UnicodeScriptOldSouthArabian
| UnicodeScriptOldTurkic
| UnicodeScriptSamaritan
| UnicodeScriptTaiTham
| UnicodeScriptTaiViet
| UnicodeScriptBatak
| UnicodeScriptBrahmi
| UnicodeScriptMandaic
| UnicodeScriptChakma
| UnicodeScriptMeroiticCursive
| UnicodeScriptMeroiticHieroglyphs
| UnicodeScriptMiao
| UnicodeScriptSharada
| UnicodeScriptSoraSompeng
| UnicodeScriptTakri
| UnicodeScriptBassaVah
| UnicodeScriptCaucasianAlbanian
| UnicodeScriptDuployan
| UnicodeScriptElbasan
| UnicodeScriptGrantha
| UnicodeScriptKhojki
| UnicodeScriptKhudawadi
| UnicodeScriptLinearA
| UnicodeScriptMahajani
| UnicodeScriptManichaean
| UnicodeScriptMendeKikakui
| UnicodeScriptModi
| UnicodeScriptMro
| UnicodeScriptNabataean
| UnicodeScriptOldNorthArabian
| UnicodeScriptOldPermic
| UnicodeScriptPahawhHmong
| UnicodeScriptPalmyrene
| UnicodeScriptPauCinHau
| UnicodeScriptPsalterPahlavi
| UnicodeScriptSiddham
| UnicodeScriptTirhuta
| UnicodeScriptWarangCiti
| UnicodeScriptAhom
| UnicodeScriptAnatolianHieroglyphs
| UnicodeScriptHatran
| UnicodeScriptMultani
| UnicodeScriptOldHungarian
| UnicodeScriptSignwriting
| UnicodeScriptAdlam
| UnicodeScriptBhaiksuki
| UnicodeScriptMarchen
| UnicodeScriptNewa
| UnicodeScriptOsage
| UnicodeScriptTangut
| UnicodeScriptMasaramGondi
| UnicodeScriptNushu
| UnicodeScriptSoyombo
| UnicodeScriptZanabazarSquare
| UnicodeScriptDogra
| UnicodeScriptGunjalaGondi
| UnicodeScriptHanifiRohingya
| UnicodeScriptMakasar
| UnicodeScriptMedefaidrin
| UnicodeScriptOldSogdian
| UnicodeScriptSogdian
| AnotherUnicodeScript Int
deriving (Int -> UnicodeScript -> ShowS
[UnicodeScript] -> ShowS
UnicodeScript -> String
(Int -> UnicodeScript -> ShowS)
-> (UnicodeScript -> String)
-> ([UnicodeScript] -> ShowS)
-> Show UnicodeScript
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnicodeScript] -> ShowS
$cshowList :: [UnicodeScript] -> ShowS
show :: UnicodeScript -> String
$cshow :: UnicodeScript -> String
showsPrec :: Int -> UnicodeScript -> ShowS
$cshowsPrec :: Int -> UnicodeScript -> ShowS
Show, UnicodeScript -> UnicodeScript -> Bool
(UnicodeScript -> UnicodeScript -> Bool)
-> (UnicodeScript -> UnicodeScript -> Bool) -> Eq UnicodeScript
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnicodeScript -> UnicodeScript -> Bool
$c/= :: UnicodeScript -> UnicodeScript -> Bool
== :: UnicodeScript -> UnicodeScript -> Bool
$c== :: UnicodeScript -> UnicodeScript -> Bool
Eq)
instance P.Enum UnicodeScript where
fromEnum :: UnicodeScript -> Int
fromEnum UnicodeScriptInvalidCode = -1
fromEnum UnicodeScriptCommon = 0
fromEnum UnicodeScriptInherited = 1
fromEnum UnicodeScriptArabic = 2
fromEnum UnicodeScriptArmenian = 3
fromEnum UnicodeScriptBengali = 4
fromEnum UnicodeScriptBopomofo = 5
fromEnum UnicodeScriptCherokee = 6
fromEnum UnicodeScriptCoptic = 7
fromEnum UnicodeScriptCyrillic = 8
fromEnum UnicodeScriptDeseret = 9
fromEnum UnicodeScriptDevanagari = 10
fromEnum UnicodeScriptEthiopic = 11
fromEnum UnicodeScriptGeorgian = 12
fromEnum UnicodeScriptGothic = 13
fromEnum UnicodeScriptGreek = 14
fromEnum UnicodeScriptGujarati = 15
fromEnum UnicodeScriptGurmukhi = 16
fromEnum UnicodeScriptHan = 17
fromEnum UnicodeScriptHangul = 18
fromEnum UnicodeScriptHebrew = 19
fromEnum UnicodeScriptHiragana = 20
fromEnum UnicodeScriptKannada = 21
fromEnum UnicodeScriptKatakana = 22
fromEnum UnicodeScriptKhmer = 23
fromEnum UnicodeScriptLao = 24
fromEnum UnicodeScriptLatin = 25
fromEnum UnicodeScriptMalayalam = 26
fromEnum UnicodeScriptMongolian = 27
fromEnum UnicodeScriptMyanmar = 28
fromEnum UnicodeScriptOgham = 29
fromEnum UnicodeScriptOldItalic = 30
fromEnum UnicodeScriptOriya = 31
fromEnum UnicodeScriptRunic = 32
fromEnum UnicodeScriptSinhala = 33
fromEnum UnicodeScriptSyriac = 34
fromEnum UnicodeScriptTamil = 35
fromEnum UnicodeScriptTelugu = 36
fromEnum UnicodeScriptThaana = 37
fromEnum UnicodeScriptThai = 38
fromEnum UnicodeScriptTibetan = 39
fromEnum UnicodeScriptCanadianAboriginal = 40
fromEnum UnicodeScriptYi = 41
fromEnum UnicodeScriptTagalog = 42
fromEnum UnicodeScriptHanunoo = 43
fromEnum UnicodeScriptBuhid = 44
fromEnum UnicodeScriptTagbanwa = 45
fromEnum UnicodeScriptBraille = 46
fromEnum UnicodeScriptCypriot = 47
fromEnum UnicodeScriptLimbu = 48
fromEnum UnicodeScriptOsmanya = 49
fromEnum UnicodeScriptShavian = 50
fromEnum UnicodeScriptLinearB = 51
fromEnum UnicodeScriptTaiLe = 52
fromEnum UnicodeScriptUgaritic = 53
fromEnum UnicodeScriptNewTaiLue = 54
fromEnum UnicodeScriptBuginese = 55
fromEnum UnicodeScriptGlagolitic = 56
fromEnum UnicodeScriptTifinagh = 57
fromEnum UnicodeScriptSylotiNagri = 58
fromEnum UnicodeScriptOldPersian = 59
fromEnum UnicodeScriptKharoshthi = 60
fromEnum UnicodeScriptUnknown = 61
fromEnum UnicodeScriptBalinese = 62
fromEnum UnicodeScriptCuneiform = 63
fromEnum UnicodeScriptPhoenician = 64
fromEnum UnicodeScriptPhagsPa = 65
fromEnum UnicodeScriptNko = 66
fromEnum UnicodeScriptKayahLi = 67
fromEnum UnicodeScriptLepcha = 68
fromEnum UnicodeScriptRejang = 69
fromEnum UnicodeScriptSundanese = 70
fromEnum UnicodeScriptSaurashtra = 71
fromEnum UnicodeScriptCham = 72
fromEnum UnicodeScriptOlChiki = 73
fromEnum UnicodeScriptVai = 74
fromEnum UnicodeScriptCarian = 75
fromEnum UnicodeScriptLycian = 76
fromEnum UnicodeScriptLydian = 77
fromEnum UnicodeScriptAvestan = 78
fromEnum UnicodeScriptBamum = 79
fromEnum UnicodeScriptEgyptianHieroglyphs = 80
fromEnum UnicodeScriptImperialAramaic = 81
fromEnum UnicodeScriptInscriptionalPahlavi = 82
fromEnum UnicodeScriptInscriptionalParthian = 83
fromEnum UnicodeScriptJavanese = 84
fromEnum UnicodeScriptKaithi = 85
fromEnum UnicodeScriptLisu = 86
fromEnum UnicodeScriptMeeteiMayek = 87
fromEnum UnicodeScriptOldSouthArabian = 88
fromEnum UnicodeScriptOldTurkic = 89
fromEnum UnicodeScriptSamaritan = 90
fromEnum UnicodeScriptTaiTham = 91
fromEnum UnicodeScriptTaiViet = 92
fromEnum UnicodeScriptBatak = 93
fromEnum UnicodeScriptBrahmi = 94
fromEnum UnicodeScriptMandaic = 95
fromEnum UnicodeScriptChakma = 96
fromEnum UnicodeScriptMeroiticCursive = 97
fromEnum UnicodeScriptMeroiticHieroglyphs = 98
fromEnum UnicodeScriptMiao = 99
fromEnum UnicodeScriptSharada = 100
fromEnum UnicodeScriptSoraSompeng = 101
fromEnum UnicodeScriptTakri = 102
fromEnum UnicodeScriptBassaVah = 103
fromEnum UnicodeScriptCaucasianAlbanian = 104
fromEnum UnicodeScriptDuployan = 105
fromEnum UnicodeScriptElbasan = 106
fromEnum UnicodeScriptGrantha = 107
fromEnum UnicodeScriptKhojki = 108
fromEnum UnicodeScriptKhudawadi = 109
fromEnum UnicodeScriptLinearA = 110
fromEnum UnicodeScriptMahajani = 111
fromEnum UnicodeScriptManichaean = 112
fromEnum UnicodeScriptMendeKikakui = 113
fromEnum UnicodeScriptModi = 114
fromEnum UnicodeScriptMro = 115
fromEnum UnicodeScriptNabataean = 116
fromEnum UnicodeScriptOldNorthArabian = 117
fromEnum UnicodeScriptOldPermic = 118
fromEnum UnicodeScriptPahawhHmong = 119
fromEnum UnicodeScriptPalmyrene = 120
fromEnum UnicodeScriptPauCinHau = 121
fromEnum UnicodeScriptPsalterPahlavi = 122
fromEnum UnicodeScriptSiddham = 123
fromEnum UnicodeScriptTirhuta = 124
fromEnum UnicodeScriptWarangCiti = 125
fromEnum UnicodeScriptAhom = 126
fromEnum UnicodeScriptAnatolianHieroglyphs = 127
fromEnum UnicodeScriptHatran = 128
fromEnum UnicodeScriptMultani = 129
fromEnum UnicodeScriptOldHungarian = 130
fromEnum UnicodeScriptSignwriting = 131
fromEnum UnicodeScriptAdlam = 132
fromEnum UnicodeScriptBhaiksuki = 133
fromEnum UnicodeScriptMarchen = 134
fromEnum UnicodeScriptNewa = 135
fromEnum UnicodeScriptOsage = 136
fromEnum UnicodeScriptTangut = 137
fromEnum UnicodeScriptMasaramGondi = 138
fromEnum UnicodeScriptNushu = 139
fromEnum UnicodeScriptSoyombo = 140
fromEnum UnicodeScriptZanabazarSquare = 141
fromEnum UnicodeScriptDogra = 142
fromEnum UnicodeScriptGunjalaGondi = 143
fromEnum UnicodeScriptHanifiRohingya = 144
fromEnum UnicodeScriptMakasar = 145
fromEnum UnicodeScriptMedefaidrin = 146
fromEnum UnicodeScriptOldSogdian = 147
fromEnum UnicodeScriptSogdian = 148
fromEnum (AnotherUnicodeScript k :: Int
k) = Int
k
toEnum :: Int -> UnicodeScript
toEnum -1 = UnicodeScript
UnicodeScriptInvalidCode
toEnum 0 = UnicodeScript
UnicodeScriptCommon
toEnum 1 = UnicodeScript
UnicodeScriptInherited
toEnum 2 = UnicodeScript
UnicodeScriptArabic
toEnum 3 = UnicodeScript
UnicodeScriptArmenian
toEnum 4 = UnicodeScript
UnicodeScriptBengali
toEnum 5 = UnicodeScript
UnicodeScriptBopomofo
toEnum 6 = UnicodeScript
UnicodeScriptCherokee
toEnum 7 = UnicodeScript
UnicodeScriptCoptic
toEnum 8 = UnicodeScript
UnicodeScriptCyrillic
toEnum 9 = UnicodeScript
UnicodeScriptDeseret
toEnum 10 = UnicodeScript
UnicodeScriptDevanagari
toEnum 11 = UnicodeScript
UnicodeScriptEthiopic
toEnum 12 = UnicodeScript
UnicodeScriptGeorgian
toEnum 13 = UnicodeScript
UnicodeScriptGothic
toEnum 14 = UnicodeScript
UnicodeScriptGreek
toEnum 15 = UnicodeScript
UnicodeScriptGujarati
toEnum 16 = UnicodeScript
UnicodeScriptGurmukhi
toEnum 17 = UnicodeScript
UnicodeScriptHan
toEnum 18 = UnicodeScript
UnicodeScriptHangul
toEnum 19 = UnicodeScript
UnicodeScriptHebrew
toEnum 20 = UnicodeScript
UnicodeScriptHiragana
toEnum 21 = UnicodeScript
UnicodeScriptKannada
toEnum 22 = UnicodeScript
UnicodeScriptKatakana
toEnum 23 = UnicodeScript
UnicodeScriptKhmer
toEnum 24 = UnicodeScript
UnicodeScriptLao
toEnum 25 = UnicodeScript
UnicodeScriptLatin
toEnum 26 = UnicodeScript
UnicodeScriptMalayalam
toEnum 27 = UnicodeScript
UnicodeScriptMongolian
toEnum 28 = UnicodeScript
UnicodeScriptMyanmar
toEnum 29 = UnicodeScript
UnicodeScriptOgham
toEnum 30 = UnicodeScript
UnicodeScriptOldItalic
toEnum 31 = UnicodeScript
UnicodeScriptOriya
toEnum 32 = UnicodeScript
UnicodeScriptRunic
toEnum 33 = UnicodeScript
UnicodeScriptSinhala
toEnum 34 = UnicodeScript
UnicodeScriptSyriac
toEnum 35 = UnicodeScript
UnicodeScriptTamil
toEnum 36 = UnicodeScript
UnicodeScriptTelugu
toEnum 37 = UnicodeScript
UnicodeScriptThaana
toEnum 38 = UnicodeScript
UnicodeScriptThai
toEnum 39 = UnicodeScript
UnicodeScriptTibetan
toEnum 40 = UnicodeScript
UnicodeScriptCanadianAboriginal
toEnum 41 = UnicodeScript
UnicodeScriptYi
toEnum 42 = UnicodeScript
UnicodeScriptTagalog
toEnum 43 = UnicodeScript
UnicodeScriptHanunoo
toEnum 44 = UnicodeScript
UnicodeScriptBuhid
toEnum 45 = UnicodeScript
UnicodeScriptTagbanwa
toEnum 46 = UnicodeScript
UnicodeScriptBraille
toEnum 47 = UnicodeScript
UnicodeScriptCypriot
toEnum 48 = UnicodeScript
UnicodeScriptLimbu
toEnum 49 = UnicodeScript
UnicodeScriptOsmanya
toEnum 50 = UnicodeScript
UnicodeScriptShavian
toEnum 51 = UnicodeScript
UnicodeScriptLinearB
toEnum 52 = UnicodeScript
UnicodeScriptTaiLe
toEnum 53 = UnicodeScript
UnicodeScriptUgaritic
toEnum 54 = UnicodeScript
UnicodeScriptNewTaiLue
toEnum 55 = UnicodeScript
UnicodeScriptBuginese
toEnum 56 = UnicodeScript
UnicodeScriptGlagolitic
toEnum 57 = UnicodeScript
UnicodeScriptTifinagh
toEnum 58 = UnicodeScript
UnicodeScriptSylotiNagri
toEnum 59 = UnicodeScript
UnicodeScriptOldPersian
toEnum 60 = UnicodeScript
UnicodeScriptKharoshthi
toEnum 61 = UnicodeScript
UnicodeScriptUnknown
toEnum 62 = UnicodeScript
UnicodeScriptBalinese
toEnum 63 = UnicodeScript
UnicodeScriptCuneiform
toEnum 64 = UnicodeScript
UnicodeScriptPhoenician
toEnum 65 = UnicodeScript
UnicodeScriptPhagsPa
toEnum 66 = UnicodeScript
UnicodeScriptNko
toEnum 67 = UnicodeScript
UnicodeScriptKayahLi
toEnum 68 = UnicodeScript
UnicodeScriptLepcha
toEnum 69 = UnicodeScript
UnicodeScriptRejang
toEnum 70 = UnicodeScript
UnicodeScriptSundanese
toEnum 71 = UnicodeScript
UnicodeScriptSaurashtra
toEnum 72 = UnicodeScript
UnicodeScriptCham
toEnum 73 = UnicodeScript
UnicodeScriptOlChiki
toEnum 74 = UnicodeScript
UnicodeScriptVai
toEnum 75 = UnicodeScript
UnicodeScriptCarian
toEnum 76 = UnicodeScript
UnicodeScriptLycian
toEnum 77 = UnicodeScript
UnicodeScriptLydian
toEnum 78 = UnicodeScript
UnicodeScriptAvestan
toEnum 79 = UnicodeScript
UnicodeScriptBamum
toEnum 80 = UnicodeScript
UnicodeScriptEgyptianHieroglyphs
toEnum 81 = UnicodeScript
UnicodeScriptImperialAramaic
toEnum 82 = UnicodeScript
UnicodeScriptInscriptionalPahlavi
toEnum 83 = UnicodeScript
UnicodeScriptInscriptionalParthian
toEnum 84 = UnicodeScript
UnicodeScriptJavanese
toEnum 85 = UnicodeScript
UnicodeScriptKaithi
toEnum 86 = UnicodeScript
UnicodeScriptLisu
toEnum 87 = UnicodeScript
UnicodeScriptMeeteiMayek
toEnum 88 = UnicodeScript
UnicodeScriptOldSouthArabian
toEnum 89 = UnicodeScript
UnicodeScriptOldTurkic
toEnum 90 = UnicodeScript
UnicodeScriptSamaritan
toEnum 91 = UnicodeScript
UnicodeScriptTaiTham
toEnum 92 = UnicodeScript
UnicodeScriptTaiViet
toEnum 93 = UnicodeScript
UnicodeScriptBatak
toEnum 94 = UnicodeScript
UnicodeScriptBrahmi
toEnum 95 = UnicodeScript
UnicodeScriptMandaic
toEnum 96 = UnicodeScript
UnicodeScriptChakma
toEnum 97 = UnicodeScript
UnicodeScriptMeroiticCursive
toEnum 98 = UnicodeScript
UnicodeScriptMeroiticHieroglyphs
toEnum 99 = UnicodeScript
UnicodeScriptMiao
toEnum 100 = UnicodeScript
UnicodeScriptSharada
toEnum 101 = UnicodeScript
UnicodeScriptSoraSompeng
toEnum 102 = UnicodeScript
UnicodeScriptTakri
toEnum 103 = UnicodeScript
UnicodeScriptBassaVah
toEnum 104 = UnicodeScript
UnicodeScriptCaucasianAlbanian
toEnum 105 = UnicodeScript
UnicodeScriptDuployan
toEnum 106 = UnicodeScript
UnicodeScriptElbasan
toEnum 107 = UnicodeScript
UnicodeScriptGrantha
toEnum 108 = UnicodeScript
UnicodeScriptKhojki
toEnum 109 = UnicodeScript
UnicodeScriptKhudawadi
toEnum 110 = UnicodeScript
UnicodeScriptLinearA
toEnum 111 = UnicodeScript
UnicodeScriptMahajani
toEnum 112 = UnicodeScript
UnicodeScriptManichaean
toEnum 113 = UnicodeScript
UnicodeScriptMendeKikakui
toEnum 114 = UnicodeScript
UnicodeScriptModi
toEnum 115 = UnicodeScript
UnicodeScriptMro
toEnum 116 = UnicodeScript
UnicodeScriptNabataean
toEnum 117 = UnicodeScript
UnicodeScriptOldNorthArabian
toEnum 118 = UnicodeScript
UnicodeScriptOldPermic
toEnum 119 = UnicodeScript
UnicodeScriptPahawhHmong
toEnum 120 = UnicodeScript
UnicodeScriptPalmyrene
toEnum 121 = UnicodeScript
UnicodeScriptPauCinHau
toEnum 122 = UnicodeScript
UnicodeScriptPsalterPahlavi
toEnum 123 = UnicodeScript
UnicodeScriptSiddham
toEnum 124 = UnicodeScript
UnicodeScriptTirhuta
toEnum 125 = UnicodeScript
UnicodeScriptWarangCiti
toEnum 126 = UnicodeScript
UnicodeScriptAhom
toEnum 127 = UnicodeScript
UnicodeScriptAnatolianHieroglyphs
toEnum 128 = UnicodeScript
UnicodeScriptHatran
toEnum 129 = UnicodeScript
UnicodeScriptMultani
toEnum 130 = UnicodeScript
UnicodeScriptOldHungarian
toEnum 131 = UnicodeScript
UnicodeScriptSignwriting
toEnum 132 = UnicodeScript
UnicodeScriptAdlam
toEnum 133 = UnicodeScript
UnicodeScriptBhaiksuki
toEnum 134 = UnicodeScript
UnicodeScriptMarchen
toEnum 135 = UnicodeScript
UnicodeScriptNewa
toEnum 136 = UnicodeScript
UnicodeScriptOsage
toEnum 137 = UnicodeScript
UnicodeScriptTangut
toEnum 138 = UnicodeScript
UnicodeScriptMasaramGondi
toEnum 139 = UnicodeScript
UnicodeScriptNushu
toEnum 140 = UnicodeScript
UnicodeScriptSoyombo
toEnum 141 = UnicodeScript
UnicodeScriptZanabazarSquare
toEnum 142 = UnicodeScript
UnicodeScriptDogra
toEnum 143 = UnicodeScript
UnicodeScriptGunjalaGondi
toEnum 144 = UnicodeScript
UnicodeScriptHanifiRohingya
toEnum 145 = UnicodeScript
UnicodeScriptMakasar
toEnum 146 = UnicodeScript
UnicodeScriptMedefaidrin
toEnum 147 = UnicodeScript
UnicodeScriptOldSogdian
toEnum 148 = UnicodeScript
UnicodeScriptSogdian
toEnum k :: Int
k = Int -> UnicodeScript
AnotherUnicodeScript Int
k
instance P.Ord UnicodeScript where
compare :: UnicodeScript -> UnicodeScript -> Ordering
compare a :: UnicodeScript
a b :: UnicodeScript
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UnicodeScript -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeScript
a) (UnicodeScript -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeScript
b)
data UnicodeBreakType =
UnicodeBreakTypeMandatory
| UnicodeBreakTypeCarriageReturn
| UnicodeBreakTypeLineFeed
| UnicodeBreakTypeCombiningMark
| UnicodeBreakTypeSurrogate
| UnicodeBreakTypeZeroWidthSpace
| UnicodeBreakTypeInseparable
| UnicodeBreakTypeNonBreakingGlue
| UnicodeBreakTypeContingent
| UnicodeBreakTypeSpace
| UnicodeBreakTypeAfter
| UnicodeBreakTypeBefore
| UnicodeBreakTypeBeforeAndAfter
| UnicodeBreakTypeHyphen
| UnicodeBreakTypeNonStarter
| UnicodeBreakTypeOpenPunctuation
| UnicodeBreakTypeClosePunctuation
| UnicodeBreakTypeQuotation
| UnicodeBreakTypeExclamation
| UnicodeBreakTypeIdeographic
| UnicodeBreakTypeNumeric
| UnicodeBreakTypeInfixSeparator
| UnicodeBreakTypeSymbol
| UnicodeBreakTypeAlphabetic
| UnicodeBreakTypePrefix
| UnicodeBreakTypePostfix
| UnicodeBreakTypeComplexContext
| UnicodeBreakTypeAmbiguous
| UnicodeBreakTypeUnknown
| UnicodeBreakTypeNextLine
| UnicodeBreakTypeWordJoiner
| UnicodeBreakTypeHangulLJamo
| UnicodeBreakTypeHangulVJamo
| UnicodeBreakTypeHangulTJamo
| UnicodeBreakTypeHangulLvSyllable
| UnicodeBreakTypeHangulLvtSyllable
| UnicodeBreakTypeCloseParanthesis
| UnicodeBreakTypeConditionalJapaneseStarter
| UnicodeBreakTypeHebrewLetter
| UnicodeBreakTypeRegionalIndicator
| UnicodeBreakTypeEmojiBase
| UnicodeBreakTypeEmojiModifier
| UnicodeBreakTypeZeroWidthJoiner
| AnotherUnicodeBreakType Int
deriving (Int -> UnicodeBreakType -> ShowS
[UnicodeBreakType] -> ShowS
UnicodeBreakType -> String
(Int -> UnicodeBreakType -> ShowS)
-> (UnicodeBreakType -> String)
-> ([UnicodeBreakType] -> ShowS)
-> Show UnicodeBreakType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnicodeBreakType] -> ShowS
$cshowList :: [UnicodeBreakType] -> ShowS
show :: UnicodeBreakType -> String
$cshow :: UnicodeBreakType -> String
showsPrec :: Int -> UnicodeBreakType -> ShowS
$cshowsPrec :: Int -> UnicodeBreakType -> ShowS
Show, UnicodeBreakType -> UnicodeBreakType -> Bool
(UnicodeBreakType -> UnicodeBreakType -> Bool)
-> (UnicodeBreakType -> UnicodeBreakType -> Bool)
-> Eq UnicodeBreakType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnicodeBreakType -> UnicodeBreakType -> Bool
$c/= :: UnicodeBreakType -> UnicodeBreakType -> Bool
== :: UnicodeBreakType -> UnicodeBreakType -> Bool
$c== :: UnicodeBreakType -> UnicodeBreakType -> Bool
Eq)
instance P.Enum UnicodeBreakType where
fromEnum :: UnicodeBreakType -> Int
fromEnum UnicodeBreakTypeMandatory = 0
fromEnum UnicodeBreakTypeCarriageReturn = 1
fromEnum UnicodeBreakTypeLineFeed = 2
fromEnum UnicodeBreakTypeCombiningMark = 3
fromEnum UnicodeBreakTypeSurrogate = 4
fromEnum UnicodeBreakTypeZeroWidthSpace = 5
fromEnum UnicodeBreakTypeInseparable = 6
fromEnum UnicodeBreakTypeNonBreakingGlue = 7
fromEnum UnicodeBreakTypeContingent = 8
fromEnum UnicodeBreakTypeSpace = 9
fromEnum UnicodeBreakTypeAfter = 10
fromEnum UnicodeBreakTypeBefore = 11
fromEnum UnicodeBreakTypeBeforeAndAfter = 12
fromEnum UnicodeBreakTypeHyphen = 13
fromEnum UnicodeBreakTypeNonStarter = 14
fromEnum UnicodeBreakTypeOpenPunctuation = 15
fromEnum UnicodeBreakTypeClosePunctuation = 16
fromEnum UnicodeBreakTypeQuotation = 17
fromEnum UnicodeBreakTypeExclamation = 18
fromEnum UnicodeBreakTypeIdeographic = 19
fromEnum UnicodeBreakTypeNumeric = 20
fromEnum UnicodeBreakTypeInfixSeparator = 21
fromEnum UnicodeBreakTypeSymbol = 22
fromEnum UnicodeBreakTypeAlphabetic = 23
fromEnum UnicodeBreakTypePrefix = 24
fromEnum UnicodeBreakTypePostfix = 25
fromEnum UnicodeBreakTypeComplexContext = 26
fromEnum UnicodeBreakTypeAmbiguous = 27
fromEnum UnicodeBreakTypeUnknown = 28
fromEnum UnicodeBreakTypeNextLine = 29
fromEnum UnicodeBreakTypeWordJoiner = 30
fromEnum UnicodeBreakTypeHangulLJamo = 31
fromEnum UnicodeBreakTypeHangulVJamo = 32
fromEnum UnicodeBreakTypeHangulTJamo = 33
fromEnum UnicodeBreakTypeHangulLvSyllable = 34
fromEnum UnicodeBreakTypeHangulLvtSyllable = 35
fromEnum UnicodeBreakTypeCloseParanthesis = 36
fromEnum UnicodeBreakTypeConditionalJapaneseStarter = 37
fromEnum UnicodeBreakTypeHebrewLetter = 38
fromEnum UnicodeBreakTypeRegionalIndicator = 39
fromEnum UnicodeBreakTypeEmojiBase = 40
fromEnum UnicodeBreakTypeEmojiModifier = 41
fromEnum UnicodeBreakTypeZeroWidthJoiner = 42
fromEnum (AnotherUnicodeBreakType k :: Int
k) = Int
k
toEnum :: Int -> UnicodeBreakType
toEnum 0 = UnicodeBreakType
UnicodeBreakTypeMandatory
toEnum 1 = UnicodeBreakType
UnicodeBreakTypeCarriageReturn
toEnum 2 = UnicodeBreakType
UnicodeBreakTypeLineFeed
toEnum 3 = UnicodeBreakType
UnicodeBreakTypeCombiningMark
toEnum 4 = UnicodeBreakType
UnicodeBreakTypeSurrogate
toEnum 5 = UnicodeBreakType
UnicodeBreakTypeZeroWidthSpace
toEnum 6 = UnicodeBreakType
UnicodeBreakTypeInseparable
toEnum 7 = UnicodeBreakType
UnicodeBreakTypeNonBreakingGlue
toEnum 8 = UnicodeBreakType
UnicodeBreakTypeContingent
toEnum 9 = UnicodeBreakType
UnicodeBreakTypeSpace
toEnum 10 = UnicodeBreakType
UnicodeBreakTypeAfter
toEnum 11 = UnicodeBreakType
UnicodeBreakTypeBefore
toEnum 12 = UnicodeBreakType
UnicodeBreakTypeBeforeAndAfter
toEnum 13 = UnicodeBreakType
UnicodeBreakTypeHyphen
toEnum 14 = UnicodeBreakType
UnicodeBreakTypeNonStarter
toEnum 15 = UnicodeBreakType
UnicodeBreakTypeOpenPunctuation
toEnum 16 = UnicodeBreakType
UnicodeBreakTypeClosePunctuation
toEnum 17 = UnicodeBreakType
UnicodeBreakTypeQuotation
toEnum 18 = UnicodeBreakType
UnicodeBreakTypeExclamation
toEnum 19 = UnicodeBreakType
UnicodeBreakTypeIdeographic
toEnum 20 = UnicodeBreakType
UnicodeBreakTypeNumeric
toEnum 21 = UnicodeBreakType
UnicodeBreakTypeInfixSeparator
toEnum 22 = UnicodeBreakType
UnicodeBreakTypeSymbol
toEnum 23 = UnicodeBreakType
UnicodeBreakTypeAlphabetic
toEnum 24 = UnicodeBreakType
UnicodeBreakTypePrefix
toEnum 25 = UnicodeBreakType
UnicodeBreakTypePostfix
toEnum 26 = UnicodeBreakType
UnicodeBreakTypeComplexContext
toEnum 27 = UnicodeBreakType
UnicodeBreakTypeAmbiguous
toEnum 28 = UnicodeBreakType
UnicodeBreakTypeUnknown
toEnum 29 = UnicodeBreakType
UnicodeBreakTypeNextLine
toEnum 30 = UnicodeBreakType
UnicodeBreakTypeWordJoiner
toEnum 31 = UnicodeBreakType
UnicodeBreakTypeHangulLJamo
toEnum 32 = UnicodeBreakType
UnicodeBreakTypeHangulVJamo
toEnum 33 = UnicodeBreakType
UnicodeBreakTypeHangulTJamo
toEnum 34 = UnicodeBreakType
UnicodeBreakTypeHangulLvSyllable
toEnum 35 = UnicodeBreakType
UnicodeBreakTypeHangulLvtSyllable
toEnum 36 = UnicodeBreakType
UnicodeBreakTypeCloseParanthesis
toEnum 37 = UnicodeBreakType
UnicodeBreakTypeConditionalJapaneseStarter
toEnum 38 = UnicodeBreakType
UnicodeBreakTypeHebrewLetter
toEnum 39 = UnicodeBreakType
UnicodeBreakTypeRegionalIndicator
toEnum 40 = UnicodeBreakType
UnicodeBreakTypeEmojiBase
toEnum 41 = UnicodeBreakType
UnicodeBreakTypeEmojiModifier
toEnum 42 = UnicodeBreakType
UnicodeBreakTypeZeroWidthJoiner
toEnum k :: Int
k = Int -> UnicodeBreakType
AnotherUnicodeBreakType Int
k
instance P.Ord UnicodeBreakType where
compare :: UnicodeBreakType -> UnicodeBreakType -> Ordering
compare a :: UnicodeBreakType
a b :: UnicodeBreakType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UnicodeBreakType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeBreakType
a) (UnicodeBreakType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeBreakType
b)
data TraverseType =
TraverseTypeInOrder
| TraverseTypePreOrder
| TraverseTypePostOrder
| TraverseTypeLevelOrder
| AnotherTraverseType Int
deriving (Int -> TraverseType -> ShowS
[TraverseType] -> ShowS
TraverseType -> String
(Int -> TraverseType -> ShowS)
-> (TraverseType -> String)
-> ([TraverseType] -> ShowS)
-> Show TraverseType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TraverseType] -> ShowS
$cshowList :: [TraverseType] -> ShowS
show :: TraverseType -> String
$cshow :: TraverseType -> String
showsPrec :: Int -> TraverseType -> ShowS
$cshowsPrec :: Int -> TraverseType -> ShowS
Show, TraverseType -> TraverseType -> Bool
(TraverseType -> TraverseType -> Bool)
-> (TraverseType -> TraverseType -> Bool) -> Eq TraverseType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraverseType -> TraverseType -> Bool
$c/= :: TraverseType -> TraverseType -> Bool
== :: TraverseType -> TraverseType -> Bool
$c== :: TraverseType -> TraverseType -> Bool
Eq)
instance P.Enum TraverseType where
fromEnum :: TraverseType -> Int
fromEnum TraverseTypeInOrder = 0
fromEnum TraverseTypePreOrder = 1
fromEnum TraverseTypePostOrder = 2
fromEnum TraverseTypeLevelOrder = 3
fromEnum (AnotherTraverseType k :: Int
k) = Int
k
toEnum :: Int -> TraverseType
toEnum 0 = TraverseType
TraverseTypeInOrder
toEnum 1 = TraverseType
TraverseTypePreOrder
toEnum 2 = TraverseType
TraverseTypePostOrder
toEnum 3 = TraverseType
TraverseTypeLevelOrder
toEnum k :: Int
k = Int -> TraverseType
AnotherTraverseType Int
k
instance P.Ord TraverseType where
compare :: TraverseType -> TraverseType -> Ordering
compare a :: TraverseType
a b :: TraverseType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TraverseType -> Int
forall a. Enum a => a -> Int
P.fromEnum TraverseType
a) (TraverseType -> Int
forall a. Enum a => a -> Int
P.fromEnum TraverseType
b)
data TokenType =
TokenTypeEof
| TokenTypeLeftParen
| TokenTypeRightParen
| TokenTypeLeftCurly
| TokenTypeRightCurly
| TokenTypeLeftBrace
| TokenTypeRightBrace
| TokenTypeEqualSign
| TokenTypeComma
| TokenTypeNone
| TokenTypeError
| TokenTypeChar
| TokenTypeBinary
| TokenTypeOctal
| TokenTypeInt
| TokenTypeHex
| TokenTypeFloat
| TokenTypeString
| TokenTypeSymbol
| TokenTypeIdentifier
| TokenTypeIdentifierNull
|
|
| AnotherTokenType Int
deriving (Int -> TokenType -> ShowS
[TokenType] -> ShowS
TokenType -> String
(Int -> TokenType -> ShowS)
-> (TokenType -> String)
-> ([TokenType] -> ShowS)
-> Show TokenType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenType] -> ShowS
$cshowList :: [TokenType] -> ShowS
show :: TokenType -> String
$cshow :: TokenType -> String
showsPrec :: Int -> TokenType -> ShowS
$cshowsPrec :: Int -> TokenType -> ShowS
Show, TokenType -> TokenType -> Bool
(TokenType -> TokenType -> Bool)
-> (TokenType -> TokenType -> Bool) -> Eq TokenType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenType -> TokenType -> Bool
$c/= :: TokenType -> TokenType -> Bool
== :: TokenType -> TokenType -> Bool
$c== :: TokenType -> TokenType -> Bool
Eq)
instance P.Enum TokenType where
fromEnum :: TokenType -> Int
fromEnum TokenTypeEof = 0
fromEnum TokenTypeLeftParen = 40
fromEnum TokenTypeRightParen = 41
fromEnum TokenTypeLeftCurly = 123
fromEnum TokenTypeRightCurly = 125
fromEnum TokenTypeLeftBrace = 91
fromEnum TokenTypeRightBrace = 93
fromEnum TokenTypeEqualSign = 61
fromEnum TokenTypeComma = 44
fromEnum TokenTypeNone = 256
fromEnum TokenTypeError = 257
fromEnum TokenTypeChar = 258
fromEnum TokenTypeBinary = 259
fromEnum TokenTypeOctal = 260
fromEnum TokenTypeInt = 261
fromEnum TokenTypeHex = 262
fromEnum TokenTypeFloat = 263
fromEnum TokenTypeString = 264
fromEnum TokenTypeSymbol = 265
fromEnum TokenTypeIdentifier = 266
fromEnum TokenTypeIdentifierNull = 267
fromEnum TokenTypeCommentSingle = 268
fromEnum TokenTypeCommentMulti = 269
fromEnum (AnotherTokenType k :: Int
k) = Int
k
toEnum :: Int -> TokenType
toEnum 0 = TokenType
TokenTypeEof
toEnum 40 = TokenType
TokenTypeLeftParen
toEnum 41 = TokenType
TokenTypeRightParen
toEnum 123 = TokenType
TokenTypeLeftCurly
toEnum 125 = TokenType
TokenTypeRightCurly
toEnum 91 = TokenType
TokenTypeLeftBrace
toEnum 93 = TokenType
TokenTypeRightBrace
toEnum 61 = TokenType
TokenTypeEqualSign
toEnum 44 = TokenType
TokenTypeComma
toEnum 256 = TokenType
TokenTypeNone
toEnum 257 = TokenType
TokenTypeError
toEnum 258 = TokenType
TokenTypeChar
toEnum 259 = TokenType
TokenTypeBinary
toEnum 260 = TokenType
TokenTypeOctal
toEnum 261 = TokenType
TokenTypeInt
toEnum 262 = TokenType
TokenTypeHex
toEnum 263 = TokenType
TokenTypeFloat
toEnum 264 = TokenType
TokenTypeString
toEnum 265 = TokenType
TokenTypeSymbol
toEnum 266 = TokenType
TokenTypeIdentifier
toEnum 267 = TokenType
TokenTypeIdentifierNull
toEnum 268 = TokenType
TokenTypeCommentSingle
toEnum 269 = TokenType
TokenTypeCommentMulti
toEnum k :: Int
k = Int -> TokenType
AnotherTokenType Int
k
instance P.Ord TokenType where
compare :: TokenType -> TokenType -> Ordering
compare a :: TokenType
a b :: TokenType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TokenType -> Int
forall a. Enum a => a -> Int
P.fromEnum TokenType
a) (TokenType -> Int
forall a. Enum a => a -> Int
P.fromEnum TokenType
b)
data TimeType =
TimeTypeStandard
| TimeTypeDaylight
| TimeTypeUniversal
| AnotherTimeType Int
deriving (Int -> TimeType -> ShowS
[TimeType] -> ShowS
TimeType -> String
(Int -> TimeType -> ShowS)
-> (TimeType -> String) -> ([TimeType] -> ShowS) -> Show TimeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimeType] -> ShowS
$cshowList :: [TimeType] -> ShowS
show :: TimeType -> String
$cshow :: TimeType -> String
showsPrec :: Int -> TimeType -> ShowS
$cshowsPrec :: Int -> TimeType -> ShowS
Show, TimeType -> TimeType -> Bool
(TimeType -> TimeType -> Bool)
-> (TimeType -> TimeType -> Bool) -> Eq TimeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeType -> TimeType -> Bool
$c/= :: TimeType -> TimeType -> Bool
== :: TimeType -> TimeType -> Bool
$c== :: TimeType -> TimeType -> Bool
Eq)
instance P.Enum TimeType where
fromEnum :: TimeType -> Int
fromEnum TimeTypeStandard = 0
fromEnum TimeTypeDaylight = 1
fromEnum TimeTypeUniversal = 2
fromEnum (AnotherTimeType k :: Int
k) = Int
k
toEnum :: Int -> TimeType
toEnum 0 = TimeType
TimeTypeStandard
toEnum 1 = TimeType
TimeTypeDaylight
toEnum 2 = TimeType
TimeTypeUniversal
toEnum k :: Int
k = Int -> TimeType
AnotherTimeType Int
k
instance P.Ord TimeType where
compare :: TimeType -> TimeType -> Ordering
compare a :: TimeType
a b :: TimeType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TimeType -> Int
forall a. Enum a => a -> Int
P.fromEnum TimeType
a) (TimeType -> Int
forall a. Enum a => a -> Int
P.fromEnum TimeType
b)
data ThreadError =
ThreadErrorThreadErrorAgain
| AnotherThreadError Int
deriving (Int -> ThreadError -> ShowS
[ThreadError] -> ShowS
ThreadError -> String
(Int -> ThreadError -> ShowS)
-> (ThreadError -> String)
-> ([ThreadError] -> ShowS)
-> Show ThreadError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThreadError] -> ShowS
$cshowList :: [ThreadError] -> ShowS
show :: ThreadError -> String
$cshow :: ThreadError -> String
showsPrec :: Int -> ThreadError -> ShowS
$cshowsPrec :: Int -> ThreadError -> ShowS
Show, ThreadError -> ThreadError -> Bool
(ThreadError -> ThreadError -> Bool)
-> (ThreadError -> ThreadError -> Bool) -> Eq ThreadError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThreadError -> ThreadError -> Bool
$c/= :: ThreadError -> ThreadError -> Bool
== :: ThreadError -> ThreadError -> Bool
$c== :: ThreadError -> ThreadError -> Bool
Eq)
instance P.Enum ThreadError where
fromEnum :: ThreadError -> Int
fromEnum ThreadErrorThreadErrorAgain = 0
fromEnum (AnotherThreadError k :: Int
k) = Int
k
toEnum :: Int -> ThreadError
toEnum 0 = ThreadError
ThreadErrorThreadErrorAgain
toEnum k :: Int
k = Int -> ThreadError
AnotherThreadError Int
k
instance P.Ord ThreadError where
compare :: ThreadError -> ThreadError -> Ordering
compare a :: ThreadError
a b :: ThreadError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ThreadError -> Int
forall a. Enum a => a -> Int
P.fromEnum ThreadError
a) (ThreadError -> Int
forall a. Enum a => a -> Int
P.fromEnum ThreadError
b)
instance GErrorClass ThreadError where
gerrorClassDomain :: ThreadError -> Text
gerrorClassDomain _ = "g_thread_error"
catchThreadError ::
IO a ->
(ThreadError -> GErrorMessage -> IO a) ->
IO a
catchThreadError :: IO a -> (ThreadError -> Text -> IO a) -> IO a
catchThreadError = IO a -> (ThreadError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleThreadError ::
(ThreadError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleThreadError :: (ThreadError -> Text -> IO a) -> IO a -> IO a
handleThreadError = (ThreadError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data TestResult =
TestResultSuccess
| TestResultSkipped
| TestResultFailure
| TestResultIncomplete
| AnotherTestResult Int
deriving (Int -> TestResult -> ShowS
[TestResult] -> ShowS
TestResult -> String
(Int -> TestResult -> ShowS)
-> (TestResult -> String)
-> ([TestResult] -> ShowS)
-> Show TestResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestResult] -> ShowS
$cshowList :: [TestResult] -> ShowS
show :: TestResult -> String
$cshow :: TestResult -> String
showsPrec :: Int -> TestResult -> ShowS
$cshowsPrec :: Int -> TestResult -> ShowS
Show, TestResult -> TestResult -> Bool
(TestResult -> TestResult -> Bool)
-> (TestResult -> TestResult -> Bool) -> Eq TestResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestResult -> TestResult -> Bool
$c/= :: TestResult -> TestResult -> Bool
== :: TestResult -> TestResult -> Bool
$c== :: TestResult -> TestResult -> Bool
Eq)
instance P.Enum TestResult where
fromEnum :: TestResult -> Int
fromEnum TestResultSuccess = 0
fromEnum TestResultSkipped = 1
fromEnum TestResultFailure = 2
fromEnum TestResultIncomplete = 3
fromEnum (AnotherTestResult k :: Int
k) = Int
k
toEnum :: Int -> TestResult
toEnum 0 = TestResult
TestResultSuccess
toEnum 1 = TestResult
TestResultSkipped
toEnum 2 = TestResult
TestResultFailure
toEnum 3 = TestResult
TestResultIncomplete
toEnum k :: Int
k = Int -> TestResult
AnotherTestResult Int
k
instance P.Ord TestResult where
compare :: TestResult -> TestResult -> Ordering
compare a :: TestResult
a b :: TestResult
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TestResult -> Int
forall a. Enum a => a -> Int
P.fromEnum TestResult
a) (TestResult -> Int
forall a. Enum a => a -> Int
P.fromEnum TestResult
b)
data TestLogType =
TestLogTypeNone
| TestLogTypeError
| TestLogTypeStartBinary
| TestLogTypeListCase
| TestLogTypeSkipCase
| TestLogTypeStartCase
| TestLogTypeStopCase
| TestLogTypeMinResult
| TestLogTypeMaxResult
| TestLogTypeMessage
| TestLogTypeStartSuite
| TestLogTypeStopSuite
| AnotherTestLogType Int
deriving (Int -> TestLogType -> ShowS
[TestLogType] -> ShowS
TestLogType -> String
(Int -> TestLogType -> ShowS)
-> (TestLogType -> String)
-> ([TestLogType] -> ShowS)
-> Show TestLogType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestLogType] -> ShowS
$cshowList :: [TestLogType] -> ShowS
show :: TestLogType -> String
$cshow :: TestLogType -> String
showsPrec :: Int -> TestLogType -> ShowS
$cshowsPrec :: Int -> TestLogType -> ShowS
Show, TestLogType -> TestLogType -> Bool
(TestLogType -> TestLogType -> Bool)
-> (TestLogType -> TestLogType -> Bool) -> Eq TestLogType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestLogType -> TestLogType -> Bool
$c/= :: TestLogType -> TestLogType -> Bool
== :: TestLogType -> TestLogType -> Bool
$c== :: TestLogType -> TestLogType -> Bool
Eq)
instance P.Enum TestLogType where
fromEnum :: TestLogType -> Int
fromEnum TestLogTypeNone = 0
fromEnum TestLogTypeError = 1
fromEnum TestLogTypeStartBinary = 2
fromEnum TestLogTypeListCase = 3
fromEnum TestLogTypeSkipCase = 4
fromEnum TestLogTypeStartCase = 5
fromEnum TestLogTypeStopCase = 6
fromEnum TestLogTypeMinResult = 7
fromEnum TestLogTypeMaxResult = 8
fromEnum TestLogTypeMessage = 9
fromEnum TestLogTypeStartSuite = 10
fromEnum TestLogTypeStopSuite = 11
fromEnum (AnotherTestLogType k :: Int
k) = Int
k
toEnum :: Int -> TestLogType
toEnum 0 = TestLogType
TestLogTypeNone
toEnum 1 = TestLogType
TestLogTypeError
toEnum 2 = TestLogType
TestLogTypeStartBinary
toEnum 3 = TestLogType
TestLogTypeListCase
toEnum 4 = TestLogType
TestLogTypeSkipCase
toEnum 5 = TestLogType
TestLogTypeStartCase
toEnum 6 = TestLogType
TestLogTypeStopCase
toEnum 7 = TestLogType
TestLogTypeMinResult
toEnum 8 = TestLogType
TestLogTypeMaxResult
toEnum 9 = TestLogType
TestLogTypeMessage
toEnum 10 = TestLogType
TestLogTypeStartSuite
toEnum 11 = TestLogType
TestLogTypeStopSuite
toEnum k :: Int
k = Int -> TestLogType
AnotherTestLogType Int
k
instance P.Ord TestLogType where
compare :: TestLogType -> TestLogType -> Ordering
compare a :: TestLogType
a b :: TestLogType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TestLogType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestLogType
a) (TestLogType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestLogType
b)
data TestFileType =
TestFileTypeDist
| TestFileTypeBuilt
| AnotherTestFileType Int
deriving (Int -> TestFileType -> ShowS
[TestFileType] -> ShowS
TestFileType -> String
(Int -> TestFileType -> ShowS)
-> (TestFileType -> String)
-> ([TestFileType] -> ShowS)
-> Show TestFileType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestFileType] -> ShowS
$cshowList :: [TestFileType] -> ShowS
show :: TestFileType -> String
$cshow :: TestFileType -> String
showsPrec :: Int -> TestFileType -> ShowS
$cshowsPrec :: Int -> TestFileType -> ShowS
Show, TestFileType -> TestFileType -> Bool
(TestFileType -> TestFileType -> Bool)
-> (TestFileType -> TestFileType -> Bool) -> Eq TestFileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestFileType -> TestFileType -> Bool
$c/= :: TestFileType -> TestFileType -> Bool
== :: TestFileType -> TestFileType -> Bool
$c== :: TestFileType -> TestFileType -> Bool
Eq)
instance P.Enum TestFileType where
fromEnum :: TestFileType -> Int
fromEnum TestFileTypeDist = 0
fromEnum TestFileTypeBuilt = 1
fromEnum (AnotherTestFileType k :: Int
k) = Int
k
toEnum :: Int -> TestFileType
toEnum 0 = TestFileType
TestFileTypeDist
toEnum 1 = TestFileType
TestFileTypeBuilt
toEnum k :: Int
k = Int -> TestFileType
AnotherTestFileType Int
k
instance P.Ord TestFileType where
compare :: TestFileType -> TestFileType -> Ordering
compare a :: TestFileType
a b :: TestFileType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TestFileType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestFileType
a) (TestFileType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestFileType
b)
data SpawnError =
SpawnErrorFork
| SpawnErrorRead
| SpawnErrorChdir
| SpawnErrorAcces
| SpawnErrorPerm
| SpawnErrorTooBig
| SpawnError2big
| SpawnErrorNoexec
| SpawnErrorNametoolong
| SpawnErrorNoent
| SpawnErrorNomem
| SpawnErrorNotdir
| SpawnErrorLoop
| SpawnErrorTxtbusy
| SpawnErrorIo
| SpawnErrorNfile
| SpawnErrorMfile
| SpawnErrorInval
| SpawnErrorIsdir
| SpawnErrorLibbad
| SpawnErrorFailed
| AnotherSpawnError Int
deriving (Int -> SpawnError -> ShowS
[SpawnError] -> ShowS
SpawnError -> String
(Int -> SpawnError -> ShowS)
-> (SpawnError -> String)
-> ([SpawnError] -> ShowS)
-> Show SpawnError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpawnError] -> ShowS
$cshowList :: [SpawnError] -> ShowS
show :: SpawnError -> String
$cshow :: SpawnError -> String
showsPrec :: Int -> SpawnError -> ShowS
$cshowsPrec :: Int -> SpawnError -> ShowS
Show, SpawnError -> SpawnError -> Bool
(SpawnError -> SpawnError -> Bool)
-> (SpawnError -> SpawnError -> Bool) -> Eq SpawnError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpawnError -> SpawnError -> Bool
$c/= :: SpawnError -> SpawnError -> Bool
== :: SpawnError -> SpawnError -> Bool
$c== :: SpawnError -> SpawnError -> Bool
Eq)
instance P.Enum SpawnError where
fromEnum :: SpawnError -> Int
fromEnum SpawnErrorFork = 0
fromEnum SpawnErrorRead = 1
fromEnum SpawnErrorChdir = 2
fromEnum SpawnErrorAcces = 3
fromEnum SpawnErrorPerm = 4
fromEnum SpawnErrorTooBig = 5
fromEnum SpawnError2big = 5
fromEnum SpawnErrorNoexec = 6
fromEnum SpawnErrorNametoolong = 7
fromEnum SpawnErrorNoent = 8
fromEnum SpawnErrorNomem = 9
fromEnum SpawnErrorNotdir = 10
fromEnum SpawnErrorLoop = 11
fromEnum SpawnErrorTxtbusy = 12
fromEnum SpawnErrorIo = 13
fromEnum SpawnErrorNfile = 14
fromEnum SpawnErrorMfile = 15
fromEnum SpawnErrorInval = 16
fromEnum SpawnErrorIsdir = 17
fromEnum SpawnErrorLibbad = 18
fromEnum SpawnErrorFailed = 19
fromEnum (AnotherSpawnError k :: Int
k) = Int
k
toEnum :: Int -> SpawnError
toEnum 0 = SpawnError
SpawnErrorFork
toEnum 1 = SpawnError
SpawnErrorRead
toEnum 2 = SpawnError
SpawnErrorChdir
toEnum 3 = SpawnError
SpawnErrorAcces
toEnum 4 = SpawnError
SpawnErrorPerm
toEnum 5 = SpawnError
SpawnErrorTooBig
toEnum 6 = SpawnError
SpawnErrorNoexec
toEnum 7 = SpawnError
SpawnErrorNametoolong
toEnum 8 = SpawnError
SpawnErrorNoent
toEnum 9 = SpawnError
SpawnErrorNomem
toEnum 10 = SpawnError
SpawnErrorNotdir
toEnum 11 = SpawnError
SpawnErrorLoop
toEnum 12 = SpawnError
SpawnErrorTxtbusy
toEnum 13 = SpawnError
SpawnErrorIo
toEnum 14 = SpawnError
SpawnErrorNfile
toEnum 15 = SpawnError
SpawnErrorMfile
toEnum 16 = SpawnError
SpawnErrorInval
toEnum 17 = SpawnError
SpawnErrorIsdir
toEnum 18 = SpawnError
SpawnErrorLibbad
toEnum 19 = SpawnError
SpawnErrorFailed
toEnum k :: Int
k = Int -> SpawnError
AnotherSpawnError Int
k
instance P.Ord SpawnError where
compare :: SpawnError -> SpawnError -> Ordering
compare a :: SpawnError
a b :: SpawnError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SpawnError -> Int
forall a. Enum a => a -> Int
P.fromEnum SpawnError
a) (SpawnError -> Int
forall a. Enum a => a -> Int
P.fromEnum SpawnError
b)
instance GErrorClass SpawnError where
gerrorClassDomain :: SpawnError -> Text
gerrorClassDomain _ = "g-exec-error-quark"
catchSpawnError ::
IO a ->
(SpawnError -> GErrorMessage -> IO a) ->
IO a
catchSpawnError :: IO a -> (SpawnError -> Text -> IO a) -> IO a
catchSpawnError = IO a -> (SpawnError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleSpawnError ::
(SpawnError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleSpawnError :: (SpawnError -> Text -> IO a) -> IO a -> IO a
handleSpawnError = (SpawnError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data SliceConfig =
SliceConfigAlwaysMalloc
| SliceConfigBypassMagazines
| SliceConfigWorkingSetMsecs
| SliceConfigColorIncrement
| SliceConfigChunkSizes
| SliceConfigContentionCounter
| AnotherSliceConfig Int
deriving (Int -> SliceConfig -> ShowS
[SliceConfig] -> ShowS
SliceConfig -> String
(Int -> SliceConfig -> ShowS)
-> (SliceConfig -> String)
-> ([SliceConfig] -> ShowS)
-> Show SliceConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SliceConfig] -> ShowS
$cshowList :: [SliceConfig] -> ShowS
show :: SliceConfig -> String
$cshow :: SliceConfig -> String
showsPrec :: Int -> SliceConfig -> ShowS
$cshowsPrec :: Int -> SliceConfig -> ShowS
Show, SliceConfig -> SliceConfig -> Bool
(SliceConfig -> SliceConfig -> Bool)
-> (SliceConfig -> SliceConfig -> Bool) -> Eq SliceConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SliceConfig -> SliceConfig -> Bool
$c/= :: SliceConfig -> SliceConfig -> Bool
== :: SliceConfig -> SliceConfig -> Bool
$c== :: SliceConfig -> SliceConfig -> Bool
Eq)
instance P.Enum SliceConfig where
fromEnum :: SliceConfig -> Int
fromEnum SliceConfigAlwaysMalloc = 1
fromEnum SliceConfigBypassMagazines = 2
fromEnum SliceConfigWorkingSetMsecs = 3
fromEnum SliceConfigColorIncrement = 4
fromEnum SliceConfigChunkSizes = 5
fromEnum SliceConfigContentionCounter = 6
fromEnum (AnotherSliceConfig k :: Int
k) = Int
k
toEnum :: Int -> SliceConfig
toEnum 1 = SliceConfig
SliceConfigAlwaysMalloc
toEnum 2 = SliceConfig
SliceConfigBypassMagazines
toEnum 3 = SliceConfig
SliceConfigWorkingSetMsecs
toEnum 4 = SliceConfig
SliceConfigColorIncrement
toEnum 5 = SliceConfig
SliceConfigChunkSizes
toEnum 6 = SliceConfig
SliceConfigContentionCounter
toEnum k :: Int
k = Int -> SliceConfig
AnotherSliceConfig Int
k
instance P.Ord SliceConfig where
compare :: SliceConfig -> SliceConfig -> Ordering
compare a :: SliceConfig
a b :: SliceConfig
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SliceConfig -> Int
forall a. Enum a => a -> Int
P.fromEnum SliceConfig
a) (SliceConfig -> Int
forall a. Enum a => a -> Int
P.fromEnum SliceConfig
b)
data ShellError =
ShellErrorBadQuoting
| ShellErrorEmptyString
| ShellErrorFailed
| AnotherShellError Int
deriving (Int -> ShellError -> ShowS
[ShellError] -> ShowS
ShellError -> String
(Int -> ShellError -> ShowS)
-> (ShellError -> String)
-> ([ShellError] -> ShowS)
-> Show ShellError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShellError] -> ShowS
$cshowList :: [ShellError] -> ShowS
show :: ShellError -> String
$cshow :: ShellError -> String
showsPrec :: Int -> ShellError -> ShowS
$cshowsPrec :: Int -> ShellError -> ShowS
Show, ShellError -> ShellError -> Bool
(ShellError -> ShellError -> Bool)
-> (ShellError -> ShellError -> Bool) -> Eq ShellError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShellError -> ShellError -> Bool
$c/= :: ShellError -> ShellError -> Bool
== :: ShellError -> ShellError -> Bool
$c== :: ShellError -> ShellError -> Bool
Eq)
instance P.Enum ShellError where
fromEnum :: ShellError -> Int
fromEnum ShellErrorBadQuoting = 0
fromEnum ShellErrorEmptyString = 1
fromEnum ShellErrorFailed = 2
fromEnum (AnotherShellError k :: Int
k) = Int
k
toEnum :: Int -> ShellError
toEnum 0 = ShellError
ShellErrorBadQuoting
toEnum 1 = ShellError
ShellErrorEmptyString
toEnum 2 = ShellError
ShellErrorFailed
toEnum k :: Int
k = Int -> ShellError
AnotherShellError Int
k
instance P.Ord ShellError where
compare :: ShellError -> ShellError -> Ordering
compare a :: ShellError
a b :: ShellError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ShellError -> Int
forall a. Enum a => a -> Int
P.fromEnum ShellError
a) (ShellError -> Int
forall a. Enum a => a -> Int
P.fromEnum ShellError
b)
instance GErrorClass ShellError where
gerrorClassDomain :: ShellError -> Text
gerrorClassDomain _ = "g-shell-error-quark"
catchShellError ::
IO a ->
(ShellError -> GErrorMessage -> IO a) ->
IO a
catchShellError :: IO a -> (ShellError -> Text -> IO a) -> IO a
catchShellError = IO a -> (ShellError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleShellError ::
(ShellError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleShellError :: (ShellError -> Text -> IO a) -> IO a -> IO a
handleShellError = (ShellError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data SeekType =
SeekTypeCur
| SeekTypeSet
| SeekTypeEnd
| AnotherSeekType Int
deriving (Int -> SeekType -> ShowS
[SeekType] -> ShowS
SeekType -> String
(Int -> SeekType -> ShowS)
-> (SeekType -> String) -> ([SeekType] -> ShowS) -> Show SeekType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SeekType] -> ShowS
$cshowList :: [SeekType] -> ShowS
show :: SeekType -> String
$cshow :: SeekType -> String
showsPrec :: Int -> SeekType -> ShowS
$cshowsPrec :: Int -> SeekType -> ShowS
Show, SeekType -> SeekType -> Bool
(SeekType -> SeekType -> Bool)
-> (SeekType -> SeekType -> Bool) -> Eq SeekType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SeekType -> SeekType -> Bool
$c/= :: SeekType -> SeekType -> Bool
== :: SeekType -> SeekType -> Bool
$c== :: SeekType -> SeekType -> Bool
Eq)
instance P.Enum SeekType where
fromEnum :: SeekType -> Int
fromEnum SeekTypeCur = 0
fromEnum SeekTypeSet = 1
fromEnum SeekTypeEnd = 2
fromEnum (AnotherSeekType k :: Int
k) = Int
k
toEnum :: Int -> SeekType
toEnum 0 = SeekType
SeekTypeCur
toEnum 1 = SeekType
SeekTypeSet
toEnum 2 = SeekType
SeekTypeEnd
toEnum k :: Int
k = Int -> SeekType
AnotherSeekType Int
k
instance P.Ord SeekType where
compare :: SeekType -> SeekType -> Ordering
compare a :: SeekType
a b :: SeekType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SeekType -> Int
forall a. Enum a => a -> Int
P.fromEnum SeekType
a) (SeekType -> Int
forall a. Enum a => a -> Int
P.fromEnum SeekType
b)
data RegexError =
RegexErrorCompile
| RegexErrorOptimize
| RegexErrorReplace
| RegexErrorMatch
| RegexErrorInternal
| RegexErrorStrayBackslash
| RegexErrorMissingControlChar
| RegexErrorUnrecognizedEscape
| RegexErrorQuantifiersOutOfOrder
| RegexErrorQuantifierTooBig
| RegexErrorUnterminatedCharacterClass
| RegexErrorInvalidEscapeInCharacterClass
| RegexErrorRangeOutOfOrder
| RegexErrorNothingToRepeat
| RegexErrorUnrecognizedCharacter
| RegexErrorPosixNamedClassOutsideClass
| RegexErrorUnmatchedParenthesis
| RegexErrorInexistentSubpatternReference
|
| RegexErrorExpressionTooLarge
| RegexErrorMemoryError
| RegexErrorVariableLengthLookbehind
| RegexErrorMalformedCondition
| RegexErrorTooManyConditionalBranches
| RegexErrorAssertionExpected
| RegexErrorUnknownPosixClassName
| RegexErrorPosixCollatingElementsNotSupported
| RegexErrorHexCodeTooLarge
| RegexErrorInvalidCondition
| RegexErrorSingleByteMatchInLookbehind
| RegexErrorInfiniteLoop
| RegexErrorMissingSubpatternNameTerminator
| RegexErrorDuplicateSubpatternName
| RegexErrorMalformedProperty
| RegexErrorUnknownProperty
| RegexErrorSubpatternNameTooLong
| RegexErrorTooManySubpatterns
| RegexErrorInvalidOctalValue
| RegexErrorTooManyBranchesInDefine
| RegexErrorDefineRepetion
| RegexErrorInconsistentNewlineOptions
| RegexErrorMissingBackReference
| RegexErrorInvalidRelativeReference
| RegexErrorBacktrackingControlVerbArgumentForbidden
| RegexErrorUnknownBacktrackingControlVerb
| RegexErrorNumberTooBig
| RegexErrorMissingSubpatternName
| RegexErrorMissingDigit
| RegexErrorInvalidDataCharacter
|
| RegexErrorBacktrackingControlVerbArgumentRequired
| RegexErrorInvalidControlChar
| RegexErrorMissingName
| RegexErrorNotSupportedInClass
| RegexErrorTooManyForwardReferences
| RegexErrorNameTooLong
| RegexErrorCharacterValueTooLarge
| AnotherRegexError Int
deriving (Int -> RegexError -> ShowS
[RegexError] -> ShowS
RegexError -> String
(Int -> RegexError -> ShowS)
-> (RegexError -> String)
-> ([RegexError] -> ShowS)
-> Show RegexError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegexError] -> ShowS
$cshowList :: [RegexError] -> ShowS
show :: RegexError -> String
$cshow :: RegexError -> String
showsPrec :: Int -> RegexError -> ShowS
$cshowsPrec :: Int -> RegexError -> ShowS
Show, RegexError -> RegexError -> Bool
(RegexError -> RegexError -> Bool)
-> (RegexError -> RegexError -> Bool) -> Eq RegexError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegexError -> RegexError -> Bool
$c/= :: RegexError -> RegexError -> Bool
== :: RegexError -> RegexError -> Bool
$c== :: RegexError -> RegexError -> Bool
Eq)
instance P.Enum RegexError where
fromEnum :: RegexError -> Int
fromEnum RegexErrorCompile = 0
fromEnum RegexErrorOptimize = 1
fromEnum RegexErrorReplace = 2
fromEnum RegexErrorMatch = 3
fromEnum RegexErrorInternal = 4
fromEnum RegexErrorStrayBackslash = 101
fromEnum RegexErrorMissingControlChar = 102
fromEnum RegexErrorUnrecognizedEscape = 103
fromEnum RegexErrorQuantifiersOutOfOrder = 104
fromEnum RegexErrorQuantifierTooBig = 105
fromEnum RegexErrorUnterminatedCharacterClass = 106
fromEnum RegexErrorInvalidEscapeInCharacterClass = 107
fromEnum RegexErrorRangeOutOfOrder = 108
fromEnum RegexErrorNothingToRepeat = 109
fromEnum RegexErrorUnrecognizedCharacter = 112
fromEnum RegexErrorPosixNamedClassOutsideClass = 113
fromEnum RegexErrorUnmatchedParenthesis = 114
fromEnum RegexErrorInexistentSubpatternReference = 115
fromEnum RegexErrorUnterminatedComment = 118
fromEnum RegexErrorExpressionTooLarge = 120
fromEnum RegexErrorMemoryError = 121
fromEnum RegexErrorVariableLengthLookbehind = 125
fromEnum RegexErrorMalformedCondition = 126
fromEnum RegexErrorTooManyConditionalBranches = 127
fromEnum RegexErrorAssertionExpected = 128
fromEnum RegexErrorUnknownPosixClassName = 130
fromEnum RegexErrorPosixCollatingElementsNotSupported = 131
fromEnum RegexErrorHexCodeTooLarge = 134
fromEnum RegexErrorInvalidCondition = 135
fromEnum RegexErrorSingleByteMatchInLookbehind = 136
fromEnum RegexErrorInfiniteLoop = 140
fromEnum RegexErrorMissingSubpatternNameTerminator = 142
fromEnum RegexErrorDuplicateSubpatternName = 143
fromEnum RegexErrorMalformedProperty = 146
fromEnum RegexErrorUnknownProperty = 147
fromEnum RegexErrorSubpatternNameTooLong = 148
fromEnum RegexErrorTooManySubpatterns = 149
fromEnum RegexErrorInvalidOctalValue = 151
fromEnum RegexErrorTooManyBranchesInDefine = 154
fromEnum RegexErrorDefineRepetion = 155
fromEnum RegexErrorInconsistentNewlineOptions = 156
fromEnum RegexErrorMissingBackReference = 157
fromEnum RegexErrorInvalidRelativeReference = 158
fromEnum RegexErrorBacktrackingControlVerbArgumentForbidden = 159
fromEnum RegexErrorUnknownBacktrackingControlVerb = 160
fromEnum RegexErrorNumberTooBig = 161
fromEnum RegexErrorMissingSubpatternName = 162
fromEnum RegexErrorMissingDigit = 163
fromEnum RegexErrorInvalidDataCharacter = 164
fromEnum RegexErrorExtraSubpatternName = 165
fromEnum RegexErrorBacktrackingControlVerbArgumentRequired = 166
fromEnum RegexErrorInvalidControlChar = 168
fromEnum RegexErrorMissingName = 169
fromEnum RegexErrorNotSupportedInClass = 171
fromEnum RegexErrorTooManyForwardReferences = 172
fromEnum RegexErrorNameTooLong = 175
fromEnum RegexErrorCharacterValueTooLarge = 176
fromEnum (AnotherRegexError k :: Int
k) = Int
k
toEnum :: Int -> RegexError
toEnum 0 = RegexError
RegexErrorCompile
toEnum 1 = RegexError
RegexErrorOptimize
toEnum 2 = RegexError
RegexErrorReplace
toEnum 3 = RegexError
RegexErrorMatch
toEnum 4 = RegexError
RegexErrorInternal
toEnum 101 = RegexError
RegexErrorStrayBackslash
toEnum 102 = RegexError
RegexErrorMissingControlChar
toEnum 103 = RegexError
RegexErrorUnrecognizedEscape
toEnum 104 = RegexError
RegexErrorQuantifiersOutOfOrder
toEnum 105 = RegexError
RegexErrorQuantifierTooBig
toEnum 106 = RegexError
RegexErrorUnterminatedCharacterClass
toEnum 107 = RegexError
RegexErrorInvalidEscapeInCharacterClass
toEnum 108 = RegexError
RegexErrorRangeOutOfOrder
toEnum 109 = RegexError
RegexErrorNothingToRepeat
toEnum 112 = RegexError
RegexErrorUnrecognizedCharacter
toEnum 113 = RegexError
RegexErrorPosixNamedClassOutsideClass
toEnum 114 = RegexError
RegexErrorUnmatchedParenthesis
toEnum 115 = RegexError
RegexErrorInexistentSubpatternReference
toEnum 118 = RegexError
RegexErrorUnterminatedComment
toEnum 120 = RegexError
RegexErrorExpressionTooLarge
toEnum 121 = RegexError
RegexErrorMemoryError
toEnum 125 = RegexError
RegexErrorVariableLengthLookbehind
toEnum 126 = RegexError
RegexErrorMalformedCondition
toEnum 127 = RegexError
RegexErrorTooManyConditionalBranches
toEnum 128 = RegexError
RegexErrorAssertionExpected
toEnum 130 = RegexError
RegexErrorUnknownPosixClassName
toEnum 131 = RegexError
RegexErrorPosixCollatingElementsNotSupported
toEnum 134 = RegexError
RegexErrorHexCodeTooLarge
toEnum 135 = RegexError
RegexErrorInvalidCondition
toEnum 136 = RegexError
RegexErrorSingleByteMatchInLookbehind
toEnum 140 = RegexError
RegexErrorInfiniteLoop
toEnum 142 = RegexError
RegexErrorMissingSubpatternNameTerminator
toEnum 143 = RegexError
RegexErrorDuplicateSubpatternName
toEnum 146 = RegexError
RegexErrorMalformedProperty
toEnum 147 = RegexError
RegexErrorUnknownProperty
toEnum 148 = RegexError
RegexErrorSubpatternNameTooLong
toEnum 149 = RegexError
RegexErrorTooManySubpatterns
toEnum 151 = RegexError
RegexErrorInvalidOctalValue
toEnum 154 = RegexError
RegexErrorTooManyBranchesInDefine
toEnum 155 = RegexError
RegexErrorDefineRepetion
toEnum 156 = RegexError
RegexErrorInconsistentNewlineOptions
toEnum 157 = RegexError
RegexErrorMissingBackReference
toEnum 158 = RegexError
RegexErrorInvalidRelativeReference
toEnum 159 = RegexError
RegexErrorBacktrackingControlVerbArgumentForbidden
toEnum 160 = RegexError
RegexErrorUnknownBacktrackingControlVerb
toEnum 161 = RegexError
RegexErrorNumberTooBig
toEnum 162 = RegexError
RegexErrorMissingSubpatternName
toEnum 163 = RegexError
RegexErrorMissingDigit
toEnum 164 = RegexError
RegexErrorInvalidDataCharacter
toEnum 165 = RegexError
RegexErrorExtraSubpatternName
toEnum 166 = RegexError
RegexErrorBacktrackingControlVerbArgumentRequired
toEnum 168 = RegexError
RegexErrorInvalidControlChar
toEnum 169 = RegexError
RegexErrorMissingName
toEnum 171 = RegexError
RegexErrorNotSupportedInClass
toEnum 172 = RegexError
RegexErrorTooManyForwardReferences
toEnum 175 = RegexError
RegexErrorNameTooLong
toEnum 176 = RegexError
RegexErrorCharacterValueTooLarge
toEnum k :: Int
k = Int -> RegexError
AnotherRegexError Int
k
instance P.Ord RegexError where
compare :: RegexError -> RegexError -> Ordering
compare a :: RegexError
a b :: RegexError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (RegexError -> Int
forall a. Enum a => a -> Int
P.fromEnum RegexError
a) (RegexError -> Int
forall a. Enum a => a -> Int
P.fromEnum RegexError
b)
instance GErrorClass RegexError where
gerrorClassDomain :: RegexError -> Text
gerrorClassDomain _ = "g-regex-error-quark"
catchRegexError ::
IO a ->
(RegexError -> GErrorMessage -> IO a) ->
IO a
catchRegexError :: IO a -> (RegexError -> Text -> IO a) -> IO a
catchRegexError = IO a -> (RegexError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleRegexError ::
(RegexError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleRegexError :: (RegexError -> Text -> IO a) -> IO a -> IO a
handleRegexError = (RegexError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data OptionError =
OptionErrorUnknownOption
| OptionErrorBadValue
| OptionErrorFailed
| AnotherOptionError Int
deriving (Int -> OptionError -> ShowS
[OptionError] -> ShowS
OptionError -> String
(Int -> OptionError -> ShowS)
-> (OptionError -> String)
-> ([OptionError] -> ShowS)
-> Show OptionError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionError] -> ShowS
$cshowList :: [OptionError] -> ShowS
show :: OptionError -> String
$cshow :: OptionError -> String
showsPrec :: Int -> OptionError -> ShowS
$cshowsPrec :: Int -> OptionError -> ShowS
Show, OptionError -> OptionError -> Bool
(OptionError -> OptionError -> Bool)
-> (OptionError -> OptionError -> Bool) -> Eq OptionError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionError -> OptionError -> Bool
$c/= :: OptionError -> OptionError -> Bool
== :: OptionError -> OptionError -> Bool
$c== :: OptionError -> OptionError -> Bool
Eq)
instance P.Enum OptionError where
fromEnum :: OptionError -> Int
fromEnum OptionErrorUnknownOption = 0
fromEnum OptionErrorBadValue = 1
fromEnum OptionErrorFailed = 2
fromEnum (AnotherOptionError k :: Int
k) = Int
k
toEnum :: Int -> OptionError
toEnum 0 = OptionError
OptionErrorUnknownOption
toEnum 1 = OptionError
OptionErrorBadValue
toEnum 2 = OptionError
OptionErrorFailed
toEnum k :: Int
k = Int -> OptionError
AnotherOptionError Int
k
instance P.Ord OptionError where
compare :: OptionError -> OptionError -> Ordering
compare a :: OptionError
a b :: OptionError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (OptionError -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionError
a) (OptionError -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionError
b)
instance GErrorClass OptionError where
gerrorClassDomain :: OptionError -> Text
gerrorClassDomain _ = "g-option-context-error-quark"
catchOptionError ::
IO a ->
(OptionError -> GErrorMessage -> IO a) ->
IO a
catchOptionError :: IO a -> (OptionError -> Text -> IO a) -> IO a
catchOptionError = IO a -> (OptionError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleOptionError ::
(OptionError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleOptionError :: (OptionError -> Text -> IO a) -> IO a -> IO a
handleOptionError = (OptionError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data OptionArg =
OptionArgNone
| OptionArgString
| OptionArgInt
| OptionArgCallback
| OptionArgFilename
| OptionArgStringArray
| OptionArgFilenameArray
| OptionArgDouble
| OptionArgInt64
| AnotherOptionArg Int
deriving (Int -> OptionArg -> ShowS
[OptionArg] -> ShowS
OptionArg -> String
(Int -> OptionArg -> ShowS)
-> (OptionArg -> String)
-> ([OptionArg] -> ShowS)
-> Show OptionArg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionArg] -> ShowS
$cshowList :: [OptionArg] -> ShowS
show :: OptionArg -> String
$cshow :: OptionArg -> String
showsPrec :: Int -> OptionArg -> ShowS
$cshowsPrec :: Int -> OptionArg -> ShowS
Show, OptionArg -> OptionArg -> Bool
(OptionArg -> OptionArg -> Bool)
-> (OptionArg -> OptionArg -> Bool) -> Eq OptionArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionArg -> OptionArg -> Bool
$c/= :: OptionArg -> OptionArg -> Bool
== :: OptionArg -> OptionArg -> Bool
$c== :: OptionArg -> OptionArg -> Bool
Eq)
instance P.Enum OptionArg where
fromEnum :: OptionArg -> Int
fromEnum OptionArgNone = 0
fromEnum OptionArgString = 1
fromEnum OptionArgInt = 2
fromEnum OptionArgCallback = 3
fromEnum OptionArgFilename = 4
fromEnum OptionArgStringArray = 5
fromEnum OptionArgFilenameArray = 6
fromEnum OptionArgDouble = 7
fromEnum OptionArgInt64 = 8
fromEnum (AnotherOptionArg k :: Int
k) = Int
k
toEnum :: Int -> OptionArg
toEnum 0 = OptionArg
OptionArgNone
toEnum 1 = OptionArg
OptionArgString
toEnum 2 = OptionArg
OptionArgInt
toEnum 3 = OptionArg
OptionArgCallback
toEnum 4 = OptionArg
OptionArgFilename
toEnum 5 = OptionArg
OptionArgStringArray
toEnum 6 = OptionArg
OptionArgFilenameArray
toEnum 7 = OptionArg
OptionArgDouble
toEnum 8 = OptionArg
OptionArgInt64
toEnum k :: Int
k = Int -> OptionArg
AnotherOptionArg Int
k
instance P.Ord OptionArg where
compare :: OptionArg -> OptionArg -> Ordering
compare a :: OptionArg
a b :: OptionArg
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (OptionArg -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionArg
a) (OptionArg -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionArg
b)
data OnceStatus =
OnceStatusNotcalled
| OnceStatusProgress
| OnceStatusReady
| AnotherOnceStatus Int
deriving (Int -> OnceStatus -> ShowS
[OnceStatus] -> ShowS
OnceStatus -> String
(Int -> OnceStatus -> ShowS)
-> (OnceStatus -> String)
-> ([OnceStatus] -> ShowS)
-> Show OnceStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OnceStatus] -> ShowS
$cshowList :: [OnceStatus] -> ShowS
show :: OnceStatus -> String
$cshow :: OnceStatus -> String
showsPrec :: Int -> OnceStatus -> ShowS
$cshowsPrec :: Int -> OnceStatus -> ShowS
Show, OnceStatus -> OnceStatus -> Bool
(OnceStatus -> OnceStatus -> Bool)
-> (OnceStatus -> OnceStatus -> Bool) -> Eq OnceStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OnceStatus -> OnceStatus -> Bool
$c/= :: OnceStatus -> OnceStatus -> Bool
== :: OnceStatus -> OnceStatus -> Bool
$c== :: OnceStatus -> OnceStatus -> Bool
Eq)
instance P.Enum OnceStatus where
fromEnum :: OnceStatus -> Int
fromEnum OnceStatusNotcalled = 0
fromEnum OnceStatusProgress = 1
fromEnum OnceStatusReady = 2
fromEnum (AnotherOnceStatus k :: Int
k) = Int
k
toEnum :: Int -> OnceStatus
toEnum 0 = OnceStatus
OnceStatusNotcalled
toEnum 1 = OnceStatus
OnceStatusProgress
toEnum 2 = OnceStatus
OnceStatusReady
toEnum k :: Int
k = Int -> OnceStatus
AnotherOnceStatus Int
k
instance P.Ord OnceStatus where
compare :: OnceStatus -> OnceStatus -> Ordering
compare a :: OnceStatus
a b :: OnceStatus
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (OnceStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum OnceStatus
a) (OnceStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum OnceStatus
b)
data NumberParserError =
NumberParserErrorInvalid
| NumberParserErrorOutOfBounds
| AnotherNumberParserError Int
deriving (Int -> NumberParserError -> ShowS
[NumberParserError] -> ShowS
NumberParserError -> String
(Int -> NumberParserError -> ShowS)
-> (NumberParserError -> String)
-> ([NumberParserError] -> ShowS)
-> Show NumberParserError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NumberParserError] -> ShowS
$cshowList :: [NumberParserError] -> ShowS
show :: NumberParserError -> String
$cshow :: NumberParserError -> String
showsPrec :: Int -> NumberParserError -> ShowS
$cshowsPrec :: Int -> NumberParserError -> ShowS
Show, NumberParserError -> NumberParserError -> Bool
(NumberParserError -> NumberParserError -> Bool)
-> (NumberParserError -> NumberParserError -> Bool)
-> Eq NumberParserError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumberParserError -> NumberParserError -> Bool
$c/= :: NumberParserError -> NumberParserError -> Bool
== :: NumberParserError -> NumberParserError -> Bool
$c== :: NumberParserError -> NumberParserError -> Bool
Eq)
instance P.Enum NumberParserError where
fromEnum :: NumberParserError -> Int
fromEnum NumberParserErrorInvalid = 0
fromEnum NumberParserErrorOutOfBounds = 1
fromEnum (AnotherNumberParserError k :: Int
k) = Int
k
toEnum :: Int -> NumberParserError
toEnum 0 = NumberParserError
NumberParserErrorInvalid
toEnum 1 = NumberParserError
NumberParserErrorOutOfBounds
toEnum k :: Int
k = Int -> NumberParserError
AnotherNumberParserError Int
k
instance P.Ord NumberParserError where
compare :: NumberParserError -> NumberParserError -> Ordering
compare a :: NumberParserError
a b :: NumberParserError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (NumberParserError -> Int
forall a. Enum a => a -> Int
P.fromEnum NumberParserError
a) (NumberParserError -> Int
forall a. Enum a => a -> Int
P.fromEnum NumberParserError
b)
instance GErrorClass NumberParserError where
gerrorClassDomain :: NumberParserError -> Text
gerrorClassDomain _ = "g-number-parser-error-quark"
catchNumberParserError ::
IO a ->
(NumberParserError -> GErrorMessage -> IO a) ->
IO a
catchNumberParserError :: IO a -> (NumberParserError -> Text -> IO a) -> IO a
catchNumberParserError = IO a -> (NumberParserError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleNumberParserError ::
(NumberParserError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleNumberParserError :: (NumberParserError -> Text -> IO a) -> IO a -> IO a
handleNumberParserError = (NumberParserError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data NormalizeMode =
NormalizeModeDefault
| NormalizeModeNfd
| NormalizeModeDefaultCompose
| NormalizeModeNfc
| NormalizeModeAll
| NormalizeModeNfkd
| NormalizeModeAllCompose
| NormalizeModeNfkc
| AnotherNormalizeMode Int
deriving (Int -> NormalizeMode -> ShowS
[NormalizeMode] -> ShowS
NormalizeMode -> String
(Int -> NormalizeMode -> ShowS)
-> (NormalizeMode -> String)
-> ([NormalizeMode] -> ShowS)
-> Show NormalizeMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NormalizeMode] -> ShowS
$cshowList :: [NormalizeMode] -> ShowS
show :: NormalizeMode -> String
$cshow :: NormalizeMode -> String
showsPrec :: Int -> NormalizeMode -> ShowS
$cshowsPrec :: Int -> NormalizeMode -> ShowS
Show, NormalizeMode -> NormalizeMode -> Bool
(NormalizeMode -> NormalizeMode -> Bool)
-> (NormalizeMode -> NormalizeMode -> Bool) -> Eq NormalizeMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalizeMode -> NormalizeMode -> Bool
$c/= :: NormalizeMode -> NormalizeMode -> Bool
== :: NormalizeMode -> NormalizeMode -> Bool
$c== :: NormalizeMode -> NormalizeMode -> Bool
Eq)
instance P.Enum NormalizeMode where
fromEnum :: NormalizeMode -> Int
fromEnum NormalizeModeDefault = 0
fromEnum NormalizeModeNfd = 0
fromEnum NormalizeModeDefaultCompose = 1
fromEnum NormalizeModeNfc = 1
fromEnum NormalizeModeAll = 2
fromEnum NormalizeModeNfkd = 2
fromEnum NormalizeModeAllCompose = 3
fromEnum NormalizeModeNfkc = 3
fromEnum (AnotherNormalizeMode k :: Int
k) = Int
k
toEnum :: Int -> NormalizeMode
toEnum 0 = NormalizeMode
NormalizeModeDefault
toEnum 1 = NormalizeMode
NormalizeModeDefaultCompose
toEnum 2 = NormalizeMode
NormalizeModeAll
toEnum 3 = NormalizeMode
NormalizeModeAllCompose
toEnum k :: Int
k = Int -> NormalizeMode
AnotherNormalizeMode Int
k
instance P.Ord NormalizeMode where
compare :: NormalizeMode -> NormalizeMode -> Ordering
compare a :: NormalizeMode
a b :: NormalizeMode
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (NormalizeMode -> Int
forall a. Enum a => a -> Int
P.fromEnum NormalizeMode
a) (NormalizeMode -> Int
forall a. Enum a => a -> Int
P.fromEnum NormalizeMode
b)
data MarkupError =
MarkupErrorBadUtf8
| MarkupErrorEmpty
| MarkupErrorParse
| MarkupErrorUnknownElement
| MarkupErrorUnknownAttribute
| MarkupErrorInvalidContent
| MarkupErrorMissingAttribute
| AnotherMarkupError Int
deriving (Int -> MarkupError -> ShowS
[MarkupError] -> ShowS
MarkupError -> String
(Int -> MarkupError -> ShowS)
-> (MarkupError -> String)
-> ([MarkupError] -> ShowS)
-> Show MarkupError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MarkupError] -> ShowS
$cshowList :: [MarkupError] -> ShowS
show :: MarkupError -> String
$cshow :: MarkupError -> String
showsPrec :: Int -> MarkupError -> ShowS
$cshowsPrec :: Int -> MarkupError -> ShowS
Show, MarkupError -> MarkupError -> Bool
(MarkupError -> MarkupError -> Bool)
-> (MarkupError -> MarkupError -> Bool) -> Eq MarkupError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkupError -> MarkupError -> Bool
$c/= :: MarkupError -> MarkupError -> Bool
== :: MarkupError -> MarkupError -> Bool
$c== :: MarkupError -> MarkupError -> Bool
Eq)
instance P.Enum MarkupError where
fromEnum :: MarkupError -> Int
fromEnum MarkupErrorBadUtf8 = 0
fromEnum MarkupErrorEmpty = 1
fromEnum MarkupErrorParse = 2
fromEnum MarkupErrorUnknownElement = 3
fromEnum MarkupErrorUnknownAttribute = 4
fromEnum MarkupErrorInvalidContent = 5
fromEnum MarkupErrorMissingAttribute = 6
fromEnum (AnotherMarkupError k :: Int
k) = Int
k
toEnum :: Int -> MarkupError
toEnum 0 = MarkupError
MarkupErrorBadUtf8
toEnum 1 = MarkupError
MarkupErrorEmpty
toEnum 2 = MarkupError
MarkupErrorParse
toEnum 3 = MarkupError
MarkupErrorUnknownElement
toEnum 4 = MarkupError
MarkupErrorUnknownAttribute
toEnum 5 = MarkupError
MarkupErrorInvalidContent
toEnum 6 = MarkupError
MarkupErrorMissingAttribute
toEnum k :: Int
k = Int -> MarkupError
AnotherMarkupError Int
k
instance P.Ord MarkupError where
compare :: MarkupError -> MarkupError -> Ordering
compare a :: MarkupError
a b :: MarkupError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (MarkupError -> Int
forall a. Enum a => a -> Int
P.fromEnum MarkupError
a) (MarkupError -> Int
forall a. Enum a => a -> Int
P.fromEnum MarkupError
b)
instance GErrorClass MarkupError where
gerrorClassDomain :: MarkupError -> Text
gerrorClassDomain _ = "g-markup-error-quark"
catchMarkupError ::
IO a ->
(MarkupError -> GErrorMessage -> IO a) ->
IO a
catchMarkupError :: IO a -> (MarkupError -> Text -> IO a) -> IO a
catchMarkupError = IO a -> (MarkupError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleMarkupError ::
(MarkupError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleMarkupError :: (MarkupError -> Text -> IO a) -> IO a -> IO a
handleMarkupError = (MarkupError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data LogWriterOutput =
LogWriterOutputHandled
| LogWriterOutputUnhandled
| AnotherLogWriterOutput Int
deriving (Int -> LogWriterOutput -> ShowS
[LogWriterOutput] -> ShowS
LogWriterOutput -> String
(Int -> LogWriterOutput -> ShowS)
-> (LogWriterOutput -> String)
-> ([LogWriterOutput] -> ShowS)
-> Show LogWriterOutput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogWriterOutput] -> ShowS
$cshowList :: [LogWriterOutput] -> ShowS
show :: LogWriterOutput -> String
$cshow :: LogWriterOutput -> String
showsPrec :: Int -> LogWriterOutput -> ShowS
$cshowsPrec :: Int -> LogWriterOutput -> ShowS
Show, LogWriterOutput -> LogWriterOutput -> Bool
(LogWriterOutput -> LogWriterOutput -> Bool)
-> (LogWriterOutput -> LogWriterOutput -> Bool)
-> Eq LogWriterOutput
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogWriterOutput -> LogWriterOutput -> Bool
$c/= :: LogWriterOutput -> LogWriterOutput -> Bool
== :: LogWriterOutput -> LogWriterOutput -> Bool
$c== :: LogWriterOutput -> LogWriterOutput -> Bool
Eq)
instance P.Enum LogWriterOutput where
fromEnum :: LogWriterOutput -> Int
fromEnum LogWriterOutputHandled = 1
fromEnum LogWriterOutputUnhandled = 0
fromEnum (AnotherLogWriterOutput k :: Int
k) = Int
k
toEnum :: Int -> LogWriterOutput
toEnum 1 = LogWriterOutput
LogWriterOutputHandled
toEnum 0 = LogWriterOutput
LogWriterOutputUnhandled
toEnum k :: Int
k = Int -> LogWriterOutput
AnotherLogWriterOutput Int
k
instance P.Ord LogWriterOutput where
compare :: LogWriterOutput -> LogWriterOutput -> Ordering
compare a :: LogWriterOutput
a b :: LogWriterOutput
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (LogWriterOutput -> Int
forall a. Enum a => a -> Int
P.fromEnum LogWriterOutput
a) (LogWriterOutput -> Int
forall a. Enum a => a -> Int
P.fromEnum LogWriterOutput
b)
data KeyFileError =
KeyFileErrorUnknownEncoding
| KeyFileErrorParse
| KeyFileErrorNotFound
| KeyFileErrorKeyNotFound
| KeyFileErrorGroupNotFound
| KeyFileErrorInvalidValue
| AnotherKeyFileError Int
deriving (Int -> KeyFileError -> ShowS
[KeyFileError] -> ShowS
KeyFileError -> String
(Int -> KeyFileError -> ShowS)
-> (KeyFileError -> String)
-> ([KeyFileError] -> ShowS)
-> Show KeyFileError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyFileError] -> ShowS
$cshowList :: [KeyFileError] -> ShowS
show :: KeyFileError -> String
$cshow :: KeyFileError -> String
showsPrec :: Int -> KeyFileError -> ShowS
$cshowsPrec :: Int -> KeyFileError -> ShowS
Show, KeyFileError -> KeyFileError -> Bool
(KeyFileError -> KeyFileError -> Bool)
-> (KeyFileError -> KeyFileError -> Bool) -> Eq KeyFileError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyFileError -> KeyFileError -> Bool
$c/= :: KeyFileError -> KeyFileError -> Bool
== :: KeyFileError -> KeyFileError -> Bool
$c== :: KeyFileError -> KeyFileError -> Bool
Eq)
instance P.Enum KeyFileError where
fromEnum :: KeyFileError -> Int
fromEnum KeyFileErrorUnknownEncoding = 0
fromEnum KeyFileErrorParse = 1
fromEnum KeyFileErrorNotFound = 2
fromEnum KeyFileErrorKeyNotFound = 3
fromEnum KeyFileErrorGroupNotFound = 4
fromEnum KeyFileErrorInvalidValue = 5
fromEnum (AnotherKeyFileError k :: Int
k) = Int
k
toEnum :: Int -> KeyFileError
toEnum 0 = KeyFileError
KeyFileErrorUnknownEncoding
toEnum 1 = KeyFileError
KeyFileErrorParse
toEnum 2 = KeyFileError
KeyFileErrorNotFound
toEnum 3 = KeyFileError
KeyFileErrorKeyNotFound
toEnum 4 = KeyFileError
KeyFileErrorGroupNotFound
toEnum 5 = KeyFileError
KeyFileErrorInvalidValue
toEnum k :: Int
k = Int -> KeyFileError
AnotherKeyFileError Int
k
instance P.Ord KeyFileError where
compare :: KeyFileError -> KeyFileError -> Ordering
compare a :: KeyFileError
a b :: KeyFileError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (KeyFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum KeyFileError
a) (KeyFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum KeyFileError
b)
instance GErrorClass KeyFileError where
gerrorClassDomain :: KeyFileError -> Text
gerrorClassDomain _ = "g-key-file-error-quark"
catchKeyFileError ::
IO a ->
(KeyFileError -> GErrorMessage -> IO a) ->
IO a
catchKeyFileError :: IO a -> (KeyFileError -> Text -> IO a) -> IO a
catchKeyFileError = IO a -> (KeyFileError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleKeyFileError ::
(KeyFileError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleKeyFileError :: (KeyFileError -> Text -> IO a) -> IO a -> IO a
handleKeyFileError = (KeyFileError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data IOStatus =
IOStatusError
| IOStatusNormal
| IOStatusEof
| IOStatusAgain
| AnotherIOStatus Int
deriving (Int -> IOStatus -> ShowS
[IOStatus] -> ShowS
IOStatus -> String
(Int -> IOStatus -> ShowS)
-> (IOStatus -> String) -> ([IOStatus] -> ShowS) -> Show IOStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IOStatus] -> ShowS
$cshowList :: [IOStatus] -> ShowS
show :: IOStatus -> String
$cshow :: IOStatus -> String
showsPrec :: Int -> IOStatus -> ShowS
$cshowsPrec :: Int -> IOStatus -> ShowS
Show, IOStatus -> IOStatus -> Bool
(IOStatus -> IOStatus -> Bool)
-> (IOStatus -> IOStatus -> Bool) -> Eq IOStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOStatus -> IOStatus -> Bool
$c/= :: IOStatus -> IOStatus -> Bool
== :: IOStatus -> IOStatus -> Bool
$c== :: IOStatus -> IOStatus -> Bool
Eq)
instance P.Enum IOStatus where
fromEnum :: IOStatus -> Int
fromEnum IOStatusError = 0
fromEnum IOStatusNormal = 1
fromEnum IOStatusEof = 2
fromEnum IOStatusAgain = 3
fromEnum (AnotherIOStatus k :: Int
k) = Int
k
toEnum :: Int -> IOStatus
toEnum 0 = IOStatus
IOStatusError
toEnum 1 = IOStatus
IOStatusNormal
toEnum 2 = IOStatus
IOStatusEof
toEnum 3 = IOStatus
IOStatusAgain
toEnum k :: Int
k = Int -> IOStatus
AnotherIOStatus Int
k
instance P.Ord IOStatus where
compare :: IOStatus -> IOStatus -> Ordering
compare a :: IOStatus
a b :: IOStatus
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum IOStatus
a) (IOStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum IOStatus
b)
data IOError =
IOErrorNone
| IOErrorAgain
| IOErrorInval
| IOErrorUnknown
| AnotherIOError Int
deriving (Int -> IOError -> ShowS
[IOError] -> ShowS
IOError -> String
(Int -> IOError -> ShowS)
-> (IOError -> String) -> ([IOError] -> ShowS) -> Show IOError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IOError] -> ShowS
$cshowList :: [IOError] -> ShowS
show :: IOError -> String
$cshow :: IOError -> String
showsPrec :: Int -> IOError -> ShowS
$cshowsPrec :: Int -> IOError -> ShowS
Show, IOError -> IOError -> Bool
(IOError -> IOError -> Bool)
-> (IOError -> IOError -> Bool) -> Eq IOError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOError -> IOError -> Bool
$c/= :: IOError -> IOError -> Bool
== :: IOError -> IOError -> Bool
$c== :: IOError -> IOError -> Bool
Eq)
instance P.Enum IOError where
fromEnum :: IOError -> Int
fromEnum IOErrorNone = 0
fromEnum IOErrorAgain = 1
fromEnum IOErrorInval = 2
fromEnum IOErrorUnknown = 3
fromEnum (AnotherIOError k :: Int
k) = Int
k
toEnum :: Int -> IOError
toEnum 0 = IOError
IOErrorNone
toEnum 1 = IOError
IOErrorAgain
toEnum 2 = IOError
IOErrorInval
toEnum 3 = IOError
IOErrorUnknown
toEnum k :: Int
k = Int -> IOError
AnotherIOError Int
k
instance P.Ord IOError where
compare :: IOError -> IOError -> Ordering
compare a :: IOError
a b :: IOError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOError
a) (IOError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOError
b)
data IOChannelError =
IOChannelErrorFbig
| IOChannelErrorInval
| IOChannelErrorIo
| IOChannelErrorIsdir
| IOChannelErrorNospc
| IOChannelErrorNxio
| IOChannelErrorOverflow
| IOChannelErrorPipe
| IOChannelErrorFailed
| AnotherIOChannelError Int
deriving (Int -> IOChannelError -> ShowS
[IOChannelError] -> ShowS
IOChannelError -> String
(Int -> IOChannelError -> ShowS)
-> (IOChannelError -> String)
-> ([IOChannelError] -> ShowS)
-> Show IOChannelError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IOChannelError] -> ShowS
$cshowList :: [IOChannelError] -> ShowS
show :: IOChannelError -> String
$cshow :: IOChannelError -> String
showsPrec :: Int -> IOChannelError -> ShowS
$cshowsPrec :: Int -> IOChannelError -> ShowS
Show, IOChannelError -> IOChannelError -> Bool
(IOChannelError -> IOChannelError -> Bool)
-> (IOChannelError -> IOChannelError -> Bool) -> Eq IOChannelError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOChannelError -> IOChannelError -> Bool
$c/= :: IOChannelError -> IOChannelError -> Bool
== :: IOChannelError -> IOChannelError -> Bool
$c== :: IOChannelError -> IOChannelError -> Bool
Eq)
instance P.Enum IOChannelError where
fromEnum :: IOChannelError -> Int
fromEnum IOChannelErrorFbig = 0
fromEnum IOChannelErrorInval = 1
fromEnum IOChannelErrorIo = 2
fromEnum IOChannelErrorIsdir = 3
fromEnum IOChannelErrorNospc = 4
fromEnum IOChannelErrorNxio = 5
fromEnum IOChannelErrorOverflow = 6
fromEnum IOChannelErrorPipe = 7
fromEnum IOChannelErrorFailed = 8
fromEnum (AnotherIOChannelError k :: Int
k) = Int
k
toEnum :: Int -> IOChannelError
toEnum 0 = IOChannelError
IOChannelErrorFbig
toEnum 1 = IOChannelError
IOChannelErrorInval
toEnum 2 = IOChannelError
IOChannelErrorIo
toEnum 3 = IOChannelError
IOChannelErrorIsdir
toEnum 4 = IOChannelError
IOChannelErrorNospc
toEnum 5 = IOChannelError
IOChannelErrorNxio
toEnum 6 = IOChannelError
IOChannelErrorOverflow
toEnum 7 = IOChannelError
IOChannelErrorPipe
toEnum 8 = IOChannelError
IOChannelErrorFailed
toEnum k :: Int
k = Int -> IOChannelError
AnotherIOChannelError Int
k
instance P.Ord IOChannelError where
compare :: IOChannelError -> IOChannelError -> Ordering
compare a :: IOChannelError
a b :: IOChannelError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOChannelError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOChannelError
a) (IOChannelError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOChannelError
b)
instance GErrorClass IOChannelError where
gerrorClassDomain :: IOChannelError -> Text
gerrorClassDomain _ = "g-io-channel-error-quark"
catchIOChannelError ::
IO a ->
(IOChannelError -> GErrorMessage -> IO a) ->
IO a
catchIOChannelError :: IO a -> (IOChannelError -> Text -> IO a) -> IO a
catchIOChannelError = IO a -> (IOChannelError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleIOChannelError ::
(IOChannelError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleIOChannelError :: (IOChannelError -> Text -> IO a) -> IO a -> IO a
handleIOChannelError = (IOChannelError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data FileError =
FileErrorExist
| FileErrorIsdir
| FileErrorAcces
| FileErrorNametoolong
| FileErrorNoent
| FileErrorNotdir
| FileErrorNxio
| FileErrorNodev
| FileErrorRofs
| FileErrorTxtbsy
| FileErrorFault
| FileErrorLoop
| FileErrorNospc
| FileErrorNomem
| FileErrorMfile
| FileErrorNfile
| FileErrorBadf
| FileErrorInval
| FileErrorPipe
| FileErrorAgain
| FileErrorIntr
| FileErrorIo
| FileErrorPerm
| FileErrorNosys
| FileErrorFailed
| AnotherFileError Int
deriving (Int -> FileError -> ShowS
[FileError] -> ShowS
FileError -> String
(Int -> FileError -> ShowS)
-> (FileError -> String)
-> ([FileError] -> ShowS)
-> Show FileError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileError] -> ShowS
$cshowList :: [FileError] -> ShowS
show :: FileError -> String
$cshow :: FileError -> String
showsPrec :: Int -> FileError -> ShowS
$cshowsPrec :: Int -> FileError -> ShowS
Show, FileError -> FileError -> Bool
(FileError -> FileError -> Bool)
-> (FileError -> FileError -> Bool) -> Eq FileError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileError -> FileError -> Bool
$c/= :: FileError -> FileError -> Bool
== :: FileError -> FileError -> Bool
$c== :: FileError -> FileError -> Bool
Eq)
instance P.Enum FileError where
fromEnum :: FileError -> Int
fromEnum FileErrorExist = 0
fromEnum FileErrorIsdir = 1
fromEnum FileErrorAcces = 2
fromEnum FileErrorNametoolong = 3
fromEnum FileErrorNoent = 4
fromEnum FileErrorNotdir = 5
fromEnum FileErrorNxio = 6
fromEnum FileErrorNodev = 7
fromEnum FileErrorRofs = 8
fromEnum FileErrorTxtbsy = 9
fromEnum FileErrorFault = 10
fromEnum FileErrorLoop = 11
fromEnum FileErrorNospc = 12
fromEnum FileErrorNomem = 13
fromEnum FileErrorMfile = 14
fromEnum FileErrorNfile = 15
fromEnum FileErrorBadf = 16
fromEnum FileErrorInval = 17
fromEnum FileErrorPipe = 18
fromEnum FileErrorAgain = 19
fromEnum FileErrorIntr = 20
fromEnum FileErrorIo = 21
fromEnum FileErrorPerm = 22
fromEnum FileErrorNosys = 23
fromEnum FileErrorFailed = 24
fromEnum (AnotherFileError k :: Int
k) = Int
k
toEnum :: Int -> FileError
toEnum 0 = FileError
FileErrorExist
toEnum 1 = FileError
FileErrorIsdir
toEnum 2 = FileError
FileErrorAcces
toEnum 3 = FileError
FileErrorNametoolong
toEnum 4 = FileError
FileErrorNoent
toEnum 5 = FileError
FileErrorNotdir
toEnum 6 = FileError
FileErrorNxio
toEnum 7 = FileError
FileErrorNodev
toEnum 8 = FileError
FileErrorRofs
toEnum 9 = FileError
FileErrorTxtbsy
toEnum 10 = FileError
FileErrorFault
toEnum 11 = FileError
FileErrorLoop
toEnum 12 = FileError
FileErrorNospc
toEnum 13 = FileError
FileErrorNomem
toEnum 14 = FileError
FileErrorMfile
toEnum 15 = FileError
FileErrorNfile
toEnum 16 = FileError
FileErrorBadf
toEnum 17 = FileError
FileErrorInval
toEnum 18 = FileError
FileErrorPipe
toEnum 19 = FileError
FileErrorAgain
toEnum 20 = FileError
FileErrorIntr
toEnum 21 = FileError
FileErrorIo
toEnum 22 = FileError
FileErrorPerm
toEnum 23 = FileError
FileErrorNosys
toEnum 24 = FileError
FileErrorFailed
toEnum k :: Int
k = Int -> FileError
AnotherFileError Int
k
instance P.Ord FileError where
compare :: FileError -> FileError -> Ordering
compare a :: FileError
a b :: FileError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (FileError -> Int
forall a. Enum a => a -> Int
P.fromEnum FileError
a) (FileError -> Int
forall a. Enum a => a -> Int
P.fromEnum FileError
b)
instance GErrorClass FileError where
gerrorClassDomain :: FileError -> Text
gerrorClassDomain _ = "g-file-error-quark"
catchFileError ::
IO a ->
(FileError -> GErrorMessage -> IO a) ->
IO a
catchFileError :: IO a -> (FileError -> Text -> IO a) -> IO a
catchFileError = IO a -> (FileError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleFileError ::
(FileError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleFileError :: (FileError -> Text -> IO a) -> IO a -> IO a
handleFileError = (FileError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data ErrorType =
ErrorTypeUnknown
| ErrorTypeUnexpEof
| ErrorTypeUnexpEofInString
|
| ErrorTypeNonDigitInConst
| ErrorTypeDigitRadix
| ErrorTypeFloatRadix
| ErrorTypeFloatMalformed
| AnotherErrorType Int
deriving (Int -> ErrorType -> ShowS
[ErrorType] -> ShowS
ErrorType -> String
(Int -> ErrorType -> ShowS)
-> (ErrorType -> String)
-> ([ErrorType] -> ShowS)
-> Show ErrorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrorType] -> ShowS
$cshowList :: [ErrorType] -> ShowS
show :: ErrorType -> String
$cshow :: ErrorType -> String
showsPrec :: Int -> ErrorType -> ShowS
$cshowsPrec :: Int -> ErrorType -> ShowS
Show, ErrorType -> ErrorType -> Bool
(ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> Bool) -> Eq ErrorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorType -> ErrorType -> Bool
$c/= :: ErrorType -> ErrorType -> Bool
== :: ErrorType -> ErrorType -> Bool
$c== :: ErrorType -> ErrorType -> Bool
Eq)
instance P.Enum ErrorType where
fromEnum :: ErrorType -> Int
fromEnum ErrorTypeUnknown = 0
fromEnum ErrorTypeUnexpEof = 1
fromEnum ErrorTypeUnexpEofInString = 2
fromEnum ErrorTypeUnexpEofInComment = 3
fromEnum ErrorTypeNonDigitInConst = 4
fromEnum ErrorTypeDigitRadix = 5
fromEnum ErrorTypeFloatRadix = 6
fromEnum ErrorTypeFloatMalformed = 7
fromEnum (AnotherErrorType k :: Int
k) = Int
k
toEnum :: Int -> ErrorType
toEnum 0 = ErrorType
ErrorTypeUnknown
toEnum 1 = ErrorType
ErrorTypeUnexpEof
toEnum 2 = ErrorType
ErrorTypeUnexpEofInString
toEnum 3 = ErrorType
ErrorTypeUnexpEofInComment
toEnum 4 = ErrorType
ErrorTypeNonDigitInConst
toEnum 5 = ErrorType
ErrorTypeDigitRadix
toEnum 6 = ErrorType
ErrorTypeFloatRadix
toEnum 7 = ErrorType
ErrorTypeFloatMalformed
toEnum k :: Int
k = Int -> ErrorType
AnotherErrorType Int
k
instance P.Ord ErrorType where
compare :: ErrorType -> ErrorType -> Ordering
compare a :: ErrorType
a b :: ErrorType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ErrorType -> Int
forall a. Enum a => a -> Int
P.fromEnum ErrorType
a) (ErrorType -> Int
forall a. Enum a => a -> Int
P.fromEnum ErrorType
b)
data DateWeekday =
DateWeekdayBadWeekday
| DateWeekdayMonday
| DateWeekdayTuesday
| DateWeekdayWednesday
| DateWeekdayThursday
| DateWeekdayFriday
| DateWeekdaySaturday
| DateWeekdaySunday
| AnotherDateWeekday Int
deriving (Int -> DateWeekday -> ShowS
[DateWeekday] -> ShowS
DateWeekday -> String
(Int -> DateWeekday -> ShowS)
-> (DateWeekday -> String)
-> ([DateWeekday] -> ShowS)
-> Show DateWeekday
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateWeekday] -> ShowS
$cshowList :: [DateWeekday] -> ShowS
show :: DateWeekday -> String
$cshow :: DateWeekday -> String
showsPrec :: Int -> DateWeekday -> ShowS
$cshowsPrec :: Int -> DateWeekday -> ShowS
Show, DateWeekday -> DateWeekday -> Bool
(DateWeekday -> DateWeekday -> Bool)
-> (DateWeekday -> DateWeekday -> Bool) -> Eq DateWeekday
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateWeekday -> DateWeekday -> Bool
$c/= :: DateWeekday -> DateWeekday -> Bool
== :: DateWeekday -> DateWeekday -> Bool
$c== :: DateWeekday -> DateWeekday -> Bool
Eq)
instance P.Enum DateWeekday where
fromEnum :: DateWeekday -> Int
fromEnum DateWeekdayBadWeekday = 0
fromEnum DateWeekdayMonday = 1
fromEnum DateWeekdayTuesday = 2
fromEnum DateWeekdayWednesday = 3
fromEnum DateWeekdayThursday = 4
fromEnum DateWeekdayFriday = 5
fromEnum DateWeekdaySaturday = 6
fromEnum DateWeekdaySunday = 7
fromEnum (AnotherDateWeekday k :: Int
k) = Int
k
toEnum :: Int -> DateWeekday
toEnum 0 = DateWeekday
DateWeekdayBadWeekday
toEnum 1 = DateWeekday
DateWeekdayMonday
toEnum 2 = DateWeekday
DateWeekdayTuesday
toEnum 3 = DateWeekday
DateWeekdayWednesday
toEnum 4 = DateWeekday
DateWeekdayThursday
toEnum 5 = DateWeekday
DateWeekdayFriday
toEnum 6 = DateWeekday
DateWeekdaySaturday
toEnum 7 = DateWeekday
DateWeekdaySunday
toEnum k :: Int
k = Int -> DateWeekday
AnotherDateWeekday Int
k
instance P.Ord DateWeekday where
compare :: DateWeekday -> DateWeekday -> Ordering
compare a :: DateWeekday
a b :: DateWeekday
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DateWeekday -> Int
forall a. Enum a => a -> Int
P.fromEnum DateWeekday
a) (DateWeekday -> Int
forall a. Enum a => a -> Int
P.fromEnum DateWeekday
b)
data DateMonth =
DateMonthBadMonth
| DateMonthJanuary
| DateMonthFebruary
| DateMonthMarch
| DateMonthApril
| DateMonthMay
| DateMonthJune
| DateMonthJuly
| DateMonthAugust
| DateMonthSeptember
| DateMonthOctober
| DateMonthNovember
| DateMonthDecember
| AnotherDateMonth Int
deriving (Int -> DateMonth -> ShowS
[DateMonth] -> ShowS
DateMonth -> String
(Int -> DateMonth -> ShowS)
-> (DateMonth -> String)
-> ([DateMonth] -> ShowS)
-> Show DateMonth
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateMonth] -> ShowS
$cshowList :: [DateMonth] -> ShowS
show :: DateMonth -> String
$cshow :: DateMonth -> String
showsPrec :: Int -> DateMonth -> ShowS
$cshowsPrec :: Int -> DateMonth -> ShowS
Show, DateMonth -> DateMonth -> Bool
(DateMonth -> DateMonth -> Bool)
-> (DateMonth -> DateMonth -> Bool) -> Eq DateMonth
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateMonth -> DateMonth -> Bool
$c/= :: DateMonth -> DateMonth -> Bool
== :: DateMonth -> DateMonth -> Bool
$c== :: DateMonth -> DateMonth -> Bool
Eq)
instance P.Enum DateMonth where
fromEnum :: DateMonth -> Int
fromEnum DateMonthBadMonth = 0
fromEnum DateMonthJanuary = 1
fromEnum DateMonthFebruary = 2
fromEnum DateMonthMarch = 3
fromEnum DateMonthApril = 4
fromEnum DateMonthMay = 5
fromEnum DateMonthJune = 6
fromEnum DateMonthJuly = 7
fromEnum DateMonthAugust = 8
fromEnum DateMonthSeptember = 9
fromEnum DateMonthOctober = 10
fromEnum DateMonthNovember = 11
fromEnum DateMonthDecember = 12
fromEnum (AnotherDateMonth k :: Int
k) = Int
k
toEnum :: Int -> DateMonth
toEnum 0 = DateMonth
DateMonthBadMonth
toEnum 1 = DateMonth
DateMonthJanuary
toEnum 2 = DateMonth
DateMonthFebruary
toEnum 3 = DateMonth
DateMonthMarch
toEnum 4 = DateMonth
DateMonthApril
toEnum 5 = DateMonth
DateMonthMay
toEnum 6 = DateMonth
DateMonthJune
toEnum 7 = DateMonth
DateMonthJuly
toEnum 8 = DateMonth
DateMonthAugust
toEnum 9 = DateMonth
DateMonthSeptember
toEnum 10 = DateMonth
DateMonthOctober
toEnum 11 = DateMonth
DateMonthNovember
toEnum 12 = DateMonth
DateMonthDecember
toEnum k :: Int
k = Int -> DateMonth
AnotherDateMonth Int
k
instance P.Ord DateMonth where
compare :: DateMonth -> DateMonth -> Ordering
compare a :: DateMonth
a b :: DateMonth
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DateMonth -> Int
forall a. Enum a => a -> Int
P.fromEnum DateMonth
a) (DateMonth -> Int
forall a. Enum a => a -> Int
P.fromEnum DateMonth
b)
data DateDMY =
DateDMYDay
| DateDMYMonth
| DateDMYYear
| AnotherDateDMY Int
deriving (Int -> DateDMY -> ShowS
[DateDMY] -> ShowS
DateDMY -> String
(Int -> DateDMY -> ShowS)
-> (DateDMY -> String) -> ([DateDMY] -> ShowS) -> Show DateDMY
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateDMY] -> ShowS
$cshowList :: [DateDMY] -> ShowS
show :: DateDMY -> String
$cshow :: DateDMY -> String
showsPrec :: Int -> DateDMY -> ShowS
$cshowsPrec :: Int -> DateDMY -> ShowS
Show, DateDMY -> DateDMY -> Bool
(DateDMY -> DateDMY -> Bool)
-> (DateDMY -> DateDMY -> Bool) -> Eq DateDMY
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateDMY -> DateDMY -> Bool
$c/= :: DateDMY -> DateDMY -> Bool
== :: DateDMY -> DateDMY -> Bool
$c== :: DateDMY -> DateDMY -> Bool
Eq)
instance P.Enum DateDMY where
fromEnum :: DateDMY -> Int
fromEnum DateDMYDay = 0
fromEnum DateDMYMonth = 1
fromEnum DateDMYYear = 2
fromEnum (AnotherDateDMY k :: Int
k) = Int
k
toEnum :: Int -> DateDMY
toEnum 0 = DateDMY
DateDMYDay
toEnum 1 = DateDMY
DateDMYMonth
toEnum 2 = DateDMY
DateDMYYear
toEnum k :: Int
k = Int -> DateDMY
AnotherDateDMY Int
k
instance P.Ord DateDMY where
compare :: DateDMY -> DateDMY -> Ordering
compare a :: DateDMY
a b :: DateDMY
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DateDMY -> Int
forall a. Enum a => a -> Int
P.fromEnum DateDMY
a) (DateDMY -> Int
forall a. Enum a => a -> Int
P.fromEnum DateDMY
b)
data ConvertError =
ConvertErrorNoConversion
| ConvertErrorIllegalSequence
| ConvertErrorFailed
| ConvertErrorPartialInput
| ConvertErrorBadUri
| ConvertErrorNotAbsolutePath
| ConvertErrorNoMemory
| ConvertErrorEmbeddedNul
| AnotherConvertError Int
deriving (Int -> ConvertError -> ShowS
[ConvertError] -> ShowS
ConvertError -> String
(Int -> ConvertError -> ShowS)
-> (ConvertError -> String)
-> ([ConvertError] -> ShowS)
-> Show ConvertError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConvertError] -> ShowS
$cshowList :: [ConvertError] -> ShowS
show :: ConvertError -> String
$cshow :: ConvertError -> String
showsPrec :: Int -> ConvertError -> ShowS
$cshowsPrec :: Int -> ConvertError -> ShowS
Show, ConvertError -> ConvertError -> Bool
(ConvertError -> ConvertError -> Bool)
-> (ConvertError -> ConvertError -> Bool) -> Eq ConvertError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConvertError -> ConvertError -> Bool
$c/= :: ConvertError -> ConvertError -> Bool
== :: ConvertError -> ConvertError -> Bool
$c== :: ConvertError -> ConvertError -> Bool
Eq)
instance P.Enum ConvertError where
fromEnum :: ConvertError -> Int
fromEnum ConvertErrorNoConversion = 0
fromEnum ConvertErrorIllegalSequence = 1
fromEnum ConvertErrorFailed = 2
fromEnum ConvertErrorPartialInput = 3
fromEnum ConvertErrorBadUri = 4
fromEnum ConvertErrorNotAbsolutePath = 5
fromEnum ConvertErrorNoMemory = 6
fromEnum ConvertErrorEmbeddedNul = 7
fromEnum (AnotherConvertError k :: Int
k) = Int
k
toEnum :: Int -> ConvertError
toEnum 0 = ConvertError
ConvertErrorNoConversion
toEnum 1 = ConvertError
ConvertErrorIllegalSequence
toEnum 2 = ConvertError
ConvertErrorFailed
toEnum 3 = ConvertError
ConvertErrorPartialInput
toEnum 4 = ConvertError
ConvertErrorBadUri
toEnum 5 = ConvertError
ConvertErrorNotAbsolutePath
toEnum 6 = ConvertError
ConvertErrorNoMemory
toEnum 7 = ConvertError
ConvertErrorEmbeddedNul
toEnum k :: Int
k = Int -> ConvertError
AnotherConvertError Int
k
instance P.Ord ConvertError where
compare :: ConvertError -> ConvertError -> Ordering
compare a :: ConvertError
a b :: ConvertError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ConvertError -> Int
forall a. Enum a => a -> Int
P.fromEnum ConvertError
a) (ConvertError -> Int
forall a. Enum a => a -> Int
P.fromEnum ConvertError
b)
instance GErrorClass ConvertError where
gerrorClassDomain :: ConvertError -> Text
gerrorClassDomain _ = "g_convert_error"
catchConvertError ::
IO a ->
(ConvertError -> GErrorMessage -> IO a) ->
IO a
catchConvertError :: IO a -> (ConvertError -> Text -> IO a) -> IO a
catchConvertError = IO a -> (ConvertError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleConvertError ::
(ConvertError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleConvertError :: (ConvertError -> Text -> IO a) -> IO a -> IO a
handleConvertError = (ConvertError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
data ChecksumType =
ChecksumTypeMd5
| ChecksumTypeSha1
| ChecksumTypeSha256
| ChecksumTypeSha512
| ChecksumTypeSha384
| AnotherChecksumType Int
deriving (Int -> ChecksumType -> ShowS
[ChecksumType] -> ShowS
ChecksumType -> String
(Int -> ChecksumType -> ShowS)
-> (ChecksumType -> String)
-> ([ChecksumType] -> ShowS)
-> Show ChecksumType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChecksumType] -> ShowS
$cshowList :: [ChecksumType] -> ShowS
show :: ChecksumType -> String
$cshow :: ChecksumType -> String
showsPrec :: Int -> ChecksumType -> ShowS
$cshowsPrec :: Int -> ChecksumType -> ShowS
Show, ChecksumType -> ChecksumType -> Bool
(ChecksumType -> ChecksumType -> Bool)
-> (ChecksumType -> ChecksumType -> Bool) -> Eq ChecksumType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChecksumType -> ChecksumType -> Bool
$c/= :: ChecksumType -> ChecksumType -> Bool
== :: ChecksumType -> ChecksumType -> Bool
$c== :: ChecksumType -> ChecksumType -> Bool
Eq)
instance P.Enum ChecksumType where
fromEnum :: ChecksumType -> Int
fromEnum ChecksumTypeMd5 = 0
fromEnum ChecksumTypeSha1 = 1
fromEnum ChecksumTypeSha256 = 2
fromEnum ChecksumTypeSha512 = 3
fromEnum ChecksumTypeSha384 = 4
fromEnum (AnotherChecksumType k :: Int
k) = Int
k
toEnum :: Int -> ChecksumType
toEnum 0 = ChecksumType
ChecksumTypeMd5
toEnum 1 = ChecksumType
ChecksumTypeSha1
toEnum 2 = ChecksumType
ChecksumTypeSha256
toEnum 3 = ChecksumType
ChecksumTypeSha512
toEnum 4 = ChecksumType
ChecksumTypeSha384
toEnum k :: Int
k = Int -> ChecksumType
AnotherChecksumType Int
k
instance P.Ord ChecksumType where
compare :: ChecksumType -> ChecksumType -> Ordering
compare a :: ChecksumType
a b :: ChecksumType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ChecksumType -> Int
forall a. Enum a => a -> Int
P.fromEnum ChecksumType
a) (ChecksumType -> Int
forall a. Enum a => a -> Int
P.fromEnum ChecksumType
b)
data BookmarkFileError =
BookmarkFileErrorInvalidUri
| BookmarkFileErrorInvalidValue
| BookmarkFileErrorAppNotRegistered
| BookmarkFileErrorUriNotFound
| BookmarkFileErrorRead
| BookmarkFileErrorUnknownEncoding
| BookmarkFileErrorWrite
| BookmarkFileErrorFileNotFound
| AnotherBookmarkFileError Int
deriving (Int -> BookmarkFileError -> ShowS
[BookmarkFileError] -> ShowS
BookmarkFileError -> String
(Int -> BookmarkFileError -> ShowS)
-> (BookmarkFileError -> String)
-> ([BookmarkFileError] -> ShowS)
-> Show BookmarkFileError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BookmarkFileError] -> ShowS
$cshowList :: [BookmarkFileError] -> ShowS
show :: BookmarkFileError -> String
$cshow :: BookmarkFileError -> String
showsPrec :: Int -> BookmarkFileError -> ShowS
$cshowsPrec :: Int -> BookmarkFileError -> ShowS
Show, BookmarkFileError -> BookmarkFileError -> Bool
(BookmarkFileError -> BookmarkFileError -> Bool)
-> (BookmarkFileError -> BookmarkFileError -> Bool)
-> Eq BookmarkFileError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BookmarkFileError -> BookmarkFileError -> Bool
$c/= :: BookmarkFileError -> BookmarkFileError -> Bool
== :: BookmarkFileError -> BookmarkFileError -> Bool
$c== :: BookmarkFileError -> BookmarkFileError -> Bool
Eq)
instance P.Enum BookmarkFileError where
fromEnum :: BookmarkFileError -> Int
fromEnum BookmarkFileErrorInvalidUri = 0
fromEnum BookmarkFileErrorInvalidValue = 1
fromEnum BookmarkFileErrorAppNotRegistered = 2
fromEnum BookmarkFileErrorUriNotFound = 3
fromEnum BookmarkFileErrorRead = 4
fromEnum BookmarkFileErrorUnknownEncoding = 5
fromEnum BookmarkFileErrorWrite = 6
fromEnum BookmarkFileErrorFileNotFound = 7
fromEnum (AnotherBookmarkFileError k :: Int
k) = Int
k
toEnum :: Int -> BookmarkFileError
toEnum 0 = BookmarkFileError
BookmarkFileErrorInvalidUri
toEnum 1 = BookmarkFileError
BookmarkFileErrorInvalidValue
toEnum 2 = BookmarkFileError
BookmarkFileErrorAppNotRegistered
toEnum 3 = BookmarkFileError
BookmarkFileErrorUriNotFound
toEnum 4 = BookmarkFileError
BookmarkFileErrorRead
toEnum 5 = BookmarkFileError
BookmarkFileErrorUnknownEncoding
toEnum 6 = BookmarkFileError
BookmarkFileErrorWrite
toEnum 7 = BookmarkFileError
BookmarkFileErrorFileNotFound
toEnum k :: Int
k = Int -> BookmarkFileError
AnotherBookmarkFileError Int
k
instance P.Ord BookmarkFileError where
compare :: BookmarkFileError -> BookmarkFileError -> Ordering
compare a :: BookmarkFileError
a b :: BookmarkFileError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (BookmarkFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum BookmarkFileError
a) (BookmarkFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum BookmarkFileError
b)
instance GErrorClass BookmarkFileError where
gerrorClassDomain :: BookmarkFileError -> Text
gerrorClassDomain _ = "g-bookmark-file-error-quark"
catchBookmarkFileError ::
IO a ->
(BookmarkFileError -> GErrorMessage -> IO a) ->
IO a
catchBookmarkFileError :: IO a -> (BookmarkFileError -> Text -> IO a) -> IO a
catchBookmarkFileError = IO a -> (BookmarkFileError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleBookmarkFileError ::
(BookmarkFileError -> GErrorMessage -> IO a) ->
IO a ->
IO a
handleBookmarkFileError :: (BookmarkFileError -> Text -> IO a) -> IO a -> IO a
handleBookmarkFileError = (BookmarkFileError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain