Skip to content

Commit 9f14733

Browse files
authored
Remove some dead code (#17086)
* Remove some dead code * Fix * Remove unnecessary fn * oops
1 parent 8653ab3 commit 9f14733

17 files changed

+3
-281
lines changed

src/Compiler/Checking/CheckDeclarations.fs

Lines changed: 0 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -920,11 +920,6 @@ module MutRecBindingChecking =
920920
/// A 'member' definition in a class
921921
| Phase2AMember of PreCheckingRecursiveBinding
922922

923-
#if OPEN_IN_TYPE_DECLARATIONS
924-
/// A dummy declaration, should we ever support 'open' in type definitions
925-
| Phase2AOpen of SynOpenDeclTarget * range
926-
#endif
927-
928923
/// Indicates the super init has just been called, 'this' may now be published
929924
| Phase2AIncrClassCtorJustAfterSuperInit
930925

@@ -1142,13 +1137,6 @@ module MutRecBindingChecking =
11421137

11431138
let innerState = (incrCtorInfoOpt, envForTycon, tpenv, recBindIdx, List.rev binds @ uncheckedBindsRev)
11441139
cbinds, innerState
1145-
1146-
#if OPEN_IN_TYPE_DECLARATIONS
1147-
| Some (SynMemberDefn.Open (target, m)), _ ->
1148-
let innerState = (incrCtorInfoOpt, env, tpenv, recBindIdx, prelimRecValuesRev, uncheckedBindsRev)
1149-
[ Phase2AOpen (target, m) ], innerState
1150-
#endif
1151-
11521140
| definition ->
11531141
error(InternalError(sprintf "Unexpected definition %A" definition, m)))
11541142

@@ -1196,9 +1184,6 @@ module MutRecBindingChecking =
11961184
let rest =
11971185
let isAfter b =
11981186
match b with
1199-
#if OPEN_IN_TYPE_DECLARATIONS
1200-
| Phase2AOpen _
1201-
#endif
12021187
| Phase2AIncrClassCtor _ | Phase2AInherit _ | Phase2AIncrClassCtorJustAfterSuperInit -> false
12031188
| Phase2AIncrClassBindings (_, binds, _, _, _) -> binds |> List.exists (function SynBinding (kind=SynBindingKind.Do) -> true | _ -> false)
12041189
| Phase2AIncrClassCtorJustAfterLastLet
@@ -1417,16 +1402,6 @@ module MutRecBindingChecking =
14171402
| Phase2AIncrClassCtorJustAfterLastLet ->
14181403
let innerState = (tpenv, envInstance, envStatic, envNonRec, generalizedRecBinds, preGeneralizationRecBinds, uncheckedRecBindsTable)
14191404
Phase2BIncrClassCtorJustAfterLastLet, innerState
1420-
1421-
1422-
#if OPEN_IN_TYPE_DECLARATIONS
1423-
| Phase2AOpen(target, m) ->
1424-
let envInstance = TcOpenDecl cenv m scopem envInstance target
1425-
let envStatic = TcOpenDecl cenv m scopem envStatic target
1426-
let innerState = (tpenv, envInstance, envStatic, envNonRec, generalizedRecBinds, preGeneralizationRecBinds, uncheckedRecBindsTable)
1427-
Phase2BOpen, innerState
1428-
#endif
1429-
14301405

14311406
// Note: this path doesn't add anything the environment, because the member is already available off via its type
14321407

src/Compiler/Checking/CheckExpressions.fs

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -2614,13 +2614,8 @@ module EventDeclarationNormalization =
26142614
let FreshenObjectArgType (cenv: cenv) m rigid tcref isExtrinsic declaredTyconTypars =
26152615
let g = cenv.g
26162616

2617-
#if EXTENDED_EXTENSION_MEMBERS // indicates if extension members can add additional constraints to type parameters
2618-
let tcrefObjTy, enclosingDeclaredTypars, renaming, objTy =
2619-
FreshenTyconRef g m (if isExtrinsic then TyparRigidity.Flexible else rigid) tcref declaredTyconTypars
2620-
#else
26212617
let tcrefObjTy, enclosingDeclaredTypars, renaming, objTy =
26222618
FreshenTyconRef g m rigid tcref declaredTyconTypars
2623-
#endif
26242619

26252620
// Struct members have a byref 'this' type (unless they are extrinsic extension members)
26262621
let thisTy =
@@ -12386,11 +12381,7 @@ and FixupLetrecBind (cenv: cenv) denv generalizedTyparsForRecursiveBlock (bind:
1238612381

1238712382
// Check coherence of generalization of variables for memberInfo members in generic classes
1238812383
match vspec.MemberInfo with
12389-
#if EXTENDED_EXTENSION_MEMBERS // indicates if extension members can add additional constraints to type parameters
12390-
| Some _ when not vspec.IsExtensionMember ->
12391-
#else
1239212384
| Some _ ->
12393-
#endif
1239412385
match PartitionValTyparsForApparentEnclosingType g vspec with
1239512386
| Some(parentTypars, memberParentTypars, _, _, _) ->
1239612387
ignore(SignatureConformance.Checker(g, cenv.amap, denv, SignatureRepackageInfo.Empty, false).CheckTypars vspec.Range TypeEquivEnv.Empty memberParentTypars parentTypars)

src/Compiler/Checking/ConstraintSolver.fs

Lines changed: 1 addition & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -1058,10 +1058,6 @@ and SolveTypeEqualsType (csenv: ConstraintSolverEnv) ndeep m2 (trace: OptionalTr
10581058
let aenv = csenv.EquivEnv
10591059
let g = csenv.g
10601060

1061-
// Pre F# 6.0 we asssert the trait solution here
1062-
#if TRAIT_CONSTRAINT_CORRECTIONS
1063-
if not (csenv.g.langVersion.SupportsFeature LanguageFeature.TraitConstraintCorrections) then
1064-
#endif
10651061
match cxsln with
10661062
| Some (traitInfo, traitSln) when traitInfo.Solution.IsNone ->
10671063
// If this is an overload resolution at this point it's safe to assume the candidate member being evaluated solves this member constraint.
@@ -2895,22 +2891,11 @@ and ReportNoCandidatesErrorSynExpr csenv callerArgCounts methodName ad calledMet
28952891
///
28962892
/// In F# 5.0 and 6.0 we assert this late by passing the cxsln parameter around. However this
28972893
/// relies on not checking return types for SRTP constraints eagerly
2898-
///
2899-
/// Post F# 6.0 (TraitConstraintCorrections) we will assert this early and add a proper check that return types match for SRTP constraint solving
2900-
/// (see alwaysCheckReturn)
2901-
and AssumeMethodSolvesTrait (csenv: ConstraintSolverEnv) (cx: TraitConstraintInfo option) m trace (calledMeth: CalledMeth<_>) =
2894+
and AssumeMethodSolvesTrait (csenv: ConstraintSolverEnv) (cx: TraitConstraintInfo option) m _trace (calledMeth: CalledMeth<_>) =
29022895
match cx with
29032896
| Some traitInfo when traitInfo.Solution.IsNone ->
29042897
let staticTyOpt = if calledMeth.Method.IsInstance then None else calledMeth.OptionalStaticType
29052898
let traitSln = MemberConstraintSolutionOfMethInfo csenv.SolverState m calledMeth.Method calledMeth.CalledTyArgs staticTyOpt
2906-
#if TRAIT_CONSTRAINT_CORRECTIONS
2907-
if csenv.g.langVersion.SupportsFeature LanguageFeature.TraitConstraintCorrections then
2908-
TransactMemberConstraintSolution traitInfo trace traitSln
2909-
None
2910-
else
2911-
#else
2912-
ignore trace
2913-
#endif
29142899
Some (traitInfo, traitSln)
29152900
| _ ->
29162901
None
@@ -2971,13 +2956,9 @@ and ResolveOverloading
29712956
// Always take the return type into account for
29722957
// -- op_Explicit, op_Implicit
29732958
// -- candidate method sets that potentially use tupling of unfilled out args
2974-
/// -- if TraitConstraintCorrections is enabled, also check return types for SRTP constraints
29752959
let alwaysCheckReturn =
29762960
isOpConversion ||
29772961
candidates |> List.exists (fun cmeth -> cmeth.HasOutArgs)
2978-
#if TRAIT_CONSTRAINT_CORRECTIONS
2979-
|| (csenv.g.langVersion.SupportsFeature LanguageFeature.TraitConstraintCorrections && cx.IsSome)
2980-
#endif
29812962

29822963
// Exact match rule.
29832964
//

src/Compiler/Checking/MethodCalls.fs

Lines changed: 0 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -430,14 +430,7 @@ let AdjustCalledArgType (infoReader: InfoReader) ad isConstraint enforceNullable
430430

431431
// If the called method argument is an inref type, then the caller may provide a byref or value
432432
if isInByrefTy g calledArgTy then
433-
#if IMPLICIT_ADDRESS_OF
434-
if isByrefTy g callerArgTy then
435-
calledArgTy
436-
else
437-
destByrefTy g calledArgTy
438-
#else
439433
calledArgTy, TypeDirectedConversionUsed.No, None
440-
#endif
441434

442435
// If the called method argument is a (non inref) byref type, then the caller may provide a byref or ref.
443436
elif isByrefTy g calledArgTy then
@@ -1371,12 +1364,6 @@ let AdjustCallerArgExpr tcVal (g: TcGlobals) amap infoReader ad isOutArg calledA
13711364
if isByrefTy g calledArgTy && isRefCellTy g callerArgTy then
13721365
None, Expr.Op (TOp.RefAddrGet false, [destRefCellTy g callerArgTy], [callerArgExpr], m)
13731366

1374-
#if IMPLICIT_ADDRESS_OF
1375-
elif isInByrefTy g calledArgTy && not (isByrefTy g callerArgTy) then
1376-
let wrap, callerArgExprAddress, _readonly, _writeonly = mkExprAddrOfExpr g true false NeverMutates callerArgExpr None m
1377-
Some wrap, callerArgExprAddress
1378-
#endif
1379-
13801367
// auto conversions to quotations (to match auto conversions to LINQ expressions)
13811368
elif reflArgInfo.AutoQuote && isQuotedExprTy g calledArgTy && not (isQuotedExprTy g callerArgTy) then
13821369
match reflArgInfo with
@@ -1943,13 +1930,6 @@ module ProvidedMethodCalls =
19431930
let infoReader = InfoReader(g, amap)
19441931
let exprR = CoerceFromFSharpFuncToDelegate g amap infoReader AccessorDomain.AccessibleFromSomewhere lambdaExprTy m lambdaExpr delegateTyR
19451932
None, (exprR, tyOfExpr g exprR)
1946-
#if PROVIDED_ADDRESS_OF
1947-
| ProvidedAddressOfExpr e ->
1948-
let eR = exprToExpr (exprType.PApply((fun _ -> e), m))
1949-
let wrap,exprR, _readonly, _writeonly = mkExprAddrOfExpr g true false DefinitelyMutates eR None m
1950-
let exprR = wrap exprR
1951-
None, (exprR, tyOfExpr g exprR)
1952-
#endif
19531933
| ProvidedDefaultExpr pty ->
19541934
let ty = Import.ImportProvidedType amap m (exprType.PApply((fun _ -> pty), m))
19551935
let exprR = mkDefault (m, ty)

src/Compiler/Checking/PatternMatchCompilation.fs

Lines changed: 0 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -735,26 +735,6 @@ let ChooseInvestigationPointLeftToRight frontiers =
735735
| [] -> failwith "ChooseInvestigationPointLeftToRight: no frontiers!"
736736

737737

738-
739-
#if OPTIMIZE_LIST_MATCHING
740-
// This is an initial attempt to remove extra typetests/castclass for simple list pattern matching "match x with h :: t -> ... | [] -> ..."
741-
// The problem with this technique is that it creates extra locals which inhibit the process of converting pattern matches into linear let bindings.
742-
743-
[<return: Struct>]
744-
let (|ListConsDiscrim|_|) g = function
745-
| (DecisionTreeTest.UnionCase (ucref, tinst))
746-
(* check we can use a simple 'isinst' instruction *)
747-
when tyconRefEq g ucref.TyconRef g.list_tcr_canon & ucref.CaseName = "op_ColonColon" -> ValueSome tinst
748-
| _ -> ValueNone
749-
750-
[<return: Struct>]
751-
let (|ListEmptyDiscrim|_|) g = function
752-
| (DecisionTreeTest.UnionCase (ucref, tinst))
753-
(* check we can use a simple 'isinst' instruction *)
754-
when tyconRefEq g ucref.TyconRef g.list_tcr_canon & ucref.CaseName = "op_Nil" -> ValueSome tinst
755-
| _ -> ValueNone
756-
#endif
757-
758738
[<return: Struct>]
759739
let (|ConstNeedsDefaultCase|_|) c =
760740
match c with
@@ -806,17 +786,6 @@ let rec BuildSwitch inpExprOpt g expr edges dflt m =
806786
| TCase((DecisionTreeTest.IsNull | DecisionTreeTest.IsInst _), _) as edge :: edges, dflt ->
807787
TDSwitch(expr, [edge], Some (BuildSwitch None g expr edges dflt m), m)
808788

809-
#if OPTIMIZE_LIST_MATCHING
810-
// 'cons/nil' tests where we have stored the result of the cons test in an 'isinst' in a variable
811-
// In this case the 'expr' already holds the result of the 'isinst' test.
812-
| [TCase(ListConsDiscrim g tinst, consCase)], Some emptyCase
813-
| [TCase(ListEmptyDiscrim g tinst, emptyCase)], Some consCase
814-
| [TCase(ListEmptyDiscrim g _, emptyCase); TCase(ListConsDiscrim g tinst, consCase)], None
815-
| [TCase(ListConsDiscrim g tinst, consCase); TCase(ListEmptyDiscrim g _, emptyCase)], None
816-
when Option.isSome inpExprOpt ->
817-
TDSwitch(expr, [TCase(DecisionTreeTest.IsNull, emptyCase)], Some consCase, m)
818-
#endif
819-
820789
// All these should also always have default cases
821790
| TCase(DecisionTreeTest.Const ConstNeedsDefaultCase, _) :: _, None ->
822791
error(InternalError("inexhaustive match - need a default case!", m))
@@ -1272,25 +1241,6 @@ let CompilePatternBasic
12721241
AdjustValToHaveValReprInfo v origInputVal.TryDeclaringEntity ValReprInfo.emptyValData
12731242
Some addrExp, Some (mkInvisibleBind v e)
12741243

1275-
1276-
1277-
#if OPTIMIZE_LIST_MATCHING
1278-
| [EdgeDiscrim(_, ListConsDiscrim g tinst, m); EdgeDiscrim(_, ListEmptyDiscrim g _, _)]
1279-
| [EdgeDiscrim(_, ListEmptyDiscrim g _, _); EdgeDiscrim(_, ListConsDiscrim g tinst, m)]
1280-
| [EdgeDiscrim(_, ListConsDiscrim g tinst, m)]
1281-
| [EdgeDiscrim(_, ListEmptyDiscrim g tinst, m)]
1282-
(* check we can use a simple 'isinst' instruction *)
1283-
when isNil origInputValTypars ->
1284-
1285-
let ucaseTy = (mkProvenUnionCaseTy g.cons_ucref tinst)
1286-
let v, vExpr = mkCompGenLocal m "unionTestResult" ucaseTy
1287-
if origInputVal.IsMemberOrModuleBinding then
1288-
AdjustValToHaveValReprInfo v origInputVal.DeclaringEntity ValReprInfo.emptyValData
1289-
let argExpr = GetSubExprOfInput subexpr
1290-
let appExpr = mkIsInst ucaseTy argExpr mMatch
1291-
Some vExpr, Some (mkInvisibleBind v appExpr)
1292-
#endif
1293-
12941244
// Active pattern matches: create a variable to hold the results of executing the active pattern.
12951245
// If a struct return we continue with an expression for taking the address of that location.
12961246
| EdgeDiscrim(_, DecisionTreeTest.ActivePatternCase(activePatExpr, resTys, retKind, _apatVrefOpt, _, apinfo), m) :: _ ->
@@ -1343,9 +1293,6 @@ let CompilePatternBasic
13431293
let resPostBindOpt, ucaseBindOpt =
13441294
match discrim with
13451295
| DecisionTreeTest.UnionCase (ucref, tinst) when
1346-
#if OPTIMIZE_LIST_MATCHING
1347-
isNone inpExprOpt &&
1348-
#endif
13491296
(isNil origInputValTypars &&
13501297
not origInputVal.IsMemberOrModuleBinding &&
13511298
not ucref.Tycon.IsStructRecordOrUnionTycon &&

src/Compiler/Checking/PostInferenceChecks.fs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2144,10 +2144,6 @@ let CheckModuleBinding cenv env (TBind(v, e, _) as bind) =
21442144

21452145
error(Duplicate(kind, v.DisplayName, v.Range))
21462146

2147-
#if CASES_IN_NESTED_CLASS
2148-
if tcref.IsUnionTycon && nm = "Cases" then
2149-
errorR(NameClash(nm, kind, v.DisplayName, v.Range, "generated type", "Cases", tcref.Range))
2150-
#endif
21512147
if tcref.IsUnionTycon then
21522148
match nm with
21532149
| "Tag" -> errorR(NameClash(nm, kind, v.DisplayName, v.Range, FSComp.SR.typeInfoGeneratedProperty(), "Tag", tcref.Range))

src/Compiler/Driver/CompilerImports.fs

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2336,12 +2336,6 @@ and [<Sealed>] TcImports
23362336
match resolutions.TryFindByOriginalReference assemblyReference with
23372337
| Some assemblyResolution -> ResultD [ assemblyResolution ]
23382338
| None ->
2339-
#if NO_MSBUILD_REFERENCE_RESOLUTION
2340-
try
2341-
ResultD [ tcConfig.ResolveLibWithDirectories assemblyReference ]
2342-
with e ->
2343-
ErrorD e
2344-
#else
23452339
// Next try to lookup up by the exact full resolved path.
23462340
match resolutions.TryFindByResolvedPath assemblyReference.Text with
23472341
| Some assemblyResolution -> ResultD [ assemblyResolution ]
@@ -2374,7 +2368,6 @@ and [<Sealed>] TcImports
23742368
// Note, if mode=ResolveAssemblyReferenceMode.Speculative and the resolution failed then TryResolveLibsUsingMSBuildRules returns
23752369
// the empty list and we convert the failure into an AssemblyNotResolved here.
23762370
ErrorD(AssemblyNotResolved(assemblyReference.Text, assemblyReference.Range))
2377-
#endif
23782371
)
23792372

23802373
member tcImports.ResolveAssemblyReference(ctok, assemblyReference, mode) : AssemblyResolution list =

src/Compiler/Facilities/BuildGraph.fs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -229,11 +229,7 @@ module GraphNode =
229229
match preferredUiLang with
230230
| Some s ->
231231
culture <- CultureInfo s
232-
#if FX_RESHAPED_GLOBALIZATION
233-
CultureInfo.CurrentUICulture <- culture
234-
#else
235232
Thread.CurrentThread.CurrentUICulture <- culture
236-
#endif
237233
| None -> ()
238234

239235
[<Sealed>]

src/Compiler/Optimize/Optimizer.fs

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2521,13 +2521,6 @@ and MakeOptimizedSystemStringConcatCall cenv env m args =
25212521
when IsILMethodRefSystemStringConcat ilMethRef ->
25222522
optimizeArgs args accArgs
25232523

2524-
// String constant folding requires a bit more work as we cannot quadratically concat strings at compile time.
2525-
#if STRING_CONSTANT_FOLDING
2526-
// Optimize string constants, e.g. "1" + "2" will turn into "12"
2527-
| Expr.Const (Const.String str1, _, _), Expr.Const (Const.String str2, _, _) :: accArgs ->
2528-
mkString g m (str1 + str2) :: accArgs
2529-
#endif
2530-
25312524
| arg, _ -> arg :: accArgs
25322525

25332526
and optimizeArgs args accArgs =

src/Compiler/SyntaxTree/XmlDoc.fs

Lines changed: 0 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -118,46 +118,6 @@ type XmlDoc(unprocessedLines: string[], range: range) =
118118
with e ->
119119
warning (Error(FSComp.SR.xmlDocBadlyFormed (e.Message), doc.Range))
120120

121-
#if CREF_ELABORATION
122-
member doc.Elaborate(crefResolver) =
123-
for see in
124-
seq {
125-
yield! xml.Descendants(XName.op_Implicit "see")
126-
yield! xml.Descendants(XName.op_Implicit "seealso")
127-
yield! xml.Descendants(XName.op_Implicit "exception")
128-
} do
129-
match see.Attribute(XName.op_Implicit "cref") with
130-
| null -> warning (Error(FSComp.SR.xmlDocMissingCrossReference (), doc.Range))
131-
| attr ->
132-
let cref = attr.Value
133-
134-
if
135-
cref.StartsWith("T:")
136-
|| cref.StartsWith("P:")
137-
|| cref.StartsWith("M:")
138-
|| cref.StartsWith("E:")
139-
|| cref.StartsWith("F:")
140-
then
141-
()
142-
else
143-
match crefResolver cref with
144-
| None -> warning (Error(FSComp.SR.xmlDocUnresolvedCrossReference (nm), doc.Range))
145-
| Some text ->
146-
attr.Value <- text
147-
modified <- true
148-
149-
if modified then
150-
let m = doc.Range
151-
152-
let newLines =
153-
[|
154-
for e in xml.Elements() do
155-
yield! e.ToString().Split([| '\r'; '\n' |], StringSplitOptions.RemoveEmptyEntries)
156-
|]
157-
158-
lines <- newLines
159-
#endif
160-
161121
// Discriminated unions can't contain statics, so we use a separate type
162122
and XmlDocStatics() =
163123

src/Compiler/TypedTree/TypeProviders.fs

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -854,9 +854,6 @@ type ProvidedConstructorInfo (x: ConstructorInfo, ctxt) =
854854

855855
type ProvidedExprType =
856856
| ProvidedNewArrayExpr of ProvidedType * ProvidedExpr[]
857-
#if PROVIDED_ADDRESS_OF
858-
| ProvidedAddressOfExpr of ProvidedExpr
859-
#endif
860857
| ProvidedNewObjectExpr of ProvidedConstructorInfo * ProvidedExpr[]
861858
| ProvidedWhileLoopExpr of ProvidedExpr * ProvidedExpr
862859
| ProvidedNewDelegateExpr of ProvidedType * ProvidedVar[] * ProvidedExpr
@@ -919,9 +916,6 @@ type ProvidedExpr (x: Expr, ctxt) =
919916
Some (ProvidedTryFinallyExpr (ProvidedExpr.Create ctxt b1, ProvidedExpr.Create ctxt b2))
920917
| Patterns.TryWith(b, v1, e1, v2, e2) ->
921918
Some (ProvidedTryWithExpr (ProvidedExpr.Create ctxt b, ProvidedVar.Create ctxt v1, ProvidedExpr.Create ctxt e1, ProvidedVar.Create ctxt v2, ProvidedExpr.Create ctxt e2))
922-
#if PROVIDED_ADDRESS_OF
923-
| Patterns.AddressOf e -> Some (ProvidedAddressOfExpr (ProvidedExpr.Create ctxt e))
924-
#endif
925919
| Patterns.TypeTest(e, ty) ->
926920
Some (ProvidedTypeTestExpr(ProvidedExpr.Create ctxt e, ProvidedType.Create ctxt ty))
927921
| Patterns.Let(v, e, b) ->

src/Compiler/TypedTree/TypeProviders.fsi

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -374,10 +374,6 @@ type ProvidedExprType =
374374

375375
| ProvidedNewArrayExpr of ProvidedType * ProvidedExpr[]
376376

377-
#if PROVIDED_ADDRESS_OF
378-
| ProvidedAddressOfExpr of ProvidedExpr
379-
#endif
380-
381377
| ProvidedNewObjectExpr of ProvidedConstructorInfo * ProvidedExpr[]
382378

383379
| ProvidedWhileLoopExpr of ProvidedExpr * ProvidedExpr

0 commit comments

Comments
 (0)