{-# OPTIONS -XEmptyDataDecls #-} module NET.System.Decimal where import NET import qualified Data.Int import qualified NET.System.Object import qualified NET.System.IFormatProvider import qualified NET.System.Globalization.NumberStyles --import qualified NET.System.Decimal& import qualified NET.System.Array --import qualified NET.System.MidpointRounding import qualified Data.Word import qualified NET.System.TypeCode import qualified NET.System.ValueType data Decimal_ a type Decimal a = NET.System.ValueType.ValueType (Decimal_ a) toOACurrency :: NET.System.Decimal.Decimal a0 -> IO (Data.Int.Int64) toOACurrency arg0 = invokeStatic "System.Decimal" "ToOACurrency" (arg0) fromOACurrency :: Data.Int.Int64 -> IO (NET.System.Decimal.Decimal a1) fromOACurrency arg0 = invokeStatic "System.Decimal" "FromOACurrency" (arg0) add :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) add arg0 arg1 = invokeStatic "System.Decimal" "Add" (arg0, arg1) ceiling :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) ceiling arg0 = invokeStatic "System.Decimal" "Ceiling" (arg0) compare :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Int) compare arg0 arg1 = invokeStatic "System.Decimal" "Compare" (arg0, arg1) compareTo :: NET.System.Object.Object a0 -> Decimal obj -> IO (Int) compareTo arg0 = invoke "CompareTo" (arg0) compareTo_1 :: NET.System.Decimal.Decimal a0 -> Decimal obj -> IO (Int) compareTo_1 arg0 = invoke "CompareTo" (arg0) divide :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) divide arg0 arg1 = invokeStatic "System.Decimal" "Divide" (arg0, arg1) equals :: NET.System.Object.Object a0 -> Decimal obj -> IO (Bool) equals arg0 = invoke "Equals" (arg0) equals_1 :: NET.System.Decimal.Decimal a0 -> Decimal obj -> IO (Bool) equals_1 arg0 = invoke "Equals" (arg0) getHashCode :: Decimal obj -> IO (Int) getHashCode = invoke "GetHashCode" () equals_2 :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Bool) equals_2 arg0 arg1 = invokeStatic "System.Decimal" "Equals" (arg0, arg1) floor :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) floor arg0 = invokeStatic "System.Decimal" "Floor" (arg0) toString :: Decimal obj -> IO (String) toString = invoke "ToString" () toString_1 :: String -> Decimal obj -> IO (String) toString_1 arg0 = invoke "ToString" (arg0) toString_2 :: NET.System.IFormatProvider.IFormatProvider a0 -> Decimal obj -> IO (String) toString_2 arg0 = invoke "ToString" (arg0) toString_3 :: String -> NET.System.IFormatProvider.IFormatProvider a1 -> Decimal obj -> IO (String) toString_3 arg0 arg1 = invoke "ToString" (arg0, arg1) parse :: String -> IO (NET.System.Decimal.Decimal a1) parse arg0 = invokeStatic "System.Decimal" "Parse" (arg0) parse_1 :: String -> NET.System.Globalization.NumberStyles.NumberStyles a1 -> IO (NET.System.Decimal.Decimal a2) parse_1 arg0 arg1 = invokeStatic "System.Decimal" "Parse" (arg0, arg1) parse_2 :: String -> NET.System.IFormatProvider.IFormatProvider a1 -> IO (NET.System.Decimal.Decimal a2) parse_2 arg0 arg1 = invokeStatic "System.Decimal" "Parse" (arg0, arg1) parse_3 :: String -> NET.System.Globalization.NumberStyles.NumberStyles a1 -> NET.System.IFormatProvider.IFormatProvider a2 -> IO (NET.System.Decimal.Decimal a3) parse_3 arg0 arg1 arg2 = invokeStatic "System.Decimal" "Parse" (arg0, arg1, arg2) --tryParse :: String -> NET.System.Decimal&.Decimal& a1 -> IO (Bool) --tryParse arg0 arg1 = invokeStatic "System.Decimal" "TryParse" (arg0, arg1) --tryParse_1 :: String -> NET.System.Globalization.NumberStyles.NumberStyles a1 -> NET.System.IFormatProvider.IFormatProvider a2 -> NET.System.Decimal&.Decimal& a3 -> IO (Bool) --tryParse_1 arg0 arg1 arg2 arg3 = invokeStatic "System.Decimal" "TryParse" (arg0, arg1, arg2, arg3) getBits :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Array.Array (Int)) getBits arg0 = invokeStatic "System.Decimal" "GetBits" (arg0) remainder :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) remainder arg0 arg1 = invokeStatic "System.Decimal" "Remainder" (arg0, arg1) multiply :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) multiply arg0 arg1 = invokeStatic "System.Decimal" "Multiply" (arg0, arg1) negate :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) negate arg0 = invokeStatic "System.Decimal" "Negate" (arg0) round :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) round arg0 = invokeStatic "System.Decimal" "Round" (arg0) round_1 :: NET.System.Decimal.Decimal a0 -> Int -> IO (NET.System.Decimal.Decimal a2) round_1 arg0 arg1 = invokeStatic "System.Decimal" "Round" (arg0, arg1) --round_2 :: NET.System.Decimal.Decimal a0 -> NET.System.MidpointRounding.MidpointRounding a1 -> IO (NET.System.Decimal.Decimal a2) --round_2 arg0 arg1 = invokeStatic "System.Decimal" "Round" (arg0, arg1) --round_3 :: NET.System.Decimal.Decimal a0 -> Int -> NET.System.MidpointRounding.MidpointRounding a2 -> IO (NET.System.Decimal.Decimal a3) --round_3 arg0 arg1 arg2 = invokeStatic "System.Decimal" "Round" (arg0, arg1, arg2) subtract :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) subtract arg0 arg1 = invokeStatic "System.Decimal" "Subtract" (arg0, arg1) toByte :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word8) toByte arg0 = invokeStatic "System.Decimal" "ToByte" (arg0) toSByte :: NET.System.Decimal.Decimal a0 -> IO (Data.Int.Int8) toSByte arg0 = invokeStatic "System.Decimal" "ToSByte" (arg0) toInt16 :: NET.System.Decimal.Decimal a0 -> IO (Data.Int.Int16) toInt16 arg0 = invokeStatic "System.Decimal" "ToInt16" (arg0) toDouble :: NET.System.Decimal.Decimal a0 -> IO (Double) toDouble arg0 = invokeStatic "System.Decimal" "ToDouble" (arg0) toInt32 :: NET.System.Decimal.Decimal a0 -> IO (Int) toInt32 arg0 = invokeStatic "System.Decimal" "ToInt32" (arg0) toInt64 :: NET.System.Decimal.Decimal a0 -> IO (Data.Int.Int64) toInt64 arg0 = invokeStatic "System.Decimal" "ToInt64" (arg0) toUInt16 :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word16) toUInt16 arg0 = invokeStatic "System.Decimal" "ToUInt16" (arg0) toUInt32 :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word32) toUInt32 arg0 = invokeStatic "System.Decimal" "ToUInt32" (arg0) toUInt64 :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word64) toUInt64 arg0 = invokeStatic "System.Decimal" "ToUInt64" (arg0) toSingle :: NET.System.Decimal.Decimal a0 -> IO (Double) toSingle arg0 = invokeStatic "System.Decimal" "ToSingle" (arg0) truncate :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) truncate arg0 = invokeStatic "System.Decimal" "Truncate" (arg0) op_Implicit :: Data.Word.Word8 -> IO (NET.System.Decimal.Decimal a1) op_Implicit arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_1 :: Data.Int.Int8 -> IO (NET.System.Decimal.Decimal a1) op_Implicit_1 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_2 :: Data.Int.Int16 -> IO (NET.System.Decimal.Decimal a1) op_Implicit_2 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_3 :: Data.Word.Word16 -> IO (NET.System.Decimal.Decimal a1) op_Implicit_3 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_4 :: Char -> IO (NET.System.Decimal.Decimal a1) op_Implicit_4 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_5 :: Int -> IO (NET.System.Decimal.Decimal a1) op_Implicit_5 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_6 :: Data.Word.Word32 -> IO (NET.System.Decimal.Decimal a1) op_Implicit_6 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_7 :: Data.Int.Int64 -> IO (NET.System.Decimal.Decimal a1) op_Implicit_7 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Implicit_8 :: Data.Word.Word64 -> IO (NET.System.Decimal.Decimal a1) op_Implicit_8 arg0 = invokeStatic "System.Decimal" "op_Implicit" (arg0) op_Explicit :: Double -> IO (NET.System.Decimal.Decimal a1) op_Explicit arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_1 :: Double -> IO (NET.System.Decimal.Decimal a1) op_Explicit_1 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_2 :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word8) op_Explicit_2 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_3 :: NET.System.Decimal.Decimal a0 -> IO (Data.Int.Int8) op_Explicit_3 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_4 :: NET.System.Decimal.Decimal a0 -> IO (Char) op_Explicit_4 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_5 :: NET.System.Decimal.Decimal a0 -> IO (Data.Int.Int16) op_Explicit_5 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_6 :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word16) op_Explicit_6 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_7 :: NET.System.Decimal.Decimal a0 -> IO (Int) op_Explicit_7 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_8 :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word32) op_Explicit_8 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_9 :: NET.System.Decimal.Decimal a0 -> IO (Data.Int.Int64) op_Explicit_9 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_10 :: NET.System.Decimal.Decimal a0 -> IO (Data.Word.Word64) op_Explicit_10 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_11 :: NET.System.Decimal.Decimal a0 -> IO (Double) op_Explicit_11 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_Explicit_12 :: NET.System.Decimal.Decimal a0 -> IO (Double) op_Explicit_12 arg0 = invokeStatic "System.Decimal" "op_Explicit" (arg0) op_UnaryPlus :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) op_UnaryPlus arg0 = invokeStatic "System.Decimal" "op_UnaryPlus" (arg0) op_UnaryNegation :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) op_UnaryNegation arg0 = invokeStatic "System.Decimal" "op_UnaryNegation" (arg0) op_Increment :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) op_Increment arg0 = invokeStatic "System.Decimal" "op_Increment" (arg0) op_Decrement :: NET.System.Decimal.Decimal a0 -> IO (NET.System.Decimal.Decimal a1) op_Decrement arg0 = invokeStatic "System.Decimal" "op_Decrement" (arg0) op_Addition :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) op_Addition arg0 arg1 = invokeStatic "System.Decimal" "op_Addition" (arg0, arg1) op_Subtraction :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) op_Subtraction arg0 arg1 = invokeStatic "System.Decimal" "op_Subtraction" (arg0, arg1) op_Multiply :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) op_Multiply arg0 arg1 = invokeStatic "System.Decimal" "op_Multiply" (arg0, arg1) op_Division :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) op_Division arg0 arg1 = invokeStatic "System.Decimal" "op_Division" (arg0, arg1) op_Modulus :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (NET.System.Decimal.Decimal a2) op_Modulus arg0 arg1 = invokeStatic "System.Decimal" "op_Modulus" (arg0, arg1) op_Equality :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Bool) op_Equality arg0 arg1 = invokeStatic "System.Decimal" "op_Equality" (arg0, arg1) op_Inequality :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Bool) op_Inequality arg0 arg1 = invokeStatic "System.Decimal" "op_Inequality" (arg0, arg1) op_LessThan :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Bool) op_LessThan arg0 arg1 = invokeStatic "System.Decimal" "op_LessThan" (arg0, arg1) op_LessThanOrEqual :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Bool) op_LessThanOrEqual arg0 arg1 = invokeStatic "System.Decimal" "op_LessThanOrEqual" (arg0, arg1) op_GreaterThan :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Bool) op_GreaterThan arg0 arg1 = invokeStatic "System.Decimal" "op_GreaterThan" (arg0, arg1) op_GreaterThanOrEqual :: NET.System.Decimal.Decimal a0 -> NET.System.Decimal.Decimal a1 -> IO (Bool) op_GreaterThanOrEqual arg0 arg1 = invokeStatic "System.Decimal" "op_GreaterThanOrEqual" (arg0, arg1) getTypeCode :: Decimal obj -> IO (NET.System.TypeCode.TypeCode a0) getTypeCode = invoke "GetTypeCode" () get_Zero :: IO (NET.System.Decimal.Decimal a0) get_Zero = getFieldStatic "System.Decimal" "Zero" () get_One :: IO (NET.System.Decimal.Decimal a0) get_One = getFieldStatic "System.Decimal" "One" () get_MinusOne :: IO (NET.System.Decimal.Decimal a0) get_MinusOne = getFieldStatic "System.Decimal" "MinusOne" () get_MaxValue :: IO (NET.System.Decimal.Decimal a0) get_MaxValue = getFieldStatic "System.Decimal" "MaxValue" () get_MinValue :: IO (NET.System.Decimal.Decimal a0) get_MinValue = getFieldStatic "System.Decimal" "MinValue" ()