@@ -332,6 +332,44 @@ isErasedProp prop =
332
332
C. TCon (C. PC C. PLiteralLessThan ) _ -> False
333
333
_ -> True
334
334
335
+ -- | Translate a 'Prop' containing a numeric constraint to a 'Term' that tests
336
+ -- if the 'Prop' holds. This function will 'panic' for 'Prop's that are not
337
+ -- numeric constraints, such as @Integral@. In other words, this function
338
+ -- supports the same set of 'Prop's that constraint guards do.
339
+ importNumericConstraintAsBool :: SharedContext -> Env -> C. Prop -> IO Term
340
+ importNumericConstraintAsBool sc env prop =
341
+ case prop of
342
+ C. TCon (C. PC C. PEqual ) [lhs, rhs] -> eqTerm lhs rhs
343
+ C. TCon (C. PC C. PNeq ) [lhs, rhs] -> eqTerm lhs rhs >>= scNot sc
344
+ C. TCon (C. PC C. PGeq ) [lhs, rhs] -> do
345
+ -- Convert 'lhs >= rhs' into '(rhs < lhs) \/ (rhs == lhs)'
346
+ lhs' <- importType sc env lhs
347
+ rhs' <- importType sc env rhs
348
+ lt <- scGlobalApply sc " Cryptol.tcLt" [rhs', lhs']
349
+ eq <- scGlobalApply sc " Cryptol.tcEqual" [rhs', lhs']
350
+ scOr sc lt eq
351
+ C. TCon (C. PC C. PFin ) [x] -> do
352
+ x' <- importType sc env x
353
+ scGlobalApply sc " Cryptol.tcFin" [x']
354
+ C. TCon (C. PC C. PAnd ) [lhs, rhs] -> do
355
+ lhs' <- importType sc env lhs
356
+ rhs' <- importType sc env rhs
357
+ scAnd sc lhs' rhs'
358
+ C. TCon (C. PC C. PTrue ) [] -> scBool sc True
359
+ C. TUser _ _ t -> importNumericConstraintAsBool sc env t
360
+ _ -> panic
361
+ " importNumericConstraintAsBool"
362
+ [ " importNumericConstraintAsBool called with non-numeric constraint:"
363
+ , pretty prop
364
+ ]
365
+ where
366
+ -- | Construct a term for equality of two types
367
+ eqTerm :: C. Type -> C. Type -> IO Term
368
+ eqTerm lhs rhs = do
369
+ lhs' <- importType sc env lhs
370
+ rhs' <- importType sc env rhs
371
+ scGlobalApply sc " Cryptol.tcEqual" [lhs', rhs']
372
+
335
373
importPropsType :: SharedContext -> Env -> [C. Prop ] -> C. Type -> IO Term
336
374
importPropsType sc env [] ty = importType sc env ty
337
375
importPropsType sc env (prop : props) ty
@@ -1076,25 +1114,56 @@ importExpr sc env expr =
1076
1114
C. ELocated _ e ->
1077
1115
importExpr sc env e
1078
1116
1079
- C. EPropGuards {} ->
1080
- error " Using contsraint guards is not yet supported by SAW."
1117
+ C. EPropGuards arms typ -> do
1118
+ -- Convert prop guards to nested if-then-elses
1119
+ typ' <- importType sc env typ
1120
+ errMsg <- scString sc " No constraints satisfied in constraint guard"
1121
+ err <- scGlobalApply sc " Prelude.error" [typ', errMsg]
1122
+ -- NOTE: Must use a right fold to maintain order of prop guards in
1123
+ -- generated if-then-else
1124
+ Fold. foldrM (propGuardToIte typ') err arms
1081
1125
1082
1126
where
1083
1127
the :: String -> Maybe a -> IO a
1084
1128
the what = maybe (panic " importExpr" [" internal type error" , what]) return
1085
1129
1130
+ -- | Translate an erased 'Prop' to a term and return the conjunction of the
1131
+ -- translated term and 'mt' if 'mt' is 'Just'. Otherwise, return the
1132
+ -- translated 'Prop'. This function is intended to be used in a fold,
1133
+ -- taking a 'Maybe' in the first argument to avoid creating an unnecessary
1134
+ -- conjunction over singleton lists.
1135
+ conjoinErasedProps :: Maybe Term -> C. Prop -> IO (Maybe Term )
1136
+ conjoinErasedProps mt p = do
1137
+ p' <- importNumericConstraintAsBool sc env p
1138
+ case mt of
1139
+ Just t -> Just <$> scAnd sc t p'
1140
+ Nothing -> pure $ Just p'
1141
+
1142
+ -- | A helper function to be used in a fold converting a prop guard to an
1143
+ -- if-then-else. In order, the arguments of the function are:
1144
+ -- 1. The type of the prop guard
1145
+ -- 2. An arm of the prop guard
1146
+ -- 3. A term representing the else branch of the if-then-else
1147
+ propGuardToIte :: Term -> ([C. Prop ], C. Expr ) -> Term -> IO Term
1148
+ propGuardToIte typ (props, body) falseBranch = do
1149
+ mCondition <- Fold. foldlM conjoinErasedProps Nothing props
1150
+ condition <- maybe (scBool sc True ) pure mCondition
1151
+ trueBranch <- importExpr sc env body
1152
+ scGlobalApply sc " Prelude.ite" [typ, condition, trueBranch, falseBranch]
1153
+
1086
1154
1087
1155
-- | Convert a Cryptol expression with the given type schema to a
1088
1156
-- SAW-Core term. Calling 'scTypeOf' on the result of @'importExpr''
1089
1157
-- sc env schema expr@ must yield a type that is equivalent (i.e.
1090
1158
-- convertible) with the one returned by @'importSchema' sc env
1091
1159
-- schema@.
1160
+ --
1161
+ -- Essentially, this function should be used when the expression's type is known
1162
+ -- (such as with a type annotation), and 'importExpr' should be used when the
1163
+ -- type must be inferred.
1092
1164
importExpr' :: SharedContext -> Env -> C. Schema -> C. Expr -> IO Term
1093
1165
importExpr' sc env schema expr =
1094
1166
case expr of
1095
- C. EPropGuards {} ->
1096
- error " Using contsraint guards is not yet supported by SAW."
1097
-
1098
1167
C. ETuple es ->
1099
1168
do ty <- the " Expected a mono type in ETuple" (C. isMono schema)
1100
1169
ts <- the " Expected a tuple type in ETuple" (C. tIsTuple ty)
@@ -1168,6 +1237,7 @@ importExpr' sc env schema expr =
1168
1237
C. EApp {} -> fallback
1169
1238
C. ETApp {} -> fallback
1170
1239
C. EProofApp {} -> fallback
1240
+ C. EPropGuards {} -> fallback
1171
1241
1172
1242
where
1173
1243
go :: C. Type -> C. Expr -> IO Term
0 commit comments