Skip to content

Commit cca5d53

Browse files
authored
Merge pull request #1934 from GaloisInc/T1859-mir_tuple_value
`mir_tuple_value`
2 parents 6a6a1f5 + 124709b commit cca5d53

31 files changed

+281
-14
lines changed

crucible-mir-comp/src/Mir/Compositional/Builder.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -636,6 +636,7 @@ substMethodSpec sc sm ms = do
636636
MS.SetupTerm tt -> MS.SetupTerm <$> goTypedTerm tt
637637
MS.SetupNull _ -> return sv
638638
MS.SetupStruct b svs -> MS.SetupStruct b <$> mapM goSetupValue svs
639+
MS.SetupTuple b svs -> MS.SetupTuple b <$> mapM goSetupValue svs
639640
MS.SetupArray b svs -> MS.SetupArray b <$> mapM goSetupValue svs
640641
MS.SetupElem b sv idx -> MS.SetupElem b <$> goSetupValue sv <*> pure idx
641642
MS.SetupField b sv name -> MS.SetupField b <$> goSetupValue sv <*> pure name
@@ -677,14 +678,14 @@ regToSetup bak p eval shp rv = go shp rv
677678

678679
go :: forall tp. TypeShape tp -> RegValue sym tp ->
679680
BuilderT sym t (OverrideSim p sym MIR rtp args ret) (MS.SetupValue MIR)
680-
go (UnitShape _) () = return $ MS.SetupStruct () []
681+
go (UnitShape _) () = return $ MS.SetupTuple () []
681682
go (PrimShape _ btpr) expr = do
682683
-- Record all vars used in `expr`
683684
cache <- use msbVisitCache
684685
visitExprVars cache expr $ \var -> do
685686
msbPrePost p . seVars %= Set.insert (Some var)
686687
liftIO $ MS.SetupTerm <$> eval btpr expr
687-
go (TupleShape _ _ flds) rvs = MS.SetupStruct () <$> goFields flds rvs
688+
go (TupleShape _ _ flds) rvs = MS.SetupTuple () <$> goFields flds rvs
688689
go (ArrayShape _ elemTy shp) vec = do
689690
svs <- case vec of
690691
MirVector_Vector v -> mapM (go shp) (toList v)

crucible-mir-comp/src/Mir/Compositional/Override.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -356,7 +356,7 @@ matchArg sym sc eval allocSpecs md shp rv sv = go shp rv sv
356356
where
357357
go :: forall tp. TypeShape tp -> RegValue sym tp -> MS.SetupValue MIR ->
358358
MirOverrideMatcher sym ()
359-
go (UnitShape _) () (MS.SetupStruct () []) = return ()
359+
go (UnitShape _) () (MS.SetupTuple () []) = return ()
360360
go (PrimShape _ _btpr) expr (MS.SetupTerm tt) = do
361361
loc <- use MS.osLocation
362362
exprTerm <- liftIO $ eval expr
@@ -390,7 +390,7 @@ matchArg sym sc eval allocSpecs md shp rv sv = go shp rv sv
390390
("mismatch on " ++ show (W4.exprType expr) ++ ": expected " ++
391391
show (W4.printSymExpr val))
392392
""
393-
go (TupleShape _ _ flds) rvs (MS.SetupStruct () svs) = goFields flds rvs svs
393+
go (TupleShape _ _ flds) rvs (MS.SetupTuple () svs) = goFields flds rvs svs
394394
go (ArrayShape _ _ shp) vec (MS.SetupArray _ svs) = case vec of
395395
MirVector_Vector v -> zipWithM_ (\x y -> go shp x y) (toList v) svs
396396
MirVector_PartialVector pv -> forM_ (zip (toList pv) svs) $ \(p, sv) -> do
@@ -510,7 +510,7 @@ setupToReg :: forall sym t st fs tp.
510510
setupToReg sym sc termSub regMap allocMap shp sv = go shp sv
511511
where
512512
go :: forall tp. TypeShape tp -> MS.SetupValue MIR -> IO (RegValue sym tp)
513-
go (UnitShape _) (MS.SetupStruct _ []) = return ()
513+
go (UnitShape _) (MS.SetupTuple _ []) = return ()
514514
go (PrimShape _ btpr) (MS.SetupTerm tt) = do
515515
term <- liftIO $ SAW.scInstantiateExt sc termSub $ SAW.ttTerm tt
516516
Some expr <- termToExpr sym sc regMap term
@@ -519,7 +519,7 @@ setupToReg sym sc termSub regMap allocMap shp sv = go shp sv
519519
Nothing -> error $ "setupToReg: expected " ++ show btpr ++ ", but got " ++
520520
show (W4.exprType expr)
521521
return expr
522-
go (TupleShape _ _ flds) (MS.SetupStruct _ svs) = goFields flds svs
522+
go (TupleShape _ _ flds) (MS.SetupTuple _ svs) = goFields flds svs
523523
go (ArrayShape _ _ shp) (MS.SetupArray _ svs) = do
524524
rvs <- mapM (go shp) svs
525525
return $ MirVector_Vector $ V.fromList rvs

doc/manual/manual.md

+6-4
Original file line numberDiff line numberDiff line change
@@ -2435,9 +2435,9 @@ The experimental MIR implementation also has a `mir_alloc` function, which
24352435
behaves similarly to `llvm_alloc`. `mir_alloc` creates an immutable reference,
24362436
but there is also a `mir_alloc_mut` function for creating a mutable reference:
24372437

2438-
* `mir_alloc : MIRType -> MIRSetup SetupValue`
2438+
* `mir_alloc : MIRType -> MIRSetup MIRValue`
24392439

2440-
* `mir_alloc_mut : MIRType -> MIRSetup SetupValue`
2440+
* `mir_alloc_mut : MIRType -> MIRSetup MIRValue`
24412441

24422442
MIR tracks whether references are mutable or immutable at the type level, so it
24432443
is important to use the right allocation command for a given reference type.
@@ -2538,7 +2538,7 @@ value.
25382538

25392539
MIR verification has a single `mir_points_to` command:
25402540

2541-
* `mir_points_to : SetupValue -> SetupValue -> MIRSetup ()`
2541+
* `mir_points_to : MIRValue -> MIRValue -> MIRSetup ()`
25422542
takes two `SetupValue` arguments, the first of which must be a reference,
25432543
and states that the memory specified by that reference should contain the
25442544
value given in the second argument (which may be any type of
@@ -2624,9 +2624,11 @@ specifies the name of an object field.
26242624
In the experimental MIR verification implementation, the following functions
26252625
construct compound values:
26262626

2627-
* `mir_array_value : MIRType -> [SetupValue] -> SetupValue` constructs an array
2627+
* `mir_array_value : MIRType -> [MIRValue] -> MIRValue` constructs an array
26282628
of the given type whose elements consist of the given values. Supplying the
26292629
element type is necessary to support length-0 arrays.
2630+
* `mir_tuple_value : [MIRValue] -> MIRValue` construct a tuple with the given
2631+
list of values as elements.
26302632

26312633
### Bitfields
26322634

+13
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
all: test.linked-mir.json
2+
3+
test.linked-mir.json: test.rs
4+
saw-rustc $<
5+
$(MAKE) remove-unused-build-artifacts
6+
7+
.PHONY: remove-unused-build-artifacts
8+
remove-unused-build-artifacts:
9+
rm -f test libtest.mir libtest.rlib
10+
11+
.PHONY: clean
12+
clean: remove-unused-build-artifacts
13+
rm -f test.linked-mir.json
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
{"fns":[{"abi":{"kind":"Rust"},"args":[{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::25602b11826e1882"}],"body":{"blocks":[{"block":{"data":[{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_2","ty":"ty::u32"}},"pos":"test.rs:10:13: 10:16","rhs":{"kind":"Use","usevar":{"data":{"data":[{"kind":"Deref"},{"field":0,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::25602b11826e1882"}},"kind":"Copy"}}},{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_3","ty":"ty::u32"}},"pos":"test.rs:11:13: 11:16","rhs":{"kind":"Use","usevar":{"data":{"data":[{"kind":"Deref"},{"field":1,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::25602b11826e1882"}},"kind":"Copy"}}},{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}},"pos":"test.rs:12:11: 12:12","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_3","ty":"ty::u32"}},"kind":"Copy"}}}],"terminator":{"args":[{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}},"kind":"Move"},{"data":{"rendered":{"kind":"uint","size":4,"val":"1"},"ty":"ty::u32"},"kind":"Constant"}],"cleanup":null,"destination":[{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"bb1"],"from_hir_call":true,"func":{"data":{"rendered":{"kind":"zst"},"ty":"ty::FnDef::f55acdef755f1aaa"},"kind":"Constant"},"kind":"Call","pos":"test.rs:12:11: 12:28"}},"blockid":"bb0"},{"block":{"data":[{"kind":"Assign","lhs":{"data":[{"kind":"Deref"},{"field":0,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::25602b11826e1882"}},"pos":"test.rs:12:5: 12:28","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"kind":"Move"}}},{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_7","ty":"ty::u32"}},"pos":"test.rs:13:11: 13:12","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_2","ty":"ty::u32"}},"kind":"Copy"}}}],"terminator":{"args":[{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_7","ty":"ty::u32"}},"kind":"Move"},{"data":{"rendered":{"kind":"uint","size":4,"val":"2"},"ty":"ty::u32"},"kind":"Constant"}],"cleanup":null,"destination":[{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_6","ty":"ty::u32"}},"bb2"],"from_hir_call":true,"func":{"data":{"rendered":{"kind":"zst"},"ty":"ty::FnDef::f55acdef755f1aaa"},"kind":"Constant"},"kind":"Call","pos":"test.rs:13:11: 13:28"}},"blockid":"bb1"},{"block":{"data":[{"kind":"Assign","lhs":{"data":[{"kind":"Deref"},{"field":1,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::25602b11826e1882"}},"pos":"test.rs:13:5: 13:28","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_6","ty":"ty::u32"}},"kind":"Move"}}}],"terminator":{"kind":"Return","pos":"test.rs:14:2: 14:2"}},"blockid":"bb2"}],"vars":[{"is_zst":true,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::Tuple::e93222e871854c41"},{"is_zst":false,"mut":{"kind":"Not"},"name":"_2","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Not"},"name":"_3","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_6","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_7","ty":"ty::u32"}]},"name":"test/34c2a073::h","return_ty":"ty::Tuple::e93222e871854c41","spread_arg":null},{"abi":{"kind":"Rust"},"args":[{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Tuple::f54c7b3282e27392"}],"body":{"blocks":[{"block":{"data":[{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}},"pos":"test.rs:2:6: 2:9","rhs":{"kind":"Use","usevar":{"data":{"data":[{"field":1,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Tuple::f54c7b3282e27392"}},"kind":"Copy"}}}],"terminator":{"args":[{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}},"kind":"Move"},{"data":{"rendered":{"kind":"uint","size":4,"val":"1"},"ty":"ty::u32"},"kind":"Constant"}],"cleanup":null,"destination":[{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_2","ty":"ty::u32"}},"bb1"],"from_hir_call":true,"func":{"data":{"rendered":{"kind":"zst"},"ty":"ty::FnDef::f55acdef755f1aaa"},"kind":"Constant"},"kind":"Call","pos":"test.rs:2:6: 2:25"}},"blockid":"bb0"},{"block":{"data":[{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}},"pos":"test.rs:2:27: 2:30","rhs":{"kind":"Use","usevar":{"data":{"data":[{"field":0,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Tuple::f54c7b3282e27392"}},"kind":"Copy"}}}],"terminator":{"args":[{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}},"kind":"Move"},{"data":{"rendered":{"kind":"uint","size":4,"val":"2"},"ty":"ty::u32"},"kind":"Constant"}],"cleanup":null,"destination":[{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"bb2"],"from_hir_call":true,"func":{"data":{"rendered":{"kind":"zst"},"ty":"ty::FnDef::f55acdef755f1aaa"},"kind":"Constant"},"kind":"Call","pos":"test.rs:2:27: 2:46"}},"blockid":"bb1"},{"block":{"data":[{"kind":"Deinit","pos":"test.rs:2:5: 2:47"},{"kind":"Assign","lhs":{"data":[{"field":0,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::Tuple::f54c7b3282e27392"}},"pos":"test.rs:2:5: 2:47","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_2","ty":"ty::u32"}},"kind":"Move"}}},{"kind":"Assign","lhs":{"data":[{"field":1,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::Tuple::f54c7b3282e27392"}},"pos":"test.rs:2:5: 2:47","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"kind":"Move"}}}],"terminator":{"kind":"Return","pos":"test.rs:3:2: 3:2"}},"blockid":"bb2"}],"vars":[{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::Tuple::f54c7b3282e27392"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_2","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}]},"name":"test/34c2a073::f","return_ty":"ty::Tuple::f54c7b3282e27392","spread_arg":null},{"abi":{"kind":"Rust"},"args":[{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::22d6f3c23aaa2830"}],"body":{"blocks":[{"block":{"data":[{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}},"pos":"test.rs:6:6: 6:9","rhs":{"kind":"Use","usevar":{"data":{"data":[{"kind":"Deref"},{"field":1,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::22d6f3c23aaa2830"}},"kind":"Copy"}}}],"terminator":{"args":[{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}},"kind":"Move"},{"data":{"rendered":{"kind":"uint","size":4,"val":"1"},"ty":"ty::u32"},"kind":"Constant"}],"cleanup":null,"destination":[{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_2","ty":"ty::u32"}},"bb1"],"from_hir_call":true,"func":{"data":{"rendered":{"kind":"zst"},"ty":"ty::FnDef::f55acdef755f1aaa"},"kind":"Constant"},"kind":"Call","pos":"test.rs:6:6: 6:25"}},"blockid":"bb0"},{"block":{"data":[{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}},"pos":"test.rs:6:27: 6:30","rhs":{"kind":"Use","usevar":{"data":{"data":[{"kind":"Deref"},{"field":0,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::Ref::22d6f3c23aaa2830"}},"kind":"Copy"}}}],"terminator":{"args":[{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}},"kind":"Move"},{"data":{"rendered":{"kind":"uint","size":4,"val":"2"},"ty":"ty::u32"},"kind":"Constant"}],"cleanup":null,"destination":[{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"bb2"],"from_hir_call":true,"func":{"data":{"rendered":{"kind":"zst"},"ty":"ty::FnDef::f55acdef755f1aaa"},"kind":"Constant"},"kind":"Call","pos":"test.rs:6:27: 6:46"}},"blockid":"bb1"},{"block":{"data":[{"kind":"Deinit","pos":"test.rs:6:5: 6:47"},{"kind":"Assign","lhs":{"data":[{"field":0,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::Tuple::f54c7b3282e27392"}},"pos":"test.rs:6:5: 6:47","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_2","ty":"ty::u32"}},"kind":"Move"}}},{"kind":"Assign","lhs":{"data":[{"field":1,"kind":"Field","ty":"ty::u32"}],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::Tuple::f54c7b3282e27392"}},"pos":"test.rs:6:5: 6:47","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"kind":"Move"}}}],"terminator":{"kind":"Return","pos":"test.rs:7:2: 7:2"}},"blockid":"bb2"}],"vars":[{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::Tuple::f54c7b3282e27392"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_2","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_5","ty":"ty::u32"}]},"name":"test/34c2a073::g","return_ty":"ty::Tuple::f54c7b3282e27392","spread_arg":null},{"abi":{"kind":"Rust"},"args":[{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Not"},"name":"_2","ty":"ty::u32"}],"body":{"blocks":[{"block":{"data":[{"kind":"StorageLive","pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1162:38: 1162:42 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101","slvar":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}},{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}},"pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1162:38: 1162:42 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_1","ty":"ty::u32"}},"kind":"Copy"}}},{"kind":"StorageLive","pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1162:44: 1162:47 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101","slvar":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1162:44: 1162:47 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101","rhs":{"kind":"Use","usevar":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Not"},"name":"_2","ty":"ty::u32"}},"kind":"Copy"}}},{"kind":"Assign","lhs":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::u32"}},"pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1162:13: 1162:48 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101","rhs":{"L":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}},"kind":"Move"},"R":{"data":{"data":[],"var":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},"kind":"Move"},"kind":"BinaryOp","op":{"kind":"Add"}}},{"kind":"StorageDead","pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1162:47: 1162:48 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101","sdvar":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}},{"kind":"StorageDead","pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1162:47: 1162:48 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101","sdvar":{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"}}],"terminator":{"kind":"Return","pos":"/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/uint_macros.rs:1163:10: 1163:10 !/rustc/5e37043d63bfe2f3be8fa5a05b07d6c0dad5775d/library/core/src/num/mod.rs:921:5: 922:101"}},"blockid":"bb0"}],"vars":[{"is_zst":false,"mut":{"kind":"Mut"},"name":"_0","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_3","ty":"ty::u32"},{"is_zst":false,"mut":{"kind":"Mut"},"name":"_4","ty":"ty::u32"}]},"name":"core/73237d41::num::{impl#9}::wrapping_add","return_ty":"ty::u32","spread_arg":null}],"adts":[],"statics":[],"vtables":[],"traits":[],"intrinsics":[{"inst":{"def_id":"test/34c2a073::h","kind":"Item","substs":[]},"name":"test/34c2a073::h"},{"inst":{"def_id":"test/34c2a073::f","kind":"Item","substs":[]},"name":"test/34c2a073::f"},{"inst":{"def_id":"test/34c2a073::g","kind":"Item","substs":[]},"name":"test/34c2a073::g"},{"inst":{"def_id":"core/73237d41::num::{impl#9}::wrapping_add","kind":"Item","substs":[]},"name":"core/73237d41::num::{impl#9}::wrapping_add"}],"tys":[{"name":"ty::u32","ty":{"kind":"Uint","uintkind":{"kind":"U32"}}},{"name":"ty::Tuple::f54c7b3282e27392","ty":{"kind":"Tuple","tys":["ty::u32","ty::u32"]}},{"name":"ty::Ref::25602b11826e1882","ty":{"kind":"Ref","mutability":{"kind":"Mut"},"ty":"ty::Tuple::f54c7b3282e27392"}},{"name":"ty::Tuple::e93222e871854c41","ty":{"kind":"Tuple","tys":[]}},{"name":"ty::FnDef::f55acdef755f1aaa","ty":{"defid":"core/73237d41::num::{impl#9}::wrapping_add","kind":"FnDef"}},{"name":"ty::Ref::22d6f3c23aaa2830","ty":{"kind":"Ref","mutability":{"kind":"Not"},"ty":"ty::Tuple::f54c7b3282e27392"}}],"roots":["test/34c2a073::f","test/34c2a073::g","test/34c2a073::h"]}
+14
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
pub fn f(s: (u32, u32)) -> (u32, u32) {
2+
(s.1.wrapping_add(1), s.0.wrapping_add(2))
3+
}
4+
5+
pub fn g(s: &(u32, u32)) -> (u32, u32) {
6+
(s.1.wrapping_add(1), s.0.wrapping_add(2))
7+
}
8+
9+
pub fn h(s: &mut (u32, u32)) {
10+
let x = s.0;
11+
let y = s.1;
12+
s.0 = y.wrapping_add(1);
13+
s.1 = x.wrapping_add(2);
14+
}

0 commit comments

Comments
 (0)