{-# OPTIONS -XEmptyDataDecls #-} module NET.System.Char where import NET import qualified NET.System.Object import qualified NET.System.IFormatProvider import qualified NET.System.Globalization.CultureInfo import qualified NET.System.TypeCode import qualified NET.System.Globalization.UnicodeCategory import qualified NET.System.ValueType data Char_ a type Char a = NET.System.ValueType.ValueType (Char_ a) getHashCode :: NET.System.Char.Char obj -> IO (Int) getHashCode = invoke "GetHashCode" () equals :: NET.System.Object.Object a0 -> NET.System.Char.Char obj -> IO (Bool) equals arg0 = invoke "Equals" (arg0) equals_1 :: Prelude.Char -> NET.System.Char.Char obj -> IO (Bool) equals_1 arg0 = invoke "Equals" (arg0) compareTo :: NET.System.Object.Object a0 -> NET.System.Char.Char obj -> IO (Int) compareTo arg0 = invoke "CompareTo" (arg0) compareTo_1 :: Prelude.Char -> NET.System.Char.Char obj -> IO (Int) compareTo_1 arg0 = invoke "CompareTo" (arg0) toString :: NET.System.Char.Char obj -> IO (String) toString = invoke "ToString" () toString_1 :: NET.System.IFormatProvider.IFormatProvider a0 -> NET.System.Char.Char obj -> IO (String) toString_1 arg0 = invoke "ToString" (arg0) toString_2 :: Prelude.Char -> IO (String) toString_2 arg0 = invokeStatic "System.Char" "ToString" (arg0) parse :: String -> IO (Prelude.Char) parse arg0 = invokeStatic "System.Char" "Parse" (arg0) tryParse :: String -> Prelude.Char -> IO (Bool) tryParse arg0 arg1 = invokeStatic "System.Char" "TryParse" (arg0, arg1) isDigit :: Prelude.Char -> IO (Bool) isDigit arg0 = invokeStatic "System.Char" "IsDigit" (arg0) isLetter :: Prelude.Char -> IO (Bool) isLetter arg0 = invokeStatic "System.Char" "IsLetter" (arg0) isWhiteSpace :: Prelude.Char -> IO (Bool) isWhiteSpace arg0 = invokeStatic "System.Char" "IsWhiteSpace" (arg0) isUpper :: Prelude.Char -> IO (Bool) isUpper arg0 = invokeStatic "System.Char" "IsUpper" (arg0) isLower :: Prelude.Char -> IO (Bool) isLower arg0 = invokeStatic "System.Char" "IsLower" (arg0) isPunctuation :: Prelude.Char -> IO (Bool) isPunctuation arg0 = invokeStatic "System.Char" "IsPunctuation" (arg0) isLetterOrDigit :: Prelude.Char -> IO (Bool) isLetterOrDigit arg0 = invokeStatic "System.Char" "IsLetterOrDigit" (arg0) toUpper :: Prelude.Char -> NET.System.Globalization.CultureInfo.CultureInfo a1 -> IO (Prelude.Char) toUpper arg0 arg1 = invokeStatic "System.Char" "ToUpper" (arg0, arg1) toUpper_1 :: Prelude.Char -> IO (Prelude.Char) toUpper_1 arg0 = invokeStatic "System.Char" "ToUpper" (arg0) toUpperInvariant :: Prelude.Char -> IO (Prelude.Char) toUpperInvariant arg0 = invokeStatic "System.Char" "ToUpperInvariant" (arg0) toLower :: Prelude.Char -> NET.System.Globalization.CultureInfo.CultureInfo a1 -> IO (Prelude.Char) toLower arg0 arg1 = invokeStatic "System.Char" "ToLower" (arg0, arg1) toLower_1 :: Prelude.Char -> IO (Prelude.Char) toLower_1 arg0 = invokeStatic "System.Char" "ToLower" (arg0) toLowerInvariant :: Prelude.Char -> IO (Prelude.Char) toLowerInvariant arg0 = invokeStatic "System.Char" "ToLowerInvariant" (arg0) getTypeCode :: NET.System.Char.Char obj -> IO (NET.System.TypeCode.TypeCode a0) getTypeCode = invoke "GetTypeCode" () isControl :: Prelude.Char -> IO (Bool) isControl arg0 = invokeStatic "System.Char" "IsControl" (arg0) isControl_1 :: String -> Int -> IO (Bool) isControl_1 arg0 arg1 = invokeStatic "System.Char" "IsControl" (arg0, arg1) isDigit_1 :: String -> Int -> IO (Bool) isDigit_1 arg0 arg1 = invokeStatic "System.Char" "IsDigit" (arg0, arg1) isLetter_1 :: String -> Int -> IO (Bool) isLetter_1 arg0 arg1 = invokeStatic "System.Char" "IsLetter" (arg0, arg1) isLetterOrDigit_1 :: String -> Int -> IO (Bool) isLetterOrDigit_1 arg0 arg1 = invokeStatic "System.Char" "IsLetterOrDigit" (arg0, arg1) isLower_1 :: String -> Int -> IO (Bool) isLower_1 arg0 arg1 = invokeStatic "System.Char" "IsLower" (arg0, arg1) isNumber :: Prelude.Char -> IO (Bool) isNumber arg0 = invokeStatic "System.Char" "IsNumber" (arg0) isNumber_1 :: String -> Int -> IO (Bool) isNumber_1 arg0 arg1 = invokeStatic "System.Char" "IsNumber" (arg0, arg1) isPunctuation_1 :: String -> Int -> IO (Bool) isPunctuation_1 arg0 arg1 = invokeStatic "System.Char" "IsPunctuation" (arg0, arg1) isSeparator :: Prelude.Char -> IO (Bool) isSeparator arg0 = invokeStatic "System.Char" "IsSeparator" (arg0) isSeparator_1 :: String -> Int -> IO (Bool) isSeparator_1 arg0 arg1 = invokeStatic "System.Char" "IsSeparator" (arg0, arg1) isSurrogate :: Prelude.Char -> IO (Bool) isSurrogate arg0 = invokeStatic "System.Char" "IsSurrogate" (arg0) isSurrogate_1 :: String -> Int -> IO (Bool) isSurrogate_1 arg0 arg1 = invokeStatic "System.Char" "IsSurrogate" (arg0, arg1) isSymbol :: Prelude.Char -> IO (Bool) isSymbol arg0 = invokeStatic "System.Char" "IsSymbol" (arg0) isSymbol_1 :: String -> Int -> IO (Bool) isSymbol_1 arg0 arg1 = invokeStatic "System.Char" "IsSymbol" (arg0, arg1) isUpper_1 :: String -> Int -> IO (Bool) isUpper_1 arg0 arg1 = invokeStatic "System.Char" "IsUpper" (arg0, arg1) isWhiteSpace_1 :: String -> Int -> IO (Bool) isWhiteSpace_1 arg0 arg1 = invokeStatic "System.Char" "IsWhiteSpace" (arg0, arg1) getUnicodeCategory :: Prelude.Char -> IO (NET.System.Globalization.UnicodeCategory.UnicodeCategory a1) getUnicodeCategory arg0 = invokeStatic "System.Char" "GetUnicodeCategory" (arg0) getUnicodeCategory_1 :: String -> Int -> IO (NET.System.Globalization.UnicodeCategory.UnicodeCategory a2) getUnicodeCategory_1 arg0 arg1 = invokeStatic "System.Char" "GetUnicodeCategory" (arg0, arg1) getNumericValue :: Prelude.Char -> IO (Double) getNumericValue arg0 = invokeStatic "System.Char" "GetNumericValue" (arg0) getNumericValue_1 :: String -> Int -> IO (Double) getNumericValue_1 arg0 arg1 = invokeStatic "System.Char" "GetNumericValue" (arg0, arg1) isHighSurrogate :: Prelude.Char -> IO (Bool) isHighSurrogate arg0 = invokeStatic "System.Char" "IsHighSurrogate" (arg0) isHighSurrogate_1 :: String -> Int -> IO (Bool) isHighSurrogate_1 arg0 arg1 = invokeStatic "System.Char" "IsHighSurrogate" (arg0, arg1) isLowSurrogate :: Prelude.Char -> IO (Bool) isLowSurrogate arg0 = invokeStatic "System.Char" "IsLowSurrogate" (arg0) isLowSurrogate_1 :: String -> Int -> IO (Bool) isLowSurrogate_1 arg0 arg1 = invokeStatic "System.Char" "IsLowSurrogate" (arg0, arg1) isSurrogatePair :: String -> Int -> IO (Bool) isSurrogatePair arg0 arg1 = invokeStatic "System.Char" "IsSurrogatePair" (arg0, arg1) isSurrogatePair_1 :: Prelude.Char -> Prelude.Char -> IO (Bool) isSurrogatePair_1 arg0 arg1 = invokeStatic "System.Char" "IsSurrogatePair" (arg0, arg1) convertFromUtf32 :: Int -> IO (String) convertFromUtf32 arg0 = invokeStatic "System.Char" "ConvertFromUtf32" (arg0) convertToUtf32 :: Prelude.Char -> Prelude.Char -> IO (Int) convertToUtf32 arg0 arg1 = invokeStatic "System.Char" "ConvertToUtf32" (arg0, arg1) convertToUtf32_1 :: String -> Int -> IO (Int) convertToUtf32_1 arg0 arg1 = invokeStatic "System.Char" "ConvertToUtf32" (arg0, arg1) get_MaxValue :: IO (Prelude.Char) get_MaxValue = getFieldStatic "System.Char" "MaxValue" () set_MaxValue :: Prelude.Char -> IO () set_MaxValue = setFieldStatic "System.Char" "MaxValue" get_MinValue :: IO (Prelude.Char) get_MinValue = getFieldStatic "System.Char" "MinValue" () set_MinValue :: Prelude.Char -> IO () set_MinValue = setFieldStatic "System.Char" "MinValue"