{-# LINE 1 "Std/Data/Text/UTF8Rewind.hsc" #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Std.Data.Text.UTF8Rewind where
import Data.Bits
import Foreign.C.Types
import GHC.Generics
newtype Locale = Locale CSize deriving (Show, Eq, Ord, Generic)
localeDefault :: Locale
localeDefault = Locale 0
{-# LINE 29 "Std/Data/Text/UTF8Rewind.hsc" #-}
localeLithuanian :: Locale
localeLithuanian = Locale 1
{-# LINE 30 "Std/Data/Text/UTF8Rewind.hsc" #-}
localeTurkishAndAzeriLatin :: Locale
localeTurkishAndAzeriLatin = Locale 2
{-# LINE 31 "Std/Data/Text/UTF8Rewind.hsc" #-}
normalizeCompose :: CSize
normalizeCompose = CSize 1
{-# LINE 34 "Std/Data/Text/UTF8Rewind.hsc" #-}
normalizeDecompose :: CSize
normalizeDecompose = CSize 2
{-# LINE 35 "Std/Data/Text/UTF8Rewind.hsc" #-}
normalizeCompatibility :: CSize
normalizeCompatibility = CSize 4
{-# LINE 36 "Std/Data/Text/UTF8Rewind.hsc" #-}
data NormalizeMode = NFC | NFKC | NFD | NFKD deriving (Show, Eq, Ord, Generic)
normalizeModeToFlag :: NormalizeMode -> CSize
normalizeModeToFlag NFC = 1
{-# LINE 53 "Std/Data/Text/UTF8Rewind.hsc" #-}
normalizeModeToFlag NFKC = 1 + 4
{-# LINE 54 "Std/Data/Text/UTF8Rewind.hsc" #-}
normalizeModeToFlag NFD = 2
{-# LINE 55 "Std/Data/Text/UTF8Rewind.hsc" #-}
normalizeModeToFlag NFKD = 2 + 4
{-# LINE 56 "Std/Data/Text/UTF8Rewind.hsc" #-}
data NormalizationResult = NormalizedYes | NormalizedMaybe | NormalizedNo deriving (Show, Eq, Ord, Generic)
toNormalizationResult :: Int -> NormalizationResult
toNormalizationResult 0 = NormalizedYes
{-# LINE 61 "Std/Data/Text/UTF8Rewind.hsc" #-}
toNormalizationResult 1 = NormalizedMaybe
{-# LINE 62 "Std/Data/Text/UTF8Rewind.hsc" #-}
toNormalizationResult 2 = NormalizedNo
{-# LINE 63 "Std/Data/Text/UTF8Rewind.hsc" #-}
newtype Category = Category CSize deriving (Show, Eq, Ord, Bits, FiniteBits, Generic)
categoryLetterUppercase :: Category
categoryLetterUppercase = Category 1
{-# LINE 70 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryLetterLowercase :: Category
categoryLetterLowercase = Category 2
{-# LINE 71 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryLetterTitlecase :: Category
categoryLetterTitlecase = Category 4
{-# LINE 72 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryLetterOther :: Category
categoryLetterOther = Category 16
{-# LINE 73 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryLetter :: Category
categoryLetter = Category 31
{-# LINE 74 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryCaseMapped :: Category
categoryCaseMapped = Category 7
{-# LINE 75 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryMarkNonSpacing :: Category
categoryMarkNonSpacing = Category 32
{-# LINE 77 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryMarkSpacing :: Category
categoryMarkSpacing = Category 64
{-# LINE 78 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryMarkEnclosing :: Category
categoryMarkEnclosing = Category 128
{-# LINE 79 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryMark :: Category
categoryMark = Category 224
{-# LINE 80 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryNumberDecimal :: Category
categoryNumberDecimal = Category 256
{-# LINE 82 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryNumberLetter :: Category
categoryNumberLetter = Category 512
{-# LINE 83 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryNumberOther :: Category
categoryNumberOther = Category 1024
{-# LINE 84 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryNumber :: Category
categoryNumber = Category 1792
{-# LINE 85 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuationConnector :: Category
categoryPunctuationConnector = Category 2048
{-# LINE 87 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuationDash :: Category
categoryPunctuationDash = Category 4096
{-# LINE 88 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuationOpen :: Category
categoryPunctuationOpen = Category 8192
{-# LINE 89 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuationClose :: Category
categoryPunctuationClose = Category 16384
{-# LINE 90 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuationInitial :: Category
categoryPunctuationInitial = Category 32768
{-# LINE 91 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuationFinal :: Category
categoryPunctuationFinal = Category 65536
{-# LINE 92 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuationOther :: Category
categoryPunctuationOther = Category 131072
{-# LINE 93 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPunctuation :: Category
categoryPunctuation = Category 260096
{-# LINE 94 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySymbolMath :: Category
categorySymbolMath = Category 262144
{-# LINE 96 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySymbolCurrency :: Category
categorySymbolCurrency = Category 524288
{-# LINE 97 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySymbolModifier :: Category
categorySymbolModifier = Category 1048576
{-# LINE 98 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySymbolOther :: Category
categorySymbolOther = Category 2097152
{-# LINE 99 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySymbol :: Category
categorySymbol = Category 3932160
{-# LINE 100 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySeparatorSpace :: Category
categorySeparatorSpace = Category 4194304
{-# LINE 102 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySeparatorLine :: Category
categorySeparatorLine = Category 8388608
{-# LINE 103 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySeparatorParagraph :: Category
categorySeparatorParagraph = Category 16777216
{-# LINE 104 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySeparator :: Category
categorySeparator = Category 29360128
{-# LINE 105 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryControl :: Category
categoryControl = Category 33554432
{-# LINE 106 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryFormat :: Category
categoryFormat = Category 67108864
{-# LINE 107 "Std/Data/Text/UTF8Rewind.hsc" #-}
categorySurrogate :: Category
categorySurrogate = Category 134217728
{-# LINE 108 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryPrivateUse :: Category
categoryPrivateUse = Category 268435456
{-# LINE 109 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryUnassigned :: Category
categoryUnassigned = Category 536870912
{-# LINE 110 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryCompatibility :: Category
categoryCompatibility = Category 1073741824
{-# LINE 111 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIgnoreGraphemeCluste :: Category
categoryIgnoreGraphemeCluste = Category 2147483648
{-# LINE 112 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIscntrl :: Category
categoryIscntrl = Category 1107296256
{-# LINE 113 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsprint :: Category
categoryIsprint = Category 1107296031
{-# LINE 115 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsspace :: Category
categoryIsspace = Category 1077936128
{-# LINE 116 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsblank :: Category
categoryIsblank = Category 1346371584
{-# LINE 117 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsgraph :: Category
categoryIsgraph = Category 1077935903
{-# LINE 118 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIspunct :: Category
categoryIspunct = Category 1077934080
{-# LINE 119 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsalnum :: Category
categoryIsalnum = Category 1073743647
{-# LINE 120 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsalpha :: Category
categoryIsalpha = Category 1073741855
{-# LINE 121 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsupper :: Category
categoryIsupper = Category 1073741825
{-# LINE 122 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIslower :: Category
categoryIslower = Category 1073741826
{-# LINE 123 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsdigit :: Category
categoryIsdigit = Category 1073743616
{-# LINE 124 "Std/Data/Text/UTF8Rewind.hsc" #-}
categoryIsxdigit :: Category
categoryIsxdigit = Category 1342179072
{-# LINE 125 "Std/Data/Text/UTF8Rewind.hsc" #-}
foreign import ccall unsafe utf8envlocale :: IO Category