DAML-LF: Prepare archive proto for Numeric (#2298)

* daml-lf: prepare archive proto for Numeric

* replace DECIMAL by NUMERIC in messages and fields
* add nat kind and nat type
* add builtins CAST_NUMERIC and SHIFT_NUMERIC

* daml-lf: remove new builtins from archive proto

* daml-lf: some more doc about numeric

* daml-lf: fix spec
This commit is contained in:
Remy 2019-07-29 20:33:52 +02:00 committed by mergify[bot]
parent 0b56eedcea
commit 0ffe5945b8
8 changed files with 292 additions and 155 deletions

View File

@ -193,11 +193,11 @@ instance Pretty BuiltinExpr where
BEGreater t -> maybeParens (prec > precEApp) ("GREATER" <-> prettyBTyArg t)
BEGreaterEq t -> maybeParens (prec > precEApp) ("GREATER_EQ" <-> prettyBTyArg t)
BEToText t -> maybeParens (prec > precEApp) ("TO_TEXT" <-> prettyBTyArg t)
BEAddDecimal -> "ADD_DECIMAL"
BESubDecimal -> "SUB_DECIMAL"
BEMulDecimal -> "MUL_DECIMAL"
BEDivDecimal -> "DIV_DECIMAL"
BERoundDecimal -> "ROUND_DECIMAL"
BEAddDecimal -> "ADD_NUMERIC"
BESubDecimal -> "SUB_NUMERIC"
BEMulDecimal -> "MUL_NUMERIC"
BEDivDecimal -> "DIV_NUMERIC"
BERoundDecimal -> "ROUND_NUMERIC"
BEAddInt64 -> "ADD_INT64"
BESubInt64 -> "SUB_INT64"
BEMulInt64 -> "MUL_INT64"
@ -216,8 +216,8 @@ instance Pretty BuiltinExpr where
BEAppendText -> "APPEND_TEXT"
BETimestamp ts -> pretty (timestampToText ts)
BEDate date -> pretty (dateToText date)
BEInt64ToDecimal -> "INT64_TO_DECIMAL"
BEDecimalToInt64 -> "DECIMAL_TO_INT64"
BEInt64ToDecimal -> "INT64_TO_NUMERIC"
BEDecimalToInt64 -> "NUMERIC_TO_INT64"
BETimestampToUnixMicroseconds -> "TIMESTAMP_TO_UNIX_MICROSECONDS"
BEUnixMicrosecondsToTimestamp -> "UNIX_MICROSECONDS_TO_TIMESTAMP"
BEDateToUnixDays -> "DATE_TO_UNIX_DAYS"
@ -229,7 +229,7 @@ instance Pretty BuiltinExpr where
BEEqualContractId -> "EQUAL_CONTRACT_ID"
BEPartyFromText -> "FROM_TEXT_PARTY"
BEInt64FromText -> "FROM_TEXT_INT64"
BEDecimalFromText -> "FROM_TEXT_DECIMAL"
BEDecimalFromText -> "FROM_TEXT_NUMERIC"
BEPartyToQuotedText -> "PARTY_TO_QUOTED_TEXT"
BETextToCodePoints -> "TEXT_TO_CODE_POINTS"
BETextFromCodePoints -> "TEXT_FROM_CODE_POINTS"

View File

@ -167,7 +167,7 @@ decodeChoice LF1.TemplateChoice{..} =
decodeBuiltinFunction :: MonadDecode m => LF1.BuiltinFunction -> m BuiltinExpr
decodeBuiltinFunction = pure . \case
LF1.BuiltinFunctionEQUAL_INT64 -> BEEqual BTInt64
LF1.BuiltinFunctionEQUAL_DECIMAL -> BEEqual BTDecimal
LF1.BuiltinFunctionEQUAL_NUMERIC -> BEEqual BTDecimal
LF1.BuiltinFunctionEQUAL_TEXT -> BEEqual BTText
LF1.BuiltinFunctionEQUAL_TIMESTAMP -> BEEqual BTTimestamp
LF1.BuiltinFunctionEQUAL_DATE -> BEEqual BTDate
@ -175,35 +175,35 @@ decodeBuiltinFunction = pure . \case
LF1.BuiltinFunctionEQUAL_BOOL -> BEEqual BTBool
LF1.BuiltinFunctionLEQ_INT64 -> BELessEq BTInt64
LF1.BuiltinFunctionLEQ_DECIMAL -> BELessEq BTDecimal
LF1.BuiltinFunctionLEQ_NUMERIC -> BELessEq BTDecimal
LF1.BuiltinFunctionLEQ_TEXT -> BELessEq BTText
LF1.BuiltinFunctionLEQ_TIMESTAMP -> BELessEq BTTimestamp
LF1.BuiltinFunctionLEQ_DATE -> BELessEq BTDate
LF1.BuiltinFunctionLEQ_PARTY -> BELessEq BTParty
LF1.BuiltinFunctionLESS_INT64 -> BELess BTInt64
LF1.BuiltinFunctionLESS_DECIMAL -> BELess BTDecimal
LF1.BuiltinFunctionLESS_NUMERIC -> BELess BTDecimal
LF1.BuiltinFunctionLESS_TEXT -> BELess BTText
LF1.BuiltinFunctionLESS_TIMESTAMP -> BELess BTTimestamp
LF1.BuiltinFunctionLESS_DATE -> BELess BTDate
LF1.BuiltinFunctionLESS_PARTY -> BELess BTParty
LF1.BuiltinFunctionGEQ_INT64 -> BEGreaterEq BTInt64
LF1.BuiltinFunctionGEQ_DECIMAL -> BEGreaterEq BTDecimal
LF1.BuiltinFunctionGEQ_NUMERIC -> BEGreaterEq BTDecimal
LF1.BuiltinFunctionGEQ_TEXT -> BEGreaterEq BTText
LF1.BuiltinFunctionGEQ_TIMESTAMP -> BEGreaterEq BTTimestamp
LF1.BuiltinFunctionGEQ_DATE -> BEGreaterEq BTDate
LF1.BuiltinFunctionGEQ_PARTY -> BEGreaterEq BTParty
LF1.BuiltinFunctionGREATER_INT64 -> BEGreater BTInt64
LF1.BuiltinFunctionGREATER_DECIMAL -> BEGreater BTDecimal
LF1.BuiltinFunctionGREATER_NUMERIC -> BEGreater BTDecimal
LF1.BuiltinFunctionGREATER_TEXT -> BEGreater BTText
LF1.BuiltinFunctionGREATER_TIMESTAMP -> BEGreater BTTimestamp
LF1.BuiltinFunctionGREATER_DATE -> BEGreater BTDate
LF1.BuiltinFunctionGREATER_PARTY -> BEGreater BTParty
LF1.BuiltinFunctionTO_TEXT_INT64 -> BEToText BTInt64
LF1.BuiltinFunctionTO_TEXT_DECIMAL -> BEToText BTDecimal
LF1.BuiltinFunctionTO_TEXT_NUMERIC -> BEToText BTDecimal
LF1.BuiltinFunctionTO_TEXT_TEXT -> BEToText BTText
LF1.BuiltinFunctionTO_TEXT_TIMESTAMP -> BEToText BTTimestamp
LF1.BuiltinFunctionTO_TEXT_PARTY -> BEToText BTParty
@ -211,15 +211,15 @@ decodeBuiltinFunction = pure . \case
LF1.BuiltinFunctionTEXT_FROM_CODE_POINTS -> BETextFromCodePoints
LF1.BuiltinFunctionFROM_TEXT_PARTY -> BEPartyFromText
LF1.BuiltinFunctionFROM_TEXT_INT64 -> BEInt64FromText
LF1.BuiltinFunctionFROM_TEXT_DECIMAL -> BEDecimalFromText
LF1.BuiltinFunctionFROM_TEXT_NUMERIC -> BEDecimalFromText
LF1.BuiltinFunctionTEXT_TO_CODE_POINTS -> BETextToCodePoints
LF1.BuiltinFunctionTO_QUOTED_TEXT_PARTY -> BEPartyToQuotedText
LF1.BuiltinFunctionADD_DECIMAL -> BEAddDecimal
LF1.BuiltinFunctionSUB_DECIMAL -> BESubDecimal
LF1.BuiltinFunctionMUL_DECIMAL -> BEMulDecimal
LF1.BuiltinFunctionDIV_DECIMAL -> BEDivDecimal
LF1.BuiltinFunctionROUND_DECIMAL -> BERoundDecimal
LF1.BuiltinFunctionADD_NUMERIC -> BEAddDecimal
LF1.BuiltinFunctionSUB_NUMERIC -> BESubDecimal
LF1.BuiltinFunctionMUL_NUMERIC -> BEMulDecimal
LF1.BuiltinFunctionDIV_NUMERIC -> BEDivDecimal
LF1.BuiltinFunctionROUND_NUMERIC -> BERoundDecimal
LF1.BuiltinFunctionADD_INT64 -> BEAddInt64
LF1.BuiltinFunctionSUB_INT64 -> BESubInt64
@ -250,8 +250,8 @@ decodeBuiltinFunction = pure . \case
LF1.BuiltinFunctionTIMESTAMP_TO_UNIX_MICROSECONDS -> BETimestampToUnixMicroseconds
LF1.BuiltinFunctionUNIX_MICROSECONDS_TO_TIMESTAMP -> BEUnixMicrosecondsToTimestamp
LF1.BuiltinFunctionINT64_TO_DECIMAL -> BEInt64ToDecimal
LF1.BuiltinFunctionDECIMAL_TO_INT64 -> BEDecimalToInt64
LF1.BuiltinFunctionINT64_TO_NUMERIC -> BEInt64ToDecimal
LF1.BuiltinFunctionNUMERIC_TO_INT64 -> BEDecimalToInt64
LF1.BuiltinFunctionTRACE -> BETrace
LF1.BuiltinFunctionEQUAL_CONTRACT_ID -> BEEqualContractId
@ -477,7 +477,7 @@ decodeVarWithType LF1.VarWithType{..} =
decodePrimLit :: MonadDecode m => LF1.PrimLit -> m BuiltinExpr
decodePrimLit (LF1.PrimLit mbSum) = mayDecode "primLitSum" mbSum $ \case
LF1.PrimLitSumInt64 sInt -> pure $ BEInt64 sInt
LF1.PrimLitSumDecimal sDec -> case readMaybe (TL.unpack sDec) of
LF1.PrimLitSumNumeric sDec -> case readMaybe (TL.unpack sDec) of
Nothing -> throwError $ ParseError ("bad fixed while decoding Decimal: '" <> TL.unpack sDec <> "'")
Just dec -> return (BEDecimal dec)
LF1.PrimLitSumTimestamp sTime -> pure $ BETimestamp sTime
@ -491,11 +491,14 @@ decodeKind LF1.Kind{..} = mayDecode "kindSum" kindSum $ \case
LF1.KindSumArrow (LF1.Kind_Arrow params mbResult) -> do
result <- mayDecode "kind_ArrowResult" mbResult decodeKind
foldr KArrow result <$> traverse decodeKind (V.toList params)
LF1.KindSumNat LF1.Unit ->
-- FixMe https://github.com/digital-asset/daml/issues/2289
throwError $ ParseError "nat kind not supported"
decodePrim :: LF1.PrimType -> Decode BuiltinType
decodePrim = pure . \case
LF1.PrimTypeINT64 -> BTInt64
LF1.PrimTypeDECIMAL -> BTDecimal
LF1.PrimTypeNUMERIC -> BTDecimal
LF1.PrimTypeTEXT -> BTText
LF1.PrimTypeTIMESTAMP -> BTTimestamp
LF1.PrimTypePARTY -> BTParty
@ -529,6 +532,9 @@ decodeType LF1.Type{..} = mayDecode "typeSum" typeSum $ \case
decodeImpl $ foldr TForall body <$> traverse decodeTypeVarWithKind (V.toList binders)
LF1.TypeSumTuple (LF1.Type_Tuple flds) ->
TTuple <$> mapM (decodeFieldWithType FieldName) (V.toList flds)
LF1.TypeSumNat _ ->
-- FixMe https://github.com/digital-asset/daml/issues/2289
throwError $ ParseError "nat type not supported"
where
decodeWithArgs :: V.Vector LF1.Type -> DecodeImpl Type -> DecodeImpl Type
decodeWithArgs args fun = foldl TApp <$> fun <*> traverse decodeType args

View File

@ -137,7 +137,7 @@ encodeKind version = P.Kind . Just . \case
encodeBuiltinType :: Version -> BuiltinType -> P.Enumerated P.PrimType
encodeBuiltinType _version = P.Enumerated . Right . \case
BTInt64 -> P.PrimTypeINT64
BTDecimal -> P.PrimTypeDECIMAL
BTDecimal -> P.PrimTypeNUMERIC
BTText -> P.PrimTypeTEXT
BTTimestamp -> P.PrimTypeTIMESTAMP
BTParty -> P.PrimTypePARTY
@ -189,7 +189,7 @@ encodeTypeConApp encctx@EncodeCtx{..} (TypeConApp tycon args) = Just $ P.Type_Co
encodeBuiltinExpr :: BuiltinExpr -> P.ExprSum
encodeBuiltinExpr = \case
BEInt64 x -> lit $ P.PrimLitSumInt64 x
BEDecimal dec -> lit $ P.PrimLitSumDecimal (TL.pack (show dec))
BEDecimal dec -> lit $ P.PrimLitSumNumeric (TL.pack (show dec))
BEText x -> lit $ P.PrimLitSumText (TL.fromStrict x)
BETimestamp x -> lit $ P.PrimLitSumTimestamp x
BEParty x -> lit $ P.PrimLitSumParty $ TL.fromStrict $ unPartyLiteral x
@ -202,7 +202,7 @@ encodeBuiltinExpr = \case
BEEqual typ -> case typ of
BTInt64 -> builtin P.BuiltinFunctionEQUAL_INT64
BTDecimal -> builtin P.BuiltinFunctionEQUAL_DECIMAL
BTDecimal -> builtin P.BuiltinFunctionEQUAL_NUMERIC
BTText -> builtin P.BuiltinFunctionEQUAL_TEXT
BTTimestamp -> builtin P.BuiltinFunctionEQUAL_TIMESTAMP
BTDate -> builtin P.BuiltinFunctionEQUAL_DATE
@ -212,7 +212,7 @@ encodeBuiltinExpr = \case
BELessEq typ -> case typ of
BTInt64 -> builtin P.BuiltinFunctionLEQ_INT64
BTDecimal -> builtin P.BuiltinFunctionLEQ_DECIMAL
BTDecimal -> builtin P.BuiltinFunctionLEQ_NUMERIC
BTText -> builtin P.BuiltinFunctionLEQ_TEXT
BTTimestamp -> builtin P.BuiltinFunctionLEQ_TIMESTAMP
BTDate -> builtin P.BuiltinFunctionLEQ_DATE
@ -221,7 +221,7 @@ encodeBuiltinExpr = \case
BELess typ -> case typ of
BTInt64 -> builtin P.BuiltinFunctionLESS_INT64
BTDecimal -> builtin P.BuiltinFunctionLESS_DECIMAL
BTDecimal -> builtin P.BuiltinFunctionLESS_NUMERIC
BTText -> builtin P.BuiltinFunctionLESS_TEXT
BTTimestamp -> builtin P.BuiltinFunctionLESS_TIMESTAMP
BTDate -> builtin P.BuiltinFunctionLESS_DATE
@ -230,7 +230,7 @@ encodeBuiltinExpr = \case
BEGreaterEq typ -> case typ of
BTInt64 -> builtin P.BuiltinFunctionGEQ_INT64
BTDecimal -> builtin P.BuiltinFunctionGEQ_DECIMAL
BTDecimal -> builtin P.BuiltinFunctionGEQ_NUMERIC
BTText -> builtin P.BuiltinFunctionGEQ_TEXT
BTTimestamp -> builtin P.BuiltinFunctionGEQ_TIMESTAMP
BTDate -> builtin P.BuiltinFunctionGEQ_DATE
@ -239,7 +239,7 @@ encodeBuiltinExpr = \case
BEGreater typ -> case typ of
BTInt64 -> builtin P.BuiltinFunctionGREATER_INT64
BTDecimal -> builtin P.BuiltinFunctionGREATER_DECIMAL
BTDecimal -> builtin P.BuiltinFunctionGREATER_NUMERIC
BTText -> builtin P.BuiltinFunctionGREATER_TEXT
BTTimestamp -> builtin P.BuiltinFunctionGREATER_TIMESTAMP
BTDate -> builtin P.BuiltinFunctionGREATER_DATE
@ -248,7 +248,7 @@ encodeBuiltinExpr = \case
BEToText typ -> case typ of
BTInt64 -> builtin P.BuiltinFunctionTO_TEXT_INT64
BTDecimal -> builtin P.BuiltinFunctionTO_TEXT_DECIMAL
BTDecimal -> builtin P.BuiltinFunctionTO_TEXT_NUMERIC
BTText -> builtin P.BuiltinFunctionTO_TEXT_TEXT
BTTimestamp -> builtin P.BuiltinFunctionTO_TEXT_TIMESTAMP
BTDate -> builtin P.BuiltinFunctionTO_TEXT_DATE
@ -257,15 +257,15 @@ encodeBuiltinExpr = \case
BETextFromCodePoints -> builtin P.BuiltinFunctionTEXT_FROM_CODE_POINTS
BEPartyFromText -> builtin P.BuiltinFunctionFROM_TEXT_PARTY
BEInt64FromText -> builtin P.BuiltinFunctionFROM_TEXT_INT64
BEDecimalFromText-> builtin P.BuiltinFunctionFROM_TEXT_DECIMAL
BEDecimalFromText-> builtin P.BuiltinFunctionFROM_TEXT_NUMERIC
BETextToCodePoints -> builtin P.BuiltinFunctionTEXT_TO_CODE_POINTS
BEPartyToQuotedText -> builtin P.BuiltinFunctionTO_QUOTED_TEXT_PARTY
BEAddDecimal -> builtin P.BuiltinFunctionADD_DECIMAL
BESubDecimal -> builtin P.BuiltinFunctionSUB_DECIMAL
BEMulDecimal -> builtin P.BuiltinFunctionMUL_DECIMAL
BEDivDecimal -> builtin P.BuiltinFunctionDIV_DECIMAL
BERoundDecimal -> builtin P.BuiltinFunctionROUND_DECIMAL
BEAddDecimal -> builtin P.BuiltinFunctionADD_NUMERIC
BESubDecimal -> builtin P.BuiltinFunctionSUB_NUMERIC
BEMulDecimal -> builtin P.BuiltinFunctionMUL_NUMERIC
BEDivDecimal -> builtin P.BuiltinFunctionDIV_NUMERIC
BERoundDecimal -> builtin P.BuiltinFunctionROUND_NUMERIC
BEAddInt64 -> builtin P.BuiltinFunctionADD_INT64
BESubInt64 -> builtin P.BuiltinFunctionSUB_INT64
@ -274,8 +274,8 @@ encodeBuiltinExpr = \case
BEModInt64 -> builtin P.BuiltinFunctionMOD_INT64
BEExpInt64 -> builtin P.BuiltinFunctionEXP_INT64
BEInt64ToDecimal -> builtin P.BuiltinFunctionINT64_TO_DECIMAL
BEDecimalToInt64 -> builtin P.BuiltinFunctionDECIMAL_TO_INT64
BEInt64ToDecimal -> builtin P.BuiltinFunctionINT64_TO_NUMERIC
BEDecimalToInt64 -> builtin P.BuiltinFunctionNUMERIC_TO_INT64
BEFoldl -> builtin P.BuiltinFunctionFOLDL
BEFoldr -> builtin P.BuiltinFunctionFOLDR

View File

@ -166,8 +166,11 @@ message Kind {
oneof Sum {
// Kind of monomorphic type.
Unit star = 1;
// King of polymorphic type.
// Kind of polymorphic type.
Arrow arrow = 2;
// kind of TNat type;
// *Available since version 1.dev*
Unit nat = 3;
}
}
@ -182,8 +185,9 @@ enum PrimType {
// Builtin type 'Int64'
INT64 = 2;
// Builtin type 'Int64'
DECIMAL = 3;
// Builtin type 'Numeric'
// was named `DECIMAL` in version 1.6 or earlier
NUMERIC = 3;
// CHAR = 4; // we have removed this in favor of TEXT for everything text related.
@ -204,7 +208,7 @@ enum PrimType {
// Builtin type 'Update'
UPDATE = 10;
// Builtin type 'Scenatrio'
// Builtin type 'Scenario'
SCENARIO = 11;
// Builtin type 'Date'
@ -294,9 +298,13 @@ message Type {
Fun fun = 4;
Forall forall = 5;
Tuple tuple = 7;
// *Available since version 1.dev*
// *Must be between 0 and 38 (bounds inclusive)*
// use standard signed long for future usage.
sint64 nat = 11;
}
reserved 6; // This was list. Removed in favour of PrimType.LIST
reserved 6; // This was list. Removed in favour of PrimType.LIST
reserved 8; // This was contract_id. Removed in favour of PrimType.CONTRACT_ID
reserved 9; // This was update. Removed in favour of PrimType.UPDATE
reserved 10; // This was scenario. Removed in favor of PrimType.SCENARIO
@ -319,11 +327,11 @@ enum PrimCon {
// Builtin functions
// Refer to DAML-LF major version 1 specification for types and behavior of those.
enum BuiltinFunction {
ADD_DECIMAL = 0;
SUB_DECIMAL = 1;
MUL_DECIMAL = 2;
DIV_DECIMAL = 3;
ROUND_DECIMAL = 6;
ADD_NUMERIC = 0; // Called `ADD_DECIMAL` in version 1.6 or earlier
SUB_NUMERIC = 1; // Called `SUB_DECIMAL` in version 1.6 or earlier
MUL_NUMERIC = 2; // Called `MUL_DECIMAL` in version 1.6 or earlier
DIV_NUMERIC = 3; // Called `DIV_DECIMAL` in version 1.6 or earlier
ROUND_NUMERIC = 6; // Called `DIV_DECIMAL` in version 1.6 or earlier
ADD_INT64 = 7;
SUB_INT64 = 8;
@ -348,35 +356,35 @@ enum BuiltinFunction {
ERROR = 25;
LEQ_INT64 = 33;
LEQ_DECIMAL = 34;
LEQ_NUMERIC = 34; // Called `LEQ_DECIMAL` in version 1.6 or earlier
LEQ_TEXT = 36;
LEQ_TIMESTAMP = 37;
LEQ_DATE = 67;
LEQ_PARTY = 89; // *Available Since version 1.1*
LESS_INT64 = 39;
LESS_DECIMAL = 40;
LESS_NUMERIC = 40; // Called `LESS_DECIMAL` in version 1.6 or earlier
LESS_TEXT = 42;
LESS_TIMESTAMP = 43;
LESS_DATE = 68;
LESS_PARTY = 90; // *Available Since version 1.1*
GEQ_INT64 = 45;
GEQ_DECIMAL = 46;
GEQ_NUMERIC = 46; // Called `GEQ_DECIMAL` in version 1.6 or earlier
GEQ_TEXT = 48;
GEQ_TIMESTAMP = 49;
GEQ_DATE = 69;
GEQ_PARTY = 91; // *Available Since version 1.1*
GREATER_INT64 = 51;
GREATER_DECIMAL = 52;
GREATER_NUMERIC = 52; // Called `GREATED_DECIMAL` in version 1.6 or earlier
GREATER_TEXT = 54;
GREATER_TIMESTAMP = 55;
GREATER_DATE = 70;
GREATER_PARTY = 92; // *Available Since version 1.1*
TO_TEXT_INT64 = 57;
TO_TEXT_DECIMAL = 58;
TO_TEXT_NUMERIC = 58; // Called `GREATED_DECIMAL` in version 1.6 or earlier
TO_TEXT_TEXT = 60;
TO_TEXT_TIMESTAMP = 61;
TO_TEXT_DATE = 71;
@ -384,7 +392,7 @@ enum BuiltinFunction {
TO_TEXT_PARTY = 94; // *Available Since version 1.2*
FROM_TEXT_PARTY = 95; // *Available Since version 1.2*, was named FROM_TEXT_PARTY in 1.2, 1.3 and 1.4
FROM_TEXT_INT64 = 103; // *Available Since version 1.5*
FROM_TEXT_DECIMAL = 104; // *Available Since version 1.5*
FROM_TEXT_NUMERIC = 104; // *Available Since version 1.5*, was named `GREATER_DECIMAL` in version 1.5 and 1.6
SHA256_TEXT = 93; // *Available Since version 1.2*
DATE_TO_UNIX_DAYS = 72; // Date -> Int64
@ -393,13 +401,13 @@ enum BuiltinFunction {
TIMESTAMP_TO_UNIX_MICROSECONDS = 74; // Timestamp -> Int64
UNIX_MICROSECONDS_TO_TIMESTAMP = 75; // Int64 -> Timestamp
INT64_TO_DECIMAL = 76;
DECIMAL_TO_INT64 = 77;
INT64_TO_NUMERIC = 76; // was named `INT64_TO_NUMERIC` in version 1.6 or earlier
NUMERIC_TO_INT64 = 77; // was named `NUMERIC_TO_INT64` in version 1.6 or earlier
IMPLODE_TEXT = 78;
EQUAL_INT64 = 79;
EQUAL_DECIMAL = 80;
EQUAL_NUMERIC = 80; // was named `EQUAL_NUMERIC` in version 1.6 or earlier
EQUAL_TEXT = 81;
EQUAL_TIMESTAMP = 82;
EQUAL_DATE = 83;
@ -412,8 +420,8 @@ enum BuiltinFunction {
COERCE_CONTRACT_ID = 102;
TEXT_FROM_CODE_POINTS = 105; // : List Int64 -> Text *Available since version 1.6*
TEXT_TO_CODE_POINTS = 106; //: Text -> List Int64 *Available since version 1.6*
TEXT_FROM_CODE_POINTS = 105; // *Available since version 1.6*
TEXT_TO_CODE_POINTS = 106; // *Available since version 1.6*
// Next id is 107. 106 is TEXT_TO_CODE_POINTS.
}
@ -436,7 +444,7 @@ message PrimLit {
// It would fit in an int128, but sadly protobuf does not have
// one. so, string it is. note that we can't store the whole and
// decimal part in two numbers either, because 10^28 > 2^63.
string decimal = 2;
string numeric = 2;
// Unicode string literal ('LitText')
string text = 4;

View File

@ -244,6 +244,9 @@ private[archive] class DecodeV1(minor: LanguageMinorVersion) extends Decode.OfPa
val params = kArrow.getParamsList.asScala
assertNonEmpty(params, "params")
(params :\ decodeKind(kArrow.getResult))((param, kind) => KArrow(decodeKind(param), kind))
case PLF.Kind.SumCase.NAT =>
// FixMe: https://github.com/digital-asset/daml/issues/2289
throw new Error("nat kind not supported")
case PLF.Kind.SumCase.SUM_NOT_SET =>
throw ParseError("Kind.SUM_NOT_SET")
}
@ -283,6 +286,9 @@ private[archive] class DecodeV1(minor: LanguageMinorVersion) extends Decode.OfPa
TTuple(
ImmArray(fields.map(ft => name(ft.getField) -> decodeType(ft.getType)))
)
case PLF.Type.SumCase.NAT =>
// FixMe: https://github.com/digital-asset/daml/issues/2289
throw new Error("nat type not supported")
case PLF.Type.SumCase.SUM_NOT_SET =>
throw ParseError("Type.SUM_NOT_SET")
@ -664,9 +670,9 @@ private[archive] class DecodeV1(minor: LanguageMinorVersion) extends Decode.OfPa
lfPrimLit.getSumCase match {
case PLF.PrimLit.SumCase.INT64 =>
PLInt64(lfPrimLit.getInt64)
case PLF.PrimLit.SumCase.DECIMAL =>
checkDecimal(lfPrimLit.getDecimal)
val d = Decimal.fromString(lfPrimLit.getDecimal)
case PLF.PrimLit.SumCase.NUMERIC =>
checkDecimal(lfPrimLit.getNumeric)
val d = Decimal.fromString(lfPrimLit.getNumeric)
d.fold(e => throw ParseError("error parsing decimal: " + e), PLDecimal)
case PLF.PrimLit.SumCase.TEXT =>
PLText(lfPrimLit.getText)
@ -716,7 +722,7 @@ private[lf] object DecodeV1 {
BOOL -> (BTBool -> "0"),
TEXT -> (BTText -> "0"),
INT64 -> (BTInt64 -> "0"),
DECIMAL -> (BTDecimal -> "0"),
NUMERIC -> (BTDecimal -> "0"),
TIMESTAMP -> (BTTimestamp -> "0"),
PARTY -> (BTParty -> "0"),
LIST -> (BTList -> "0"),
@ -734,19 +740,19 @@ private[lf] object DecodeV1 {
import PLF.BuiltinFunction._
Map[PLF.BuiltinFunction, (Ast.BuiltinFunction, LanguageMinorVersion)](
ADD_DECIMAL -> (BAddDecimal -> "0"),
SUB_DECIMAL -> (BSubDecimal -> "0"),
MUL_DECIMAL -> (BMulDecimal -> "0"),
DIV_DECIMAL -> (BDivDecimal -> "0"),
ROUND_DECIMAL -> (BRoundDecimal -> "0"),
ADD_NUMERIC -> (BAddDecimal -> "0"),
SUB_NUMERIC -> (BSubDecimal -> "0"),
MUL_NUMERIC -> (BMulDecimal -> "0"),
DIV_NUMERIC -> (BDivDecimal -> "0"),
ROUND_NUMERIC -> (BRoundDecimal -> "0"),
ADD_INT64 -> (BAddInt64 -> "0"),
SUB_INT64 -> (BSubInt64 -> "0"),
MUL_INT64 -> (BMulInt64 -> "0"),
DIV_INT64 -> (BDivInt64 -> "0"),
MOD_INT64 -> (BModInt64 -> "0"),
EXP_INT64 -> (BExpInt64 -> "0"),
INT64_TO_DECIMAL -> (BInt64ToDecimal -> "0"),
DECIMAL_TO_INT64 -> (BDecimalToInt64 -> "0"),
INT64_TO_NUMERIC -> (BInt64ToDecimal -> "0"),
NUMERIC_TO_INT64 -> (BDecimalToInt64 -> "0"),
FOLDL -> (BFoldl -> "0"),
FOLDR -> (BFoldr -> "0"),
MAP_EMPTY -> (BMapEmpty -> "3"),
@ -758,27 +764,27 @@ private[lf] object DecodeV1 {
APPEND_TEXT -> (BAppendText -> "0"),
ERROR -> (BError -> "0"),
LEQ_INT64 -> (BLessEqInt64 -> "0"),
LEQ_DECIMAL -> (BLessEqDecimal -> "0"),
LEQ_NUMERIC -> (BLessEqDecimal -> "0"),
LEQ_TEXT -> (BLessEqText -> "0"),
LEQ_TIMESTAMP -> (BLessEqTimestamp -> "0"),
LEQ_PARTY -> (BLessEqParty -> "1"),
GEQ_INT64 -> (BGreaterEqInt64 -> "0"),
GEQ_DECIMAL -> (BGreaterEqDecimal -> "0"),
GEQ_NUMERIC -> (BGreaterEqDecimal -> "0"),
GEQ_TEXT -> (BGreaterEqText -> "0"),
GEQ_TIMESTAMP -> (BGreaterEqTimestamp -> "0"),
GEQ_PARTY -> (BGreaterEqParty -> "1"),
LESS_INT64 -> (BLessInt64 -> "0"),
LESS_DECIMAL -> (BLessDecimal -> "0"),
LESS_NUMERIC -> (BLessDecimal -> "0"),
LESS_TEXT -> (BLessText -> "0"),
LESS_TIMESTAMP -> (BLessTimestamp -> "0"),
LESS_PARTY -> (BLessParty -> "1"),
GREATER_INT64 -> (BGreaterInt64 -> "0"),
GREATER_DECIMAL -> (BGreaterDecimal -> "0"),
GREATER_NUMERIC -> (BGreaterDecimal -> "0"),
GREATER_TEXT -> (BGreaterText -> "0"),
GREATER_TIMESTAMP -> (BGreaterTimestamp -> "0"),
GREATER_PARTY -> (BGreaterParty -> "1"),
TO_TEXT_INT64 -> (BToTextInt64 -> "0"),
TO_TEXT_DECIMAL -> (BToTextDecimal -> "0"),
TO_TEXT_NUMERIC -> (BToTextDecimal -> "0"),
TO_TEXT_TIMESTAMP -> (BToTextTimestamp -> "0"),
TO_TEXT_PARTY -> (BToTextParty -> "2"),
TO_TEXT_TEXT -> (BToTextText -> "0"),
@ -786,7 +792,7 @@ private[lf] object DecodeV1 {
TEXT_FROM_CODE_POINTS -> (BToTextCodePoints -> "6"),
FROM_TEXT_PARTY -> (BFromTextParty -> "2"),
FROM_TEXT_INT64 -> (BFromTextInt64 -> "5"),
FROM_TEXT_DECIMAL -> (BFromTextDecimal -> "5"),
FROM_TEXT_NUMERIC -> (BFromTextDecimal -> "5"),
TEXT_TO_CODE_POINTS -> (BFromTextCodePoints -> "6"),
SHA256_TEXT -> (BSHA256Text -> "2"),
DATE_TO_UNIX_DAYS -> (BDateToUnixDays -> "0"),
@ -801,7 +807,7 @@ private[lf] object DecodeV1 {
UNIX_MICROSECONDS_TO_TIMESTAMP -> (BUnixMicrosecondsToTimestamp -> "0"),
GREATER_DATE -> (BGreaterDate -> "0"),
EQUAL_INT64 -> (BEqualInt64 -> "0"),
EQUAL_DECIMAL -> (BEqualDecimal -> "0"),
EQUAL_NUMERIC -> (BEqualDecimal -> "0"),
EQUAL_TEXT -> (BEqualText -> "0"),
EQUAL_TIMESTAMP -> (BEqualTimestamp -> "0"),
EQUAL_DATE -> (BEqualDate -> "0"),

View File

@ -334,7 +334,7 @@ private[digitalasset] class EncodeV1(val minor: LanguageMinorVersion) {
val builder = PLF.PrimLit.newBuilder()
primLit match {
case PLInt64(value) => builder.setInt64(value)
case PLDecimal(value) => builder.setDecimal(Decimal.toString(value))
case PLDecimal(value) => builder.setNumeric(Decimal.toString(value))
case PLText(value) => builder.setText(value)
case PLTimestamp(value) => builder.setTimestamp(value.micros)
case PLParty(party) => builder.setParty(party)

View File

@ -286,6 +286,9 @@ object InterfaceReader {
case TSC.STAR => name(a.getVar)
case TSC.ARROW =>
-\/(UnserializableDataType(s"non-star-kinded type variable: ${showKind(a.getKind)}"))
case TSC.NAT =>
// FixMe: https://github.com/digital-asset/daml/issues/2289
-\/(InvalidDataTypeDefinition("DamlLf1.Kind.SumCase.NAT"))
case TSC.SUM_NOT_SET =>
-\/(InvalidDataTypeDefinition("DamlLf1.Kind.SumCase.SUM_NOT_SET"))
}
@ -320,6 +323,9 @@ object InterfaceReader {
case TSC.PRIM => primitiveType(a.getPrim, ctx)
case sc @ (TSC.FUN | TSC.FORALL | TSC.TUPLE) =>
-\/(unserializableDataType(a, s"Unserializable data type: DamlLf1.Type.SumCase.${sc.name}"))
case TSC.NAT =>
// FixMe: https://github.com/digital-asset/daml/issues/2289
-\/(invalidDataTypeDefinition(a, "DamlLf1.Type.SumCase.NAT"))
case TSC.SUM_NOT_SET =>
-\/(invalidDataTypeDefinition(a, "DamlLf1.Type.SumCase.SUM_NOT_SET"))
}
@ -375,7 +381,7 @@ object InterfaceReader {
case PT.UNIT => \/-((0, PrimType.Unit))
case PT.BOOL => \/-((0, PrimType.Bool))
case PT.INT64 => \/-((0, PrimType.Int64))
case PT.DECIMAL => \/-((0, PrimType.Decimal))
case PT.NUMERIC => \/-((0, PrimType.Decimal))
case PT.TEXT => \/-((0, PrimType.Text))
case PT.DATE => \/-((0, PrimType.Date))
case PT.TIMESTAMP => \/-((0, PrimType.Timestamp))

View File

@ -233,7 +233,10 @@ Version: 1.dev
* Description:
* **Change** nothing yet.
* **Add** Nat kind and Nat type.
* **Replace** fixed scaled 'Decimal' type by parametric scaled
'Numeric' typer.
Abstract syntax
@ -332,9 +335,9 @@ be escaped with backslash ``\\``. DAML-LF considers legal `Unicode
code point <https://unicode.org/glossary/#code_point>` that is not a
`Surrogate Code Point
<https://unicode.org/glossary/#surrogate_code_point>`, in other words
any code point with an integer value in the range from
`0x000000` to `0x00D7FF` or in the range from `0x00DFFF` to `0x10FFFF`
(bounds included).
any code point with an integer value in the range from ``0x000000`` to
``0x00D7FF`` or in the range from ``0x00DFFF`` to ``0x10FFFF`` (bounds
included).
Then, we define the so-called *PackageId strings* and *PartyId
@ -366,11 +369,14 @@ and other similar pitfalls. ::
We can now define all the literals that a program can handle::
64-bits integer literals:
LitInt64 ∈ (-?)[0-9]+ -- LitInt64:
Nat type literals: -- LitNatType
n ∈ \d+
Decimal literals:
LitDecimal ∈ ([+-]?)\d{1,28}(.[0-9]\d{1-10})? -- LitDecimal
64-bits integer literals:
LitInt64 ∈ (-?)\d+ -- LitInt64:
Numeric literals:
LitNumeric ∈ ([+-]?)([1-9]\d+|0).\d* -- LitNumeric
Date literals:
LitDate ∈ \d{4}-\d{4}-\d{4} -- LitDate
@ -386,12 +392,16 @@ We can now define all the literals that a program can handle::
The literals represent actual DAML-LF values:
* A ``LitNatType`` represents a natural number between ``0`` and
``38``, bounds inclusive.
* A ``LitInt64`` represents a standard signed 64-bit integer (integer
between ``2⁶³`` to ``2⁶³1``).
* A ``LitDecimal`` represents a number in ``[(10³⁸1)÷10¹⁰,
(10³⁸1)÷10¹⁰]`` with at most 10 digits of decimal precision. In
other words, in base-10, a number with 28 digits before the decimal
point and up to 10 after the decimal point.
* A ``LitNumeric`` represents a signed number that can be represented
in base-10 without loss of precision with at most 38 digits
(ignoring possible leading 0 and with a scale (the number of
significant digits on the right of the decimal point) between ``0``
and ``38`` (bounds inclusive). In the following, we will use
``scale(LitNumeric)`` to denote the scale of the decimal number.
* A ``LitDate`` represents the number of day since
``1970-01-01`` with allowed range from ``0001-01-01`` to
``9999-12-31`` and using a year-month-day format.
@ -496,6 +506,7 @@ Then we can define our kinds, types, and expressions::
Kinds
k
::= ⋆ -- KindStar
| 'nat' -- KindNat
| k₁ → k₂ -- KindArrow
Module references
@ -506,7 +517,7 @@ Then we can define our kinds, types, and expressions::
BuiltinType
::= 'TArrow' -- BTArrow: Arrow type
| 'Int64' -- BTyInt64: 64-bit integer
| 'Decimal' -- BTyDecimal: decimal, precision 38, scale 10
| 'Numeric' -- BTyNumeric: numeric, precision 38, parametric scale between 0 and 38
| 'Text' -- BTyText: UTF-8 string
| 'Date' -- BTyDate
| 'Timestamp' -- BTyTime: UTC timestamp
@ -523,6 +534,7 @@ Then we can define our kinds, types, and expressions::
Types (mnemonic: tau for type)
τ, σ
::= α -- TyVar: Type variable
| n -- TNat: Nat Type
| τ σ -- TyApp: Type application
| ∀ α : k . τ -- TyForall: Universal quantification
| BuiltinType -- TyBuiltin: Builtin type
@ -545,7 +557,7 @@ Then we can define our kinds, types, and expressions::
| 'None' @τ -- ExpOptionNone: Empty Option
| 'Some' @τ e -- ExpOptionSome: Non-empty Option
| LitInt64 -- ExpLitInt64: 64-bit bit literal
| LitDecimal -- ExpLitDecimal: decimal literal
| LitNumeric -- ExpLitNumeric: Numeric literal
| LitText -- ExpLitText: UTF-8 string literal
| LitDate -- ExpLitDate: date literal
| LitTimestamp -- ExpLitTimestamp: UTC timestamp literal
@ -719,6 +731,9 @@ First, we formally defined *well-formed types*. ::
————————————————————————————————————————————— TyVar
Γ ⊢ α : k
————————————————————————————————————————————— TyVar
Γ ⊢ n : 'nat'
Γ ⊢ τ : k₁ → k₂ Γ ⊢ σ : k₂
————————————————————————————————————————————— TyApp
Γ ⊢ τ σ : k₁
@ -733,8 +748,8 @@ First, we formally defined *well-formed types*. ::
————————————————————————————————————————————— TyInt64
Γ ⊢ 'Int64' : ⋆
————————————————————————————————————————————— TyDecimal
Γ ⊢ 'Decimal' :
————————————————————————————————————————————— TyNumeric
Γ ⊢ 'Numeric' : 'nat' →
————————————————————————————————————————————— TyText
Γ ⊢ 'Text' : ⋆
@ -854,8 +869,9 @@ Then we define *well-formed expressions*. ::
——————————————————————————————————————————————————————————————— ExpLitInt64
Γ ⊢ LitInt64 : 'Int64'
——————————————————————————————————————————————————————————————— ExpLitDecimal
Γ ⊢ LitDecimal : 'Decimal'
n = scale(LitNumeric)
——————————————————————————————————————————————————————————————— ExpLitNumeric
Γ ⊢ LitNumeric : 'Numeric' n
——————————————————————————————————————————————————————————————— ExpLitText
Γ ⊢ LitText : 'Text'
@ -1063,8 +1079,8 @@ types are the types whose values can be persisted on the ledger. ::
———————————————————————————————————————————————————————————————— STyInt64
⊢ₛ 'Int64'
———————————————————————————————————————————————————————————————— STyDecimal
⊢ₛ 'Decimal'
———————————————————————————————————————————————————————————————— STyNumeric
⊢ₛ 'Numeric' n
———————————————————————————————————————————————————————————————— STyText
⊢ₛ 'Text'
@ -1386,8 +1402,8 @@ need to be evaluated further. ::
——————————————————————————————————————————————————— ValExpLitInt64
⊢ᵥ LitInt64
——————————————————————————————————————————————————— ValExpLitDecimal
⊢ᵥ LitDecimal
——————————————————————————————————————————————————— ValExpLitNumeric
⊢ᵥ LitNumeric
——————————————————————————————————————————————————— ValExpLitText
⊢ᵥ LitText
@ -2087,84 +2103,98 @@ Int64 functions
* ``FROM_TEXT_INT64 : 'Text' → 'Optional' 'Int64'``
Given a string representation of an integer returns the integer wrapped
in ``Some``. If the input does not match the regexp ``[+-]?[0-9]+`` or
in ``Some``. If the input does not match the regexp ``[+-]?\d+`` or
if the result of the conversion overflows, returns ``None``.
[*Available since version 1.5*]
Decimal functions
Numeric functions
~~~~~~~~~~~~~~~~~
* ``ADD_DECIMAL : 'Decimal' → 'Decimal' → 'Decimal'``
* ``ADD_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Numeric' α``
Adds the two decimals. Throws an error in case of overflow.
Adds the two decimals. The scale of the inputs and the ouput is
given by the type parameter `α`. Throws an error in case of
overflow.
* ``SUB_DECIMAL : 'Decimal' → 'Decimal' → 'Decimal'``
* ``SUB_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Numeric' α``
Subtracts the second decimal from the first one. Throws an error
if overflow.
Subtracts the second decimal from the first one. The
scale of the inputs and the ouput is given by the type parameter
`α`. Throws an error if overflow.
* ``MUL_DECIMAL : 'Decimal' → 'Decimal' → 'Decimal'``
* ``MUL_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Numeric' α``
Multiplies the two decimals and rounds the result to the closest
multiple of ``10⁻¹⁰`` using `banker's rounding convention
<https://en.wikipedia.org/wiki/Rounding#Round_half_to_even>`_.
Throws an error in case of overflow.
multiple of ``10⁻ᵅ`` using `banker's rounding convention
<https://en.wikipedia.org/wiki/Rounding#Round_half_to_even>`_. The
scale of the inputs and the ouput is given by the type parameter
`α`. Throws an error in case of overflow.
* ``DIV_DECIMAL : 'Decimal' → 'Decimal' → 'Decimal'``
* ``DIV_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Numeric' α``
Divides the first decimal by the second one and rounds the result to
the closest multiple of ``10⁻¹⁰`` using `banker's rounding
convention
<https://en.wikipedia.org/wiki/Rounding#Round_half_to_even>`_. Throws
an error in case of overflow.
the closest multiple of ``10⁻ᵅ`` using `banker's rounding convention
<https://en.wikipedia.org/wiki/Rounding#Round_half_to_even>`_ (where
`n` is given as the type parameter). The scale of the inputs and
the ouput is given by the type parameter `α`. Throws an error in
case of overflow.
* ``ROUND_DECIMAL : 'Int64' → 'Decimal' → 'Decimal'``
* ``ROUND_NUMERIC : ∀ (α : nat) . 'Int64' → 'Numeric' α → 'Numeric' α``
Round the decimal to the closest multiple of ``10ⁱ`` where ``i`` is
integer argument. Rounds the decimal argument to the closest
multiple of ``10ⁱ`` where ``i`` is integer argument. In case the
value to be rounded is exactly half-way between two multiples,
rounds toward the even one, following the `banker's rounding
convention
<https://en.wikipedia.org/wiki/Rounding#Round_half_to_even>`_. Throws
an exception if the integer is not between -27 and 10 inclusive.
Rounds the decimal to the closest multiple of ``10ⁱ`` where ``i`` is
integer argument. In case the value to be rounded is exactly
half-way between two multiples, rounds toward the even one,
following the `banker's rounding convention
<https://en.wikipedia.org/wiki/Rounding#Round_half_to_even>`_. The
scale of the inputs and the ouput is given by the type parameter
`α`. Throws an exception if the integer is not between `α-37` and
`α` inclusive.
* ``LESS_EQ_DECIMAL : 'Decimal' → 'Decimal' → 'Bool'``
* ``LESS_EQ_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Bool'``
Returns ``'True'`` if the first decimal is less or equal than the
second, ``'False'`` otherwise.
second, ``'False'`` otherwise. The scale of the inputs is given by
the type parameter `α`.
* ``GREATER_EQ_DECIMAL : 'Decimal' → 'Decimal' → 'Bool'``
* ``GREATER_EQ_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Bool'``
Returns ``'True'`` if the first decimal is greater or equal than
the second, ``'False'`` otherwise.
Returns ``'True'`` if the first decimal is greater or equal than the
second, ``'False'`` otherwise. The scale of the inputs is given by
the type parameter `α`.
* ``LESS_DECIMAL : 'Decimal' → 'Decimal' → 'Bool'``
* ``LESS_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Bool'``
Returns ``'True'`` if the first decimal is strictly less than the
second, ``'False'`` otherwise.
second, ``'False'`` otherwise. The scale of the inputs is given by
the type parameter `α`.
* ``GREATER_DECIMAL : 'Decimal' → 'Decimal' → 'Bool'``
Returns ``'True'`` if the first decimal is strictly greater than
the second, ``'False'`` otherwise.
* ``GREATER_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Bool'``
* ``EQUAL_DECIMAL : 'Decimal' → 'Decimal' → 'Bool'``
Returns ``'True'`` if the first decimal is strictly greater than the
second, ``'False'`` otherwise. The scale of the inputs is given by
the type parameter `α`.
* ``EQUAL_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Numeric' α → 'Bool'``
Returns ``'True'`` if the first decimal is equal to the second,
``'False'`` otherwise.
``'False'`` otherwise. The scale of the inputs is given by the type
parameter `α`.
* ``TO_TEXT_DECIMAL : 'Decimal' → 'Text'``
* ``TO_TEXT_NUMERIC : ∀ (α : nat) . 'Numeric' α → 'Text'``
Returns the decimal string representation of the decimal.
Returns the decimal string representation of the decimal. The scale
of the input is given by the type parameter `α`.
* ``FROM_TEXT_DECIMAL : 'Text' → 'Optional' 'DECIMAL'``
* ``FROM_TEXT_NUMERIC : ∀ (α : nat) .'Text' → 'Optional' 'Numeric' α``
Given a string representation of a decimal returns the decimal
wrapped in ``Some``. If the input does not match the regexp
``[+-]?[0-9]+(\.[0-9]+)?`` or if the result of the conversion
cannot be mapped into a decimal without loss of precision, returns ``None``.
``[+-]?\d+(\.d+)?`` or if the result of the conversion cannot
be mapped into a decimal without loss of precision, returns
``None``. The scale of the output is given by the type parameter
`α`.
[*Available since version 1.5*]
@ -2445,7 +2475,7 @@ Map functions
[*Available since version 1.3*]
* ``MAP_INSERT : ∀ α. 'Text' → α → 'Map' α → 'Map' α
* ``MAP_INSERT : ∀ α. 'Text' → α → 'Map' α → 'Map' α``
Inserts a new key and value in the map. If the key is already
present in the map, the associated value is replaced with the
@ -2453,27 +2483,27 @@ Map functions
[*Available since version 1.3*]
* ``MAP_LOOKUP : ∀ α. 'Text' → 'Map' α → 'Optional' α
* ``MAP_LOOKUP : ∀ α. 'Text' → 'Map' α → 'Optional' α``
Lookups the value at a key in the map.
[*Available since version 1.3*]
* ``MAP_DELETE : ∀ α. 'Text' → 'Map' α → 'Map' α
* ``MAP_DELETE : ∀ α. 'Text' → 'Map' α → 'Map' α``
Deletes a key and its value from the map. When the key is not a
member of the map, the original map is returned.
[*Available since version 1.3*]
* ``MAP_LIST : ∀ α. 'Map' α → 'List' ⟨ key: 'Text', value: α
* ``MAP_LIST : ∀ α. 'Map' α → 'List' ⟨ key: 'Text', value: α``
Converts to a list of key/value pairs. The output list is guaranteed to be
sorted according to the ordering of its keys.
[*Available since version 1.3*]
* ``MAP_SIZE : ∀ α. 'Map' α → 'Int64'
* ``MAP_SIZE : ∀ α. 'Map' α → 'Int64'``
Return the number of elements in the map.
@ -2482,14 +2512,17 @@ Map functions
Conversions functions
~~~~~~~~~~~~~~~~~~~~~
* ``INT64_TO_DECIMAL : 'Int64' → 'Decimal'``
* ``INT64_TO_NUMERIC : ∀ (α : nat) . 'Int64' → 'Numeric' α``
Returns a decimal representation of the integer.
Returns a decimal representation of the integer. The scale of the
output and the ouput is given by the type parameter `α`. Throws an
error in case of overflow.
* ``DECIMAL_TO_INT64 : 'Decimal' → 'Int64'``
* ``NUMERIC_TO_INT64 : ∀ (α : nat) . 'Numeric' α → 'Int64'``
Returns the integral part of the given decimal -- in other words,
rounds towards 0. Throws an error in case of overflow.
rounds towards 0. The scale of the input and the ouput is given by
the type parameter `α`. Throws an error in case of overflow.
* ``TIMESTAMP_TO_UNIX_MICROSECONDS : 'Timestamp' → 'Int64'``
@ -2823,6 +2856,84 @@ of ``package_id``, in which case the package ID will be that at the
given index into ``Package.interned_package_ids``.
See `Package reference`_.
Nat kind and Nat types
......................
[*Available since version 1.dev*]
The deserialization process will reject any DAML-LF 1.6 (or earlier)
that uses ``nat`` field in ``Kind`` or ``Type`` messages.
Starting from DAML-LF 1.dev those messages are deserialized to ``nat``
kind and ``nat`` type respectively. The field ``nat`` of ``Type``
message must be a positive integer.
Note that despite their is no concrete way to build Nat types in a
DAML-LF 1.6 (or earlier) program, those are implicitly generated when
reading as Numeric type and Numeric builtin as described in the next
section.
Parametric scaled Decimals
..........................
[*Available since version 1.dev*]
DAML-LF 1.dev is the first version that supports parametric scaled
decimals. Prior versions have decimal number with a fix scale of 10
called Decimal. Backward compatibility with the current specification
is achieved by
1. Renaming the fields and the emum values containing "``decimal``" in
the Protocol buffer definition with "``numeric``" instead,
2. Unconditionally fixing the scale of Numeric literals to ``10`` when
reading DAML-LF 1.6 (or earlier),
3. Automatically applying the Numeric types and the numeric
builtin functions to the Nat type ``10`` when reading DAML-LF
1.6 (or earlier).
On the one hand, in case of DAML-LF 1.6 (or earlier) archive:
- The ``numeric`` fields of the ``PrimLit`` message must match the
regexp::
``[+-]?\d{1,28}(.[0-9]\d{1-10})?``
The deserialization process will silently convert any message that
contains such field to a numeric literal of scale 10. The
deserialization process will reject any non-compliant program.
- ``PrimType`` message with a field ``numeric`` set are translated to
``(Numeric 10)`` type when deserialized.
- Any ``BuiltinFunction`` message that corresponds to a numeric
builtin (all those builtins that contains ``NUMERIC`` within their
name) are silently applied to the ``nat`` type ``10`` when
deserialized to expression.
On the other hand, starting from DAML-LF 1.dev:
- The ``numeric`` field of the ``PrimLit`` message must match the
regexp:
``[-]?([1-9]\d*|0).\d*``
with the addition constrains that it contains at most 38 digits
(ignoring possibly leading ``0``). The deserialization process will
use the number of digits on the right of the dot as scale when
converting the message to numeric literals. The deserialization
process will reject any non-compliant program.
- ``PrimType`` messages with a field ``numeric`` set and
``BuiltinFunction`` messages that corresponds to a numeric builtin
are straightforwardly translated to the corresponding types or
expressions without implicit application.
.. Local Variables:
.. eval: (flyspell-mode 1)
.. eval: (set-input-method "TeX")