@@ -8,9 +8,53 @@ Begin["`Private`"]
88Needs ["CodeInspector`" ]
99Needs ["CodeInspector`Utils`" ]
1010Needs ["CodeParser`" ]
11+ Needs ["CodeParser`Concretify`" ]
1112Needs ["CodeParser`Utils`" ]
1213
1314
15+ codeWithMessageStackInspectAST [ast_ , {HoldForm [Message [MessageName [Part , "partw" ], arg1_ , arg2_ ]], rest___ }] :=
16+ Catch [
17+ Module [{partCase , children , issues , replacementNode , f , r },
18+
19+ partCase = FirstCase [ast , CallNode [LeafNode [Symbol , "Part" , _ ], _ , _ ], $Failed , Infinity ];
20+ If [FailureQ [partCase ],
21+ Throw [{}]
22+ ];
23+
24+ children = partCase /. CallNode [LeafNode [Symbol , "Part" , _ ], children_ , _ ] :> children ;
25+ Which [
26+ Length [children ] < 2 ,
27+ Throw [{}]
28+ ,
29+ Length [children ] > 2 ,
30+
31+ f = children [[1 ]];
32+ r = children [[2 ;; ]];
33+
34+ replacementNode = Concretify [ContainerNode [Null , {CallNode [LeafNode [Symbol , "Indexed" , < ||> ], {f , CallNode [LeafNode [Symbol , "List" , < ||> ], r , < ||> ]}, < ||> ]}, < ||> ]][[2 , 1 ]];
35+ ,
36+ True ,
37+ replacementNode = Concretify [ContainerNode [Null , {CallNode [LeafNode [Symbol , "Indexed" , < ||> ], children , < ||> ]}, < ||> ]][[2 , 1 ]];
38+ ];
39+
40+ issues = {};
41+
42+ AppendTo [issues ,
43+ InspectionObject ["Part" , ToString [StringForm [MessageName [General , "partw" ], arg1 , arg2 ]], "Error" , < |
44+ Source -> children [[2 , 3 , Key [Source ]]],
45+ ConfidenceLevel -> 0.95 ,
46+ CodeActions -> {
47+ CodeAction ["Replace with ``Indexed``" , ReplaceNode , < |
48+ "ReplacementNode" -> replacementNode , Source -> partCase [[3 , Key [Source ]]]
49+ |> ]
50+ }
51+ |> ]
52+ ];
53+
54+ issues
55+ ]]
56+
57+
1458codeWithMessageStackInspectAST [ast_ , {HoldForm [Message [MessageName [sym_ , tag_ ], args___ ]], rest___ }] :=
1559Catch [
1660Module [{case , name , tryGeneral , namePat , poss , issues },
@@ -44,37 +88,45 @@ Module[{case, name, tryGeneral, namePat, poss, issues},
4488
4589 Function [{pos },
4690
47- Switch [pos ,
48- _ Integer ,
49- case = FirstCase [ast , CallNode [LeafNode [Symbol , namePat , _ ], children_ , _ ] :> children , $Failed , Infinity ];
50- If [FailureQ [case ],
51- Throw [{}]
52- ];
53- If [Length [case ] < pos ,
54- Throw [{}]
55- ];
56- case = case [[pos ]];
57- AppendTo [issues , InspectionObject [name , ToString [StringForm [If [tryGeneral , MessageName [General , tag ], MessageName [sym , tag ]], args ]], "Error" , < |Source -> case [[3 , Key [Source ]]], ConfidenceLevel -> 0.95 |> ]]
58- ,
59- _ Symbol ,
60- case = FirstCase [ast , CallNode [LeafNode [Symbol , namePat , _ ], children_ , _ ] :> children , $Failed , Infinity ];
61- If [FailureQ [case ],
62- Throw [{}]
63- ];
64- case = FirstCase [case , CallNode [LeafNode [Symbol , "Rule" , _ ], {LeafNode [Symbol , ToString [pos ], _ ], value_ }, _ ] :> value , $Failed , Infinity ];
65- If [FailureQ [case ],
66- Throw [{}]
67- ];
68- AppendTo [issues , InspectionObject [name , ToString [StringForm [If [tryGeneral , MessageName [General , tag ], MessageName [sym , tag ]], args ]], "Error" , < |Source -> case [[3 , Key [Source ]]], ConfidenceLevel -> 0.95 |> ]]
69- ];
91+ Module [{posReplaced },
92+
93+ posReplaced = pos /. s_ String /; StringMatchQ [s , RegularExpression ["`\\ d+`" ]] :> ReleaseHold [{args }[[ToExpression [StringTake [s , {2 , - 2 }]]]]];
94+
95+ Switch [posReplaced ,
96+ _ Integer ,
97+ case = FirstCase [ast , CallNode [LeafNode [Symbol , namePat , _ ], children_ , _ ] :> children , $Failed , Infinity ];
98+ If [FailureQ [case ],
99+ Throw [{}]
100+ ];
101+ If [Length [case ] < posReplaced ,
102+ Throw [{}]
103+ ];
104+ case = case [[posReplaced ]];
105+ AppendTo [issues , InspectionObject [name , ToString [StringForm [If [tryGeneral , MessageName [General , tag ], MessageName [sym , tag ]], args ]], "Error" , < |Source -> case [[3 , Key [Source ]]], ConfidenceLevel -> 0.95 |> ]]
106+ ,
107+ _ Symbol ,
108+ case = FirstCase [ast , CallNode [LeafNode [Symbol , namePat , _ ], children_ , _ ] :> children , $Failed , Infinity ];
109+ If [FailureQ [case ],
110+ Throw [{}]
111+ ];
112+ case = FirstCase [case , CallNode [LeafNode [Symbol , "Rule" , _ ], {LeafNode [Symbol , ToString [posReplaced ], _ ], value_ }, _ ] :> value , $Failed , Infinity ];
113+ If [FailureQ [case ],
114+ Throw [{}]
115+ ];
116+ AppendTo [issues , InspectionObject [name , ToString [StringForm [If [tryGeneral , MessageName [General , tag ], MessageName [sym , tag ]], args ]], "Error" , < |Source -> case [[3 , Key [Source ]]], ConfidenceLevel -> 0.95 |> ]]
117+ ,
118+ _ ,
119+ Message [codeWithMessageStackInspectAST ::unhandled , posReplaced // InputForm ];
120+ Null
121+ ];
122+ ]
70123
71124 ] /@ poss ;
72125
73126 issues
74127]]
75128
76129
77-
78130End []
79131
80132EndPackage []
0 commit comments