diff --git a/src/fsharp/NicePrint.fs b/src/fsharp/NicePrint.fs index 6d07c712693..50b8f8c9f63 100755 --- a/src/fsharp/NicePrint.fs +++ b/src/fsharp/NicePrint.fs @@ -46,7 +46,7 @@ module internal PrintUtilities = | x :: xs -> List.fold (^^) x xs let suppressInheritanceAndInterfacesForTyInSimplifiedDisplays g amap m ty = - isEnumTy g ty || isDelegateTy g ty || ExistsHeadTypeInEntireHierarchy g amap m ty g.exn_tcr || ExistsHeadTypeInEntireHierarchy g amap m ty g.tcref_System_Attribute + isEnumTy g ty || isDelegateTy g ty || ExistsHeadTypeInEntireHierarchy g amap m ty g.exn_tcr let applyMaxMembers maxMembers (allDecls: _ list) = match maxMembers with @@ -64,7 +64,25 @@ module internal PrintUtilities = | (x :: rest) -> [ resultFunction x (layoutFunction x -- leftL (tagText (match rest.Length with 1 -> FSComp.SR.nicePrintOtherOverloads1() | n -> FSComp.SR.nicePrintOtherOverloadsN(n)))) ] | _ -> [] - let layoutTyconRefImpl isAttribute (denv: DisplayEnv) (tcref: TyconRef) = + let layoutTyconRefImpl isAttribute (denv: DisplayEnv) (tcref: TyconRef) = + let tagEntityRefName (xref: EntityRef) name = + if xref.IsNamespace then tagNamespace name + elif xref.IsModule then tagModule name + elif xref.IsTypeAbbrev then + let ty = xref.TypeAbbrev.Value + match stripTyEqns denv.g ty with + | TType_app(tcref, _) when tcref.IsStructOrEnumTycon -> + tagStruct name + | _ -> + tagAlias name + elif xref.IsFSharpDelegateTycon then tagDelegate name + elif xref.IsILEnumTycon || xref.IsFSharpEnumTycon then tagEnum name + elif xref.IsStructOrEnumTycon then tagStruct name + elif isInterfaceTyconRef xref then tagInterface name + elif xref.IsUnionTycon then tagUnion name + elif xref.IsRecordTycon then tagRecord name + else tagClass name + let demangled = let name = if denv.includeStaticParametersInTypeNames then @@ -121,7 +139,7 @@ module private PrintIL = | [ "System"; "Int32" ] -> ["int" ] | [ "System"; "Int64" ] -> ["int64" ] | [ "System"; "UInt16" ] -> ["uint16" ] - | [ "System"; "UInt32" ] -> ["uint32" ] + | [ "System"; "UInt32" ] -> ["uint" ] | [ "System"; "UInt64" ] -> ["uint64" ] | [ "System"; "IntPtr" ] -> ["nativeint" ] | [ "System"; "UIntPtr" ] -> ["unativeint" ] @@ -138,25 +156,9 @@ module private PrintIL = let path = fullySplitILTypeRef tref layoutILTypeRefName denv path - /// this fixes up a name just like adjustILName but also handles F# - /// operators - let adjustILMethodName n = - let demangleOperatorNameIfNeeded s = - if IsMangledOpName s - then DemangleOperatorName s - else s - n |> Lexhelp.Keywords.QuoteIdentifierIfNeeded |> demangleOperatorNameIfNeeded - - let isStaticILEvent (e: ILEventDef) = - e.AddMethod.CallingSignature.CallingConv.IsStatic || - e.RemoveMethod.CallingSignature.CallingConv.IsStatic - let layoutILArrayShape (ILArrayShape sh) = SepL.leftBracket ^^ wordL (tagPunctuation (sh |> List.tail |> List.map (fun _ -> ",") |> String.concat "")) ^^ RightL.rightBracket // drop off one "," so that a n-dimensional array has n - 1 ","'s - let layoutILGenericParameterDefs (ps: ILGenericParameterDefs) = - ps |> List.map (fun x -> "'" + x.Name |> (tagTypeParameter >> wordL)) - let paramsL (ps: layout list) : layout = match ps with | [] -> emptyL @@ -206,115 +208,6 @@ module private PrintIL = | [x] -> x ^^ WordL.arrow ^^ res | _ -> sepListL WordL.star args ^^ WordL.arrow ^^ res - /// Layout a function pointer signature using type-only-F#-style. No argument names are printed. - // - // Note, this duplicates functionality in formatParamDataToBuffer - and layoutILParameter denv ilTyparSubst (p: ILParameter) = - let preL = - let isParamArray = TryFindILAttribute denv.g.attrib_ParamArrayAttribute p.CustomAttrs - match isParamArray, p.Name, p.IsOptional with - // Layout an optional argument - | _, Some nm, true -> LeftL.questionMark ^^ sepL (tagParameter nm) ^^ SepL.colon - // Layout an unnamed argument - | _, None, _ -> LeftL.colon - // Layout a named argument - | true, Some nm, _ -> - layoutBuiltinAttribute denv denv.g.attrib_ParamArrayAttribute ^^ wordL (tagParameter nm) ^^ SepL.colon - | false, Some nm, _ -> leftL (tagParameter nm) ^^ SepL.colon - preL ^^ (layoutILType denv ilTyparSubst p.Type) - - - /// Layout a function pointer signature using type-only-F#-style. No argument names are printed. - and layoutILParameters denv ilTyparSubst cons (parameters: ILParameters, retType: ILType) = - // We need a special case for constructors (Their return types are reported as `void`, but this is - // incorrect; so if we're dealing with a constructor we require that the - // return type be passed along as the `cons` parameter.) - let res = - match cons with - | Some className -> - let names = SplitNamesForILPath (PrettyNaming.DemangleGenericTypeName className) - layoutILTypeRefName denv names ^^ (pruneParams className ilTyparSubst |> paramsL) - | None -> retType |> layoutILType denv ilTyparSubst - - match parameters with - | [] -> WordL.structUnit ^^ WordL.arrow ^^ res - | [x] -> layoutILParameter denv ilTyparSubst x ^^ WordL.arrow ^^ res - | args -> sepListL WordL.star (List.map (layoutILParameter denv ilTyparSubst) args) ^^ WordL.arrow ^^ res - - - /// Layout a method's signature using type-only-F#-style. No argument names are printed. - /// - /// In the case that we've a constructor, we - /// pull off the class name from the `path`; naturally, it's the - /// most-deeply-nested element. - // - // For C# and provided members: - // new: argType1 * ... * argTypeN -> retType - // Method: argType1 * ... * argTypeN -> retType - // - let layoutILMethodDef denv ilTyparSubst className (m: ILMethodDef) = - let myParms = m.GenericParams |> layoutILGenericParameterDefs - let ilTyparSubst = ilTyparSubst @ myParms - let name = adjustILMethodName m.Name - let (nameL, isCons) = - match () with - | _ when m.IsConstructor -> (WordL.keywordNew, Some className) // we need the unadjusted name here to be able to grab the number of generic parameters - | _ when m.IsStatic -> (WordL.keywordStatic ^^ WordL.keywordMember ^^ wordL (tagMethod name) ^^ (myParms |> paramsL), None) - | _ -> (WordL.keywordMember ^^ wordL (tagMethod name) ^^ (myParms |> paramsL), None) - let signatureL = (m.Parameters, m.Return.Type) |> layoutILParameters denv ilTyparSubst isCons - nameL ^^ WordL.colon ^^ signatureL - - let layoutILFieldDef (denv: DisplayEnv) (ilTyparSubst: layout list) (f: ILFieldDef) = - let staticL = if f.IsStatic then WordL.keywordStatic else emptyL - let name = adjustILName f.Name - let nameL = wordL (tagField name) - let typL = layoutILType denv ilTyparSubst f.FieldType - staticL ^^ WordL.keywordVal ^^ nameL ^^ WordL.colon ^^ typL - - let layoutILEventDef denv ilTyparSubst (e: ILEventDef) = - let staticL = if isStaticILEvent e then WordL.keywordStatic else emptyL - let name = adjustILName e.Name - let nameL = wordL (tagEvent name) - let typL = - match e.EventType with - | Some t -> layoutILType denv ilTyparSubst t - | _ -> emptyL - staticL ^^ WordL.keywordEvent ^^ nameL ^^ WordL.colon ^^ typL - - let layoutILPropertyDef denv ilTyparSubst (p: ILPropertyDef) = - let staticL = if p.CallingConv = ILThisConvention.Static then WordL.keywordStatic else emptyL - let name = adjustILName p.Name - let nameL = wordL (tagProperty name) - - let layoutGetterType (getterRef: ILMethodRef) = - if isNil getterRef.ArgTypes then - layoutILType denv ilTyparSubst getterRef.ReturnType - else - layoutILCallingSignature denv ilTyparSubst None getterRef.CallingSignature - - let layoutSetterType (setterRef: ILMethodRef) = - let argTypes = setterRef.ArgTypes - if isNil argTypes then - emptyL // shouldn't happen - else - let frontArgs, lastArg = List.frontAndBack argTypes - let argsL = frontArgs |> List.map (layoutILType denv ilTyparSubst) |> sepListL WordL.star - argsL ^^ WordL.arrow ^^ (layoutILType denv ilTyparSubst lastArg) - - let typL = - match p.GetMethod, p.SetMethod with - | None, None -> layoutILType denv ilTyparSubst p.PropertyType // shouldn't happen - | Some getterRef, _ -> layoutGetterType getterRef - | None, Some setterRef -> layoutSetterType setterRef - - let specGetSetL = - match p.GetMethod, p.SetMethod with - | None, None - | Some _, None -> emptyL - | None, Some _ -> WordL.keywordWith ^^ WordL.keywordSet - | Some _, Some _ -> WordL.keywordWith ^^ WordL.keywordGet ^^ RightL.comma ^^ WordL.keywordSet - staticL ^^ WordL.keywordMember ^^ nameL ^^ WordL.colon ^^ typL ^^ specGetSetL - let layoutILFieldInit x = let textOpt = match x with @@ -356,187 +249,6 @@ module private PrintIL = let layoutILEnumDefParts nm litVal = WordL.bar ^^ wordL (tagEnum (adjustILName nm)) ^^ layoutILFieldInit litVal - let layoutILEnumDef (f: ILFieldDef) = layoutILEnumDefParts f.Name f.LiteralValue - - // filtering methods for hiding things we oughtn't show - let isStaticILProperty (p: ILPropertyDef) = - match p.GetMethod, p.SetMethod with - | Some getter, _ -> getter.CallingSignature.CallingConv.IsStatic - | None, Some setter -> setter.CallingSignature.CallingConv.IsStatic - | None, None -> true - - let isPublicILMethod (m: ILMethodDef) = - (m.Access = ILMemberAccess.Public) - - let isPublicILEvent typeDef (e: ILEventDef) = - try - isPublicILMethod(resolveILMethodRef typeDef e.AddMethod) && - isPublicILMethod(resolveILMethodRef typeDef e.RemoveMethod) - with _ -> - false - - let isPublicILProperty typeDef (m: ILPropertyDef) = - try - match m.GetMethod with - | Some ilMethRef -> isPublicILMethod (resolveILMethodRef typeDef ilMethRef) - | None -> - match m.SetMethod with - | None -> false - | Some ilMethRef -> isPublicILMethod (resolveILMethodRef typeDef ilMethRef) - // resolveILMethodRef is a possible point of failure if Abstract IL type equality checking fails - // to link the method ref to a method def for some reason, e.g. some feature of IL type - // equality checking has not been implemented. Since this is just intellisense pretty printing code - // it is better to swallow the exception here, though we don't know of any - // specific cases where this happens - with _ -> - false - - let isPublicILCtor (m: ILMethodDef) = - (m.Access = ILMemberAccess.Public && m.IsConstructor) - - let isNotSpecialName (m: ILMethodDef) = - not m.IsSpecialName - - let isPublicILField (f: ILFieldDef) = - (f.Access = ILMemberAccess.Public) - - let isPublicILTypeDef (c: ILTypeDef) : bool = - match c.Access with - | ILTypeDefAccess.Public - | ILTypeDefAccess.Nested ILMemberAccess.Public -> true - | _ -> false - - let isShowEnumField (f: ILFieldDef) : bool = f.Name <> "value__" // this appears to be the hard-coded underlying storage field - let noShow = set [ "System.Object" ; "Object"; "System.ValueType" ; "ValueType"; "obj" ] // hide certain 'obvious' base classes - let isShowBase (n: layout) : bool = - not (noShow.Contains(showL n)) - - let rec layoutILTypeDef (denv: DisplayEnv) (typeDef: ILTypeDef) : layout = - let ilTyparSubst = typeDef.GenericParams |> layoutILGenericParameterDefs - - let renderL pre body post = - match pre with - | Some pre -> - match body with - | [] -> emptyL // empty type - | _ -> (pre @@-- aboveListL body) @@ post - | None -> - aboveListL body - - if typeDef.IsClass || typeDef.IsStruct || typeDef.IsInterface then - let pre = - if typeDef.IsStruct then Some WordL.keywordStruct - else None - - let baseTypeL = - [ match typeDef.Extends with - | Some b -> - let baseName = layoutILType denv ilTyparSubst b - if isShowBase baseName then - yield WordL.keywordInherit ^^ baseName - | None -> - // for interface show inherited interfaces - if typeDef.IsInterface then - for b in typeDef.Implements do - let baseName = layoutILType denv ilTyparSubst b - if isShowBase baseName then - yield WordL.keywordInherit ^^ baseName ] - - let memberBlockLs (fieldDefs: ILFieldDefs, methodDefs: ILMethodDefs, propertyDefs: ILPropertyDefs, eventDefs: ILEventDefs) = - let ctors = - methodDefs.AsList - |> List.filter isPublicILCtor - |> List.sortBy (fun md -> md.Parameters.Length) - |> shrinkOverloads (layoutILMethodDef denv ilTyparSubst typeDef.Name) (fun _ xL -> xL) - - let fields = - fieldDefs.AsList - |> List.filter isPublicILField - |> List.map (layoutILFieldDef denv ilTyparSubst) - - let props = - propertyDefs.AsList - |> List.filter (isPublicILProperty typeDef) - |> List.map (fun pd -> (pd.Name, pd.Args.Length), layoutILPropertyDef denv ilTyparSubst pd) - - let events = - eventDefs.AsList - |> List.filter (isPublicILEvent typeDef) - |> List.map (layoutILEventDef denv ilTyparSubst) - - let meths = - methodDefs.AsList - |> List.filter isPublicILMethod - |> List.filter isNotSpecialName - |> List.map (fun md -> (md.Name, md.Parameters.Length), md) - // collect into overload groups - |> List.groupBy (fst >> fst) - |> List.collect (fun (_, group) -> group |> List.sortBy fst |> shrinkOverloads (snd >> layoutILMethodDef denv ilTyparSubst typeDef.Name) (fun x xL -> (fst x, xL))) - - let members = - (props @ meths) - |> List.sortBy fst - |> List.map snd // (properties and members) are sorted by name/arity - - ctors @ fields @ members @ events - - let bodyStatic = - memberBlockLs - (typeDef.Fields.AsList |> List.filter (fun fd -> fd.IsStatic) |> mkILFields, - typeDef.Methods.AsList |> List.filter (fun md -> md.IsStatic) |> mkILMethods, - typeDef.Properties.AsList |> List.filter isStaticILProperty |> mkILProperties, - typeDef.Events.AsList |> List.filter isStaticILEvent |> mkILEvents) - - let bodyInstance = - memberBlockLs - (typeDef.Fields.AsList |> List.filter (fun fd -> not (fd.IsStatic)) |> mkILFields, - typeDef.Methods.AsList |> List.filter (fun md -> not (md.IsStatic)) |> mkILMethods, - typeDef.Properties.AsList |> List.filter (fun pd -> not (isStaticILProperty pd)) |> mkILProperties, - typeDef.Events.AsList |> List.filter (fun ed -> not (isStaticILEvent ed)) |> mkILEvents ) - - let body = bodyInstance @ bodyStatic // instance "member" before "static member" - - // Only show at most maxMembers members... - let body = applyMaxMembers denv.maxMembers body - - let types = - typeDef.NestedTypes.AsList - |> List.filter isPublicILTypeDef - |> List.sortBy(fun t -> adjustILName t.Name) - |> List.map (layoutILNestedClassDef denv) - - let post = WordL.keywordEnd - renderL pre (baseTypeL @ body @ types ) post - - elif typeDef.IsEnum then - let fldsL = - typeDef.Fields.AsList - |> List.filter isShowEnumField - |> List.map layoutILEnumDef - |> applyMaxMembers denv.maxMembers - - renderL None fldsL emptyL - - else // Delegate - let rhs = - match typeDef.Methods.AsList |> List.filter (fun m -> m.Name = "Invoke") with // the delegate delegates to the type of `Invoke` - | m :: _ -> layoutILCallingSignature denv ilTyparSubst None m.CallingSignature - | _ -> comment "`Invoke` method could not be found" - WordL.keywordDelegate ^^ WordL.keywordOf ^^ rhs - - and layoutILNestedClassDef (denv: DisplayEnv) (typeDef: ILTypeDef) = - let name = adjustILName typeDef.Name - let nameL = wordL (tagClass name) - let ilTyparSubst = typeDef.GenericParams |> layoutILGenericParameterDefs - let paramsL = pruneParams typeDef.Name ilTyparSubst |> paramsL - if denv.suppressNestedTypes then - WordL.keywordNested ^^ WordL.keywordType ^^ nameL ^^ paramsL - else - let pre = WordL.keywordNested ^^ WordL.keywordType ^^ nameL ^^ paramsL - let body = layoutILTypeDef denv typeDef - (pre ^^ WordL.equals) @@-- body - - module private PrintTypes = // Note: We need nice printing of constants in order to print literals and attributes let layoutConst g ty c = @@ -735,9 +447,7 @@ module private PrintTypes = | _ -> squareAngleL (sepListL (rightL (tagPunctuation ";")) (List.map (layoutAttrib denv) attrs)) @@ restL - elif not isValue && - (isStructRecordOrUnionTyconTy denv.g ty || - ((isUnionTy denv.g ty || isRecdTy denv.g ty) && HasFSharpAttribute denv.g denv.g.attrib_StructAttribute attrs)) then + elif not isValue && (isStructTy denv.g ty && not (isEnumTy denv.g ty)) then squareAngleL (wordL (tagClass "Struct")) @@ restL else match kind with @@ -1329,7 +1039,23 @@ module private PrintTastMemberOrVals = let cxs = env.postfixConstraints let argInfos, rty = GetTopTauTypeInFSharpForm denv.g (arityOfVal v).ArgInfos tau v.Range let nameL = - (if v.IsModuleBinding then tagModuleBinding else tagUnknownEntity) v.DisplayName + let isDiscard (str: string) = str.StartsWith("_") + + let tagF = + if isForallFunctionTy denv.g v.Type && not (isDiscard v.DisplayName) then + if IsOperatorName v.DisplayName then + tagOperator + else + tagFunction + elif not v.IsCompiledAsTopLevel && not(isDiscard v.DisplayName) then + tagLocal + elif v.IsModuleBinding then + tagModuleBinding + else + tagUnknownEntity + + v.DisplayName + |> tagF |> mkNav v.DefinitionRange |> wordL let nameL = layoutAccessibility denv v.Accessibility nameL @@ -1439,30 +1165,35 @@ module InfoMemberPrinting = // new: argName1: argType1 * ... * argNameN: argTypeN -> retType // Method: argName1: argType1 * ... * argNameN: argTypeN -> retType let private layoutMethInfoFSharpStyleCore amap m denv (minfo: MethInfo) minst = - let layout = - if not minfo.IsConstructor && not minfo.IsInstance then WordL.keywordStatic - else emptyL - let layout = - layout ^^ - ( - if minfo.IsConstructor then - wordL (tagKeyword "new") - else - WordL.keywordMember ^^ - PrintTypes.layoutTyparDecls denv (wordL (tagMethod minfo.LogicalName)) true minfo.FormalMethodTypars - ) ^^ - WordL.colon - let paramDatas = minfo.GetParamDatas(amap, m, minst) - let layout = + match minfo.ArbitraryValRef with + | Some vref -> + PrintTastMemberOrVals.prettyLayoutOfValOrMemberNoInst denv vref.Deref + | None -> + let layout = + if not minfo.IsConstructor && not minfo.IsInstance then WordL.keywordStatic + else emptyL + + let layout = + layout ^^ + ( + if minfo.IsConstructor then + wordL (tagKeyword "new") + else + WordL.keywordMember ^^ + PrintTypes.layoutTyparDecls denv (minfo.LogicalName |> tagMethod |> wordL) true minfo.FormalMethodTypars + ) ^^ + WordL.colon + let paramDatas = minfo.GetParamDatas(amap, m, minst) + let layout = + layout ^^ + if List.forall isNil paramDatas then + WordL.structUnit + else + sepListL WordL.arrow (List.map ((List.map (layoutParamData denv)) >> sepListL WordL.star) paramDatas) + let retTy = minfo.GetFSharpReturnTy(amap, m, minst) layout ^^ - if List.forall isNil paramDatas then - WordL.structUnit - else - sepListL WordL.arrow (List.map ((List.map (layoutParamData denv)) >> sepListL WordL.star) paramDatas) - let retTy = minfo.GetFSharpReturnTy(amap, m, minst) - layout ^^ - WordL.arrow ^^ - PrintTypes.layoutType denv retTy + WordL.arrow ^^ + PrintTypes.layoutType denv retTy /// Format a method info using "half C# style". // @@ -1658,9 +1389,7 @@ module private TastDefinitionPrinting = | TProvidedNamespaceExtensionPoint _ #endif | TNoRepr -> false - - - + #if !NO_EXTENSIONTYPING let private layoutILFieldInfo denv amap m (e: ILFieldInfo) = let staticL = if e.IsStatic then WordL.keywordStatic else emptyL @@ -1670,44 +1399,83 @@ module private TastDefinitionPrinting = let private layoutEventInfo denv amap m (e: EventInfo) = let staticL = if e.IsStatic then WordL.keywordStatic else emptyL - let nameL = wordL (tagEvent (adjustILName e.EventName)) + + let eventTag = + let tag = + e.EventName + |> adjustILName + |> tagEvent + + match e.ArbitraryValRef with + | Some vref -> + tag |> mkNav vref.DefinitionRange + | None -> + tag + + let nameL = eventTag |> wordL let typL = layoutType denv (e.GetDelegateType(amap, m)) staticL ^^ WordL.keywordEvent ^^ nameL ^^ WordL.colon ^^ typL let private layoutPropInfo denv amap m (p: PropInfo) = - let staticL = if p.IsStatic then WordL.keywordStatic else emptyL - let nameL = wordL (tagProperty (adjustILName p.PropertyName)) + match p.ArbitraryValRef with + | Some v -> + PrintTastMemberOrVals.prettyLayoutOfValOrMemberNoInst denv v.Deref + | None -> + let modifierAndMember = + if p.IsStatic then + WordL.keywordStatic ^^ WordL.keywordMember + else + WordL.keywordMember + + let propTag = + p.PropertyName + |> adjustILName + |> tagProperty + + let nameL = propTag |> wordL - let typL = layoutType denv (p.GetPropertyType(amap, m)) // shouldn't happen - - let specGetSetL = - match p.HasGetter, p.HasSetter with - | false, false | true, false -> emptyL - | false, true -> WordL.keywordWith ^^ WordL.keywordSet - | true, true -> WordL.keywordWith ^^ WordL.keywordGet^^ SepL.comma ^^ WordL.keywordSet - - staticL ^^ WordL.keywordMember ^^ nameL ^^ WordL.colon ^^ typL ^^ specGetSetL - - /// Another re-implementation of type printing, this time based off provided info objects. - let layoutProvidedTycon (denv: DisplayEnv) (infoReader: InfoReader) ad m start lhsL ty = - let g = denv.g - let tcref = tcrefOfAppTy g ty - - if isEnumTy g ty then - let fieldLs = - infoReader.GetILFieldInfosOfType (None, ad, m, ty) - |> List.filter (fun x -> x.FieldName <> "value__") - |> List.map (fun x -> PrintIL.layoutILEnumDefParts x.FieldName x.LiteralValue) - |> aboveListL - (lhsL ^^ WordL.equals) @@-- fieldLs - else + let typL = layoutType denv (p.GetPropertyType(amap, m)) // shouldn't happen + + modifierAndMember ^^ nameL ^^ WordL.colon ^^ typL + + let layoutTycon (denv: DisplayEnv) (infoReader: InfoReader) ad m simplified typewordL (tycon: Tycon) = + let g = denv.g + let _, ty = generalizeTyconRef (mkLocalTyconRef tycon) + let start, name = + let n = tycon.DisplayName + if isStructTy g ty then + if denv.printVerboseSignatures then + Some "struct", tagStruct n + else + None, tagStruct n + elif isInterfaceTy g ty then + if denv.printVerboseSignatures then + Some "interface", tagInterface n + else + None, tagInterface n + elif isClassTy g ty then + if denv.printVerboseSignatures then + (if simplified then None else Some "class"), tagClass n + else + None, tagClass n + else + None, tagUnknownType n + let name = mkNav tycon.DefinitionRange name + let nameL = layoutAccessibility denv tycon.Accessibility (wordL name) + let denv = denv.AddAccessibility tycon.Accessibility + let lhsL = + let tps = tycon.TyparsNoRange + let tpsL = layoutTyparDecls denv nameL tycon.IsPrefixDisplay tps + typewordL ^^ tpsL + + let start = Option.map tagKeyword start let amap = infoReader.amap let sortKey (v: MethInfo) = (not v.IsConstructor, - not v.IsInstance, // instance first - v.DisplayName, // sort by name - List.sum v.NumArgs, // sort by #curried - v.NumArgs.Length) // sort by arity + not v.IsInstance, // instance first + v.DisplayName, // sort by name + List.sum v.NumArgs, // sort by #curried + v.NumArgs.Length) // sort by arity let shouldShow (valRef: ValRef option) = match valRef with @@ -1715,272 +1483,265 @@ module private TastDefinitionPrinting = | Some(vr) -> (denv.showObsoleteMembers || not (CheckFSharpAttributesForObsolete denv.g vr.Attribs)) && (denv.showHiddenMembers || not (CheckFSharpAttributesForHidden denv.g vr.Attribs)) + + let isDiscard (name: string) = name.StartsWith("_") let ctors = GetIntrinsicConstructorInfosOfType infoReader m ty - |> List.filter (fun v -> shouldShow v.ArbitraryValRef) - - let meths = - GetImmediateIntrinsicMethInfosOfType (None, ad) g amap m ty - |> List.filter (fun v -> shouldShow v.ArbitraryValRef) + |> List.filter (fun v -> not v.IsClassConstructor && shouldShow v.ArbitraryValRef) - let iimplsLs = + let iimplsLs = if suppressInheritanceAndInterfacesForTyInSimplifiedDisplays g amap m ty then [] + elif isRecdTy g ty || isUnionTy g ty || tycon.IsStructOrEnumTycon then + tycon.ImmediateInterfacesOfFSharpTycon + |> List.filter (fun (_, compgen, _) -> not compgen) + |> List.map (fun (ty, _, _) -> wordL (tagKeyword "interface") --- layoutType denv ty) else - GetImmediateInterfacesOfType SkipUnrefInterfaces.Yes g amap m ty |> List.map (fun ity -> wordL (tagKeyword (if isInterfaceTy g ty then "inherit" else "interface")) --- layoutType denv ity) + GetImmediateInterfacesOfType SkipUnrefInterfaces.Yes g amap m ty + |> List.map (fun ity -> wordL (tagKeyword (if isInterfaceTy g ty then "inherit" else "interface")) --- layoutType denv ity) - let props = - GetIntrinsicPropInfosOfType infoReader None ad AllowMultiIntfInstantiations.Yes PreferOverrides m ty + let props = + GetImmediateIntrinsicPropInfosOfType (None, ad) g amap m ty |> List.filter (fun v -> shouldShow v.ArbitraryValRef) let events = infoReader.GetEventInfosOfType(None, ad, m, ty) - |> List.filter (fun v -> shouldShow v.ArbitraryValRef) + |> List.filter (fun v -> shouldShow v.ArbitraryValRef && typeEquiv g ty v.ApparentEnclosingType) let impliedNames = try Set.ofList [ for p in props do if p.HasGetter then yield p.GetterMethod.DisplayName if p.HasSetter then yield p.SetterMethod.DisplayName - for e in events do + for e in events do yield e.AddMethod.DisplayName yield e.RemoveMethod.DisplayName ] with _ -> Set.empty - let ctorLs = - ctors - |> shrinkOverloads (InfoMemberPrinting.layoutMethInfoFSharpStyle amap m denv) (fun _ xL -> xL) + let meths = + GetImmediateIntrinsicMethInfosOfType (None, ad) g amap m ty + |> List.filter (fun m -> + not m.IsClassConstructor && + not m.IsConstructor && + shouldShow m.ArbitraryValRef && + not (impliedNames.Contains m.DisplayName) && + not (m.DisplayName.Split('.') |> Array.exists (fun part -> isDiscard part))) + + let ctorLs = + if denv.shrinkOverloads then + ctors + |> shrinkOverloads (InfoMemberPrinting.layoutMethInfoFSharpStyle amap m denv) (fun _ xL -> xL) + else + ctors + |> List.map (fun ctor -> InfoMemberPrinting.layoutMethInfoFSharpStyle amap m denv ctor) let methLs = - meths - |> List.filter (fun md -> not (impliedNames.Contains md.DisplayName)) + meths |> List.groupBy (fun md -> md.DisplayName) - |> List.collect (fun (_, group) -> shrinkOverloads (InfoMemberPrinting.layoutMethInfoFSharpStyle amap m denv) (fun x xL -> (sortKey x, xL)) group) - - let fieldLs = - infoReader.GetILFieldInfosOfType (None, ad, m, ty) + |> List.collect (fun (_, group) -> + if denv.shrinkOverloads then + shrinkOverloads (InfoMemberPrinting.layoutMethInfoFSharpStyle amap m denv) (fun x xL -> (sortKey x, xL)) group + else + group + |> List.sortBy sortKey + |> List.map (fun methinfo -> ((not methinfo.IsConstructor, methinfo.IsInstance, methinfo.DisplayName, List.sum methinfo.NumArgs, methinfo.NumArgs.Length), InfoMemberPrinting.layoutMethInfoFSharpStyle amap m denv methinfo))) + |> List.sortBy fst + |> List.map snd + + let fieldLs = + infoReader.GetILFieldInfosOfType (None, ad, m, ty) + |> List.filter (fun fld -> not (isDiscard fld.FieldName)) |> List.map (fun x -> (true, x.IsStatic, x.FieldName, 0, 0), layoutILFieldInfo denv amap m x) + |> List.sortBy fst + |> List.map snd + + let staticValsLs = + if isRecdTy g ty then + [] + else + tycon.TrueFieldsAsList + |> List.filter (fun f -> f.IsStatic && not (isDiscard f.Name)) + |> List.map (fun f -> WordL.keywordStatic ^^ WordL.keywordVal ^^ layoutRecdField true denv f) + + let instanceValsLs = + if isRecdTy g ty then + [] + else + tycon.TrueInstanceFieldsAsList + |> List.filter (fun f -> not (isDiscard f.Name)) + |> List.map (fun f -> WordL.keywordVal ^^ layoutRecdField true denv f) - let propLs = + let propLs = props |> List.map (fun x -> (true, x.IsStatic, x.PropertyName, 0, 0), layoutPropInfo denv amap m x) + |> List.sortBy fst + |> List.map snd let eventLs = events |> List.map (fun x -> (true, x.IsStatic, x.EventName, 0, 0), layoutEventInfo denv amap m x) - - let membLs = (methLs @ fieldLs @ propLs @ eventLs) |> List.sortBy fst |> List.map snd - - let nestedTypeLs = - match tcref.TypeReprInfo with - | TProvidedTypeExtensionPoint info -> - [ - for nestedType in info.ProvidedType.PApplyArray((fun sty -> sty.GetNestedTypes()), "GetNestedTypes", m) do - yield nestedType.PUntaint((fun t -> t.IsClass, t.Name), m) - ] - |> List.sortBy snd - |> List.map (fun (isClass, t) -> WordL.keywordNested ^^ WordL.keywordType ^^ wordL ((if isClass then tagClass else tagStruct) t)) - | _ -> - [] + |> List.sortBy fst + |> List.map snd + + let nestedTypeLs = + match tryTcrefOfAppTy g ty with + | ValueSome tcref -> + match tcref.TypeReprInfo with + | TProvidedTypeExtensionPoint info -> + [ + for nestedType in info.ProvidedType.PApplyArray((fun sty -> sty.GetNestedTypes()), "GetNestedTypes", m) do + yield nestedType.PUntaint((fun t -> t.IsClass, t.Name), m) + ] + |> List.sortBy snd + |> List.map (fun (isClass, t) -> WordL.keywordNested ^^ WordL.keywordType ^^ wordL ((if isClass then tagClass else tagStruct) t)) + | _ -> + [] + | ValueNone -> + [] let inherits = if suppressInheritanceAndInterfacesForTyInSimplifiedDisplays g amap m ty then [] else match GetSuperTypeOfType g amap m ty with - | Some super when not (isObjTy g super) -> [wordL (tagKeyword "inherit") ^^ (layoutType denv super)] + | Some super when not (isObjTy g super) && not (isValueTypeTy g super) -> + [wordL (tagKeyword "inherit") ^^ (layoutType denv super)] | _ -> [] let erasedL = #if SHOW_ERASURE - if tcref.IsProvidedErasedTycon then - [ wordL ""; wordL (FSComp.SR.erasedTo()) ^^ PrintIL.layoutILTypeRef { denv with shortTypeNames = false } tcref.CompiledRepresentationForNamedType; wordL "" ] - else + match tryTcrefOfAppTy g ty with + | ValueSome tcref -> + if tcref.IsProvidedErasedTycon then + [ wordL ""; wordL (FSComp.SR.erasedTo()) ^^ PrintIL.layoutILTypeRef { denv with shortTypeNames = false } tcref.CompiledRepresentationForNamedType; wordL "" ] + else + [] + | None -> #endif [] - let decls = inherits @ iimplsLs @ ctorLs @ membLs @ nestedTypeLs @ erasedL - if isNil decls then - lhsL - else - let declsL = (inherits @ iimplsLs @ ctorLs @ membLs @ nestedTypeLs @ erasedL) |> applyMaxMembers denv.maxMembers |> aboveListL - let rhsL = match start with Some s -> (wordL s @@-- declsL) @@ WordL.keywordEnd | None -> declsL - (lhsL ^^ WordL.equals) @@-- rhsL -#endif - let layoutTycon (denv: DisplayEnv) (infoReader: InfoReader) ad m simplified typewordL (tycon: Tycon) = - let g = denv.g - let _, ty = generalizeTyconRef (mkLocalTyconRef tycon) - let start, name = - let n = tycon.DisplayName - if isStructTy g ty then Some "struct", tagStruct n - elif isInterfaceTy g ty then Some "interface", tagInterface n - elif isClassTy g ty then (if simplified then None else Some "class" ), tagClass n - else None, tagUnknownType n - let name = mkNav tycon.DefinitionRange name - let nameL = layoutAccessibility denv tycon.Accessibility (wordL name) - let denv = denv.AddAccessibility tycon.Accessibility - let lhsL = - let tps = tycon.TyparsNoRange - let tpsL = layoutTyparDecls denv nameL tycon.IsPrefixDisplay tps - typewordL ^^ tpsL - let start = Option.map tagKeyword start -#if !NO_EXTENSIONTYPING - match tycon.IsProvided with - | true -> - layoutProvidedTycon denv infoReader ad m start lhsL ty - | false -> -#else - ignore (infoReader, ad, m) + let decls = inherits @ iimplsLs @ ctorLs @ methLs @ fieldLs @ propLs @ eventLs @ instanceValsLs @ staticValsLs @ nestedTypeLs @ erasedL + let declsL = + decls + |> applyMaxMembers denv.maxMembers + |> aboveListL + |> fun declsL -> + match start with + | Some s -> (wordL s @@-- declsL) @@ wordL (tagKeyword "end") + | None -> declsL + + let addMembersAsWithEnd reprL = + if isNil decls then + reprL + else + let memberLs = applyMaxMembers denv.maxMembers decls + if simplified then + reprL @@-- aboveListL memberLs + else + reprL @@ (WordL.keywordWith @@-- aboveListL memberLs) @@ WordL.keywordEnd + + let reprL = + let repr = tycon.TypeReprInfo + match repr with + | TRecdRepr _ + | TUnionRepr _ + | TFSharpObjectRepr _ + | TAsmRepr _ + | TMeasureableRepr _ + | TILObjectRepr _ -> + let brk = not (isNil decls) || breakTypeDefnEqn repr + let rhsL = + let addReprAccessL l = layoutAccessibility denv tycon.TypeReprAccessibility l + let denv = denv.AddAccessibility tycon.TypeReprAccessibility + match repr with + | TRecdRepr _ -> + let recdFieldRefL fld = layoutRecdField false denv fld + + let recdL = + tycon.TrueFieldsAsList + |> List.map recdFieldRefL + |> applyMaxMembers denv.maxMembers + |> aboveListL + |> braceL + + Some (addMembersAsWithEnd (addReprAccessL recdL)) + + | TUnionRepr _ -> + let layoutUnionCases = + tycon.UnionCasesAsList + |> layoutUnionCases denv + |> applyMaxMembers denv.maxMembers + |> aboveListL + Some (addMembersAsWithEnd (addReprAccessL layoutUnionCases)) + + | TFSharpObjectRepr r -> + match r.fsobjmodel_kind with + | TTyconDelegate (TSlotSig(_, _, _, _, paraml, rty)) -> + let rty = GetFSharpViewOfReturnType denv.g rty + Some (WordL.keywordDelegate ^^ WordL.keywordOf --- layoutTopType denv SimplifyTypes.typeSimplificationInfo0 (paraml |> List.mapSquared (fun sp -> (sp.Type, ValReprInfo.unnamedTopArg1))) rty []) + | _ -> + match r.fsobjmodel_kind with + | TTyconEnum -> + tycon.TrueFieldsAsList + |> List.map (fun f -> + match f.LiteralValue with + | None -> emptyL + | Some c -> WordL.bar ^^ + wordL (tagField f.Name) ^^ + WordL.equals ^^ + layoutConst denv.g ty c) + |> aboveListL + |> Some + | _ -> + let allDecls = inherits @ iimplsLs @ ctorLs @ instanceValsLs @ methLs @ propLs @ eventLs @ staticValsLs + if isNil allDecls then + None + else + let allDecls = applyMaxMembers denv.maxMembers allDecls + let emptyMeasure = match tycon.TypeOrMeasureKind with TyparKind.Measure -> isNil allDecls | _ -> false + if emptyMeasure then None else + let declsL = aboveListL allDecls + let declsL = match start with Some s -> (wordL s @@-- declsL) @@ wordL (tagKeyword "end") | None -> declsL + Some declsL + + | TAsmRepr _ -> + Some (wordL (tagText "(# \"\" #)")) + + | TMeasureableRepr ty -> + Some (layoutType denv ty) + + | TILObjectRepr _ -> + if tycon.ILTyconRawMetadata.IsEnum then + infoReader.GetILFieldInfosOfType (None, ad, m, ty) + |> List.filter (fun x -> x.FieldName <> "value__") + |> List.map (fun x -> PrintIL.layoutILEnumDefParts x.FieldName x.LiteralValue) + |> applyMaxMembers denv.maxMembers + |> aboveListL + |> Some + else + Some declsL + + | _ -> None + + let brk = match tycon.TypeReprInfo with | TILObjectRepr _ -> true | _ -> brk + match rhsL with + | None -> lhsL + | Some rhsL -> + if brk then + (lhsL ^^ WordL.equals) @@-- rhsL + else + (lhsL ^^ WordL.equals) --- rhsL + + | _ -> + match tycon.TypeAbbrev with + | None -> + addMembersAsWithEnd (lhsL ^^ WordL.equals) + | Some a -> + (lhsL ^^ WordL.equals) --- (layoutType { denv with shortTypeNames = false } a) + + layoutAttribs denv false ty tycon.TypeOrMeasureKind tycon.Attribs reprL #endif - let memberImplementLs, memberCtorLs, memberInstanceLs, memberStaticLs = - let adhoc = - tycon.MembersOfFSharpTyconSorted - |> List.filter (fun v -> not v.IsDispatchSlot) - |> List.filter (fun v -> not v.Deref.IsClassConstructor) - |> List.filter (fun v -> - match v.MemberInfo.Value.ImplementedSlotSigs with - | TSlotSig(_, oty, _, _, _, _) :: _ -> - // Don't print overrides in HTML docs - denv.showOverrides && - // Don't print individual methods forming interface implementations - these are currently never exported - not (isInterfaceTy denv.g oty) - | [] -> true) - |> List.filter (fun v -> denv.showObsoleteMembers || not (CheckFSharpAttributesForObsolete denv.g v.Attribs)) - |> List.filter (fun v -> denv.showHiddenMembers || not (CheckFSharpAttributesForHidden denv.g v.Attribs)) - // sort - let sortKey (v: ValRef) = - (not v.IsConstructor, // constructors before others - v.Id.idText, // sort by name - (if v.IsCompiledAsTopLevel then v.ValReprInfo.Value.NumCurriedArgs else 0), // sort by #curried - (if v.IsCompiledAsTopLevel then v.ValReprInfo.Value.AritiesOfArgs else [])) // sort by arity - let adhoc = adhoc |> List.sortBy sortKey - let iimpls = - match tycon.TypeReprInfo with - | TFSharpObjectRepr r when (match r.fsobjmodel_kind with TTyconInterface -> true | _ -> false) -> [] - | _ -> tycon.ImmediateInterfacesOfFSharpTycon - let iimpls = iimpls |> List.filter (fun (_, compgen, _) -> not compgen) - // if TTyconInterface, the iimpls should be printed as inherited interfaces - let iimplsLs = iimpls |> List.map (fun (ty, _, _) -> wordL (tagKeyword "interface") --- layoutType denv ty) - let adhocCtorsLs = adhoc |> List.filter (fun v -> v.IsConstructor) |> List.map (fun vref -> PrintTastMemberOrVals.prettyLayoutOfValOrMemberNoInst denv vref.Deref) - let adhocInstanceLs = adhoc |> List.filter (fun v -> not v.IsConstructor && v.IsInstanceMember) |> List.map (fun vref -> PrintTastMemberOrVals.prettyLayoutOfValOrMemberNoInst denv vref.Deref) - let adhocStaticLs = adhoc |> List.filter (fun v -> not v.IsConstructor && not v.IsInstanceMember) |> List.map (fun vref -> PrintTastMemberOrVals.prettyLayoutOfValOrMemberNoInst denv vref.Deref) - iimplsLs, adhocCtorsLs, adhocInstanceLs, adhocStaticLs - let memberLs = memberImplementLs @ memberCtorLs @ memberInstanceLs @ memberStaticLs - let addMembersAsWithEnd reprL = - if isNil memberLs then reprL - else - let memberLs = applyMaxMembers denv.maxMembers memberLs - if simplified then reprL @@-- aboveListL memberLs - else reprL @@ (WordL.keywordWith @@-- aboveListL memberLs) @@ WordL.keywordEnd - - let reprL = - let repr = tycon.TypeReprInfo - match repr with - | TRecdRepr _ - | TUnionRepr _ - | TFSharpObjectRepr _ - | TAsmRepr _ - | TMeasureableRepr _ - | TILObjectRepr _ -> - let brk = not (isNil memberLs) || breakTypeDefnEqn repr - let rhsL = - let addReprAccessL l = layoutAccessibility denv tycon.TypeReprAccessibility l - let denv = denv.AddAccessibility tycon.TypeReprAccessibility - match repr with - | TRecdRepr _ -> - let recdFieldRefL fld = layoutRecdField false denv fld - - let recdL = - tycon.TrueFieldsAsList - |> List.map recdFieldRefL - |> applyMaxMembers denv.maxMembers - |> aboveListL - |> braceL - - Some (addMembersAsWithEnd (addReprAccessL recdL)) - - | TFSharpObjectRepr r -> - match r.fsobjmodel_kind with - | TTyconDelegate (TSlotSig(_, _, _, _, paraml, rty)) -> - let rty = GetFSharpViewOfReturnType denv.g rty - Some (WordL.keywordDelegate ^^ WordL.keywordOf --- layoutTopType denv SimplifyTypes.typeSimplificationInfo0 (paraml |> List.mapSquared (fun sp -> (sp.Type, ValReprInfo.unnamedTopArg1))) rty []) - | _ -> - match r.fsobjmodel_kind with - | TTyconEnum -> - tycon.TrueFieldsAsList - |> List.map (fun f -> - match f.LiteralValue with - | None -> emptyL - | Some c -> WordL.bar ^^ - wordL (tagField f.Name) ^^ - WordL.equals ^^ - layoutConst denv.g ty c) - |> aboveListL - |> Some - | _ -> - let inherits = - match r.fsobjmodel_kind, tycon.TypeContents.tcaug_super with - | TTyconClass, Some super -> [wordL (tagKeyword "inherit") ^^ (layoutType denv super)] - | TTyconInterface, _ -> - tycon.ImmediateInterfacesOfFSharpTycon - |> List.filter (fun (_, compgen, _) -> not compgen) - |> List.map (fun (ity, _, _) -> wordL (tagKeyword "inherit") ^^ (layoutType denv ity)) - | _ -> [] - let vsprs = - tycon.MembersOfFSharpTyconSorted - |> List.filter (fun v -> isNil (Option.get v.MemberInfo).ImplementedSlotSigs && v.IsDispatchSlot) - |> List.map (fun vref -> PrintTastMemberOrVals.prettyLayoutOfValOrMemberNoInst denv vref.Deref) - let staticValsLs = - tycon.TrueFieldsAsList - |> List.filter (fun f -> f.IsStatic) - |> List.map (fun f -> WordL.keywordStatic ^^ WordL.keywordVal ^^ layoutRecdField true denv f) - let instanceValsLs = - tycon.TrueFieldsAsList - |> List.filter (fun f -> not f.IsStatic) - |> List.map (fun f -> WordL.keywordVal ^^ layoutRecdField true denv f) - let allDecls = inherits @ memberImplementLs @ memberCtorLs @ instanceValsLs @ vsprs @ memberInstanceLs @ staticValsLs @ memberStaticLs - if isNil allDecls then - None - else - let allDecls = applyMaxMembers denv.maxMembers allDecls - let emptyMeasure = match tycon.TypeOrMeasureKind with TyparKind.Measure -> isNil allDecls | _ -> false - if emptyMeasure then None else - let declsL = aboveListL allDecls - let declsL = match start with Some s -> (wordL s @@-- declsL) @@ wordL (tagKeyword "end") | None -> declsL - Some declsL - | TUnionRepr _ -> - let layoutUnionCases = tycon.UnionCasesAsList |> layoutUnionCases denv |> applyMaxMembers denv.maxMembers |> aboveListL - Some (addMembersAsWithEnd (addReprAccessL layoutUnionCases)) - - | TAsmRepr _ -> - Some (wordL (tagText "(# \"\" #)")) - - | TMeasureableRepr ty -> - Some (layoutType denv ty) - - | TILObjectRepr _ -> - let td = tycon.ILTyconRawMetadata - Some (PrintIL.layoutILTypeDef denv td) - | _ -> None - - let brk = match tycon.TypeReprInfo with | TILObjectRepr _ -> true | _ -> brk - match rhsL with - | None -> lhsL - | Some rhsL -> - if brk then - (lhsL ^^ WordL.equals) @@-- rhsL - else - (lhsL ^^ WordL.equals) --- rhsL - - | _ -> - match tycon.TypeAbbrev with - | None -> - addMembersAsWithEnd (lhsL ^^ WordL.equals) - | Some a -> - (lhsL ^^ WordL.equals) --- (layoutType { denv with shortTypeNames = false } a) - - layoutAttribs denv false ty tycon.TypeOrMeasureKind tycon.Attribs reprL // Layout: exception definition let layoutExnDefn denv (exnc: Entity) = @@ -2011,7 +1772,6 @@ module private TastDefinitionPrinting = let xs = List.map (layoutTycon denv infoReader ad m false (wordL (tagKeyword "and"))) t aboveListL (x :: xs) - //-------------------------------------------------------------------------- module private InferredSigPrinting = @@ -2199,10 +1959,6 @@ let stringOfParamData denv paramData = bufs (fun buf -> InfoMemberPrinting.forma let layoutOfParamData denv paramData = InfoMemberPrinting.layoutParamData denv paramData -let outputILTypeRef denv os x = x |> PrintIL.layoutILTypeRef denv |> bufferL os - -let layoutILTypeRef denv x = x |> PrintIL.layoutILTypeRef denv - let outputExnDef denv os x = x |> TastDefinitionPrinting.layoutExnDefn denv |> bufferL os let layoutExnDef denv x = x |> TastDefinitionPrinting.layoutExnDefn denv diff --git a/src/fsharp/TcGlobals.fs b/src/fsharp/TcGlobals.fs index b275bc8188d..c56be3d5bbd 100755 --- a/src/fsharp/TcGlobals.fs +++ b/src/fsharp/TcGlobals.fs @@ -1099,6 +1099,7 @@ type public TcGlobals(compilingFslib: bool, ilg:ILGlobals, fslibCcu: CcuThunk, d member val system_Array_tcref = findSysTyconRef sys "Array" member val system_Object_tcref = findSysTyconRef sys "Object" + member val system_Value_tcref = findSysTyconRef sys "ValueType" member val system_Void_tcref = findSysTyconRef sys "Void" member val system_IndexOutOfRangeException_tcref = findSysTyconRef sys "IndexOutOfRangeException" member val system_Nullable_tcref = v_nullable_tcr diff --git a/src/fsharp/TypedTreeOps.fs b/src/fsharp/TypedTreeOps.fs index 8ce4839b3da..4508a42500b 100644 --- a/src/fsharp/TypedTreeOps.fs +++ b/src/fsharp/TypedTreeOps.fs @@ -1665,6 +1665,7 @@ let isArrayTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> isA let isArray1DTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> tyconRefEq g tcref g.il_arr_tcr_map.[0] | _ -> false) let isUnitTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> tyconRefEq g g.unit_tcr_canon tcref | _ -> false) let isObjTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> tyconRefEq g g.system_Object_tcref tcref | _ -> false) +let isValueTypeTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> tyconRefEq g g.system_Value_tcref tcref | _ -> false) let isVoidTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> tyconRefEq g g.system_Void_tcref tcref | _ -> false) let isILAppTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> tcref.IsILTycon | _ -> false) let isNativePtrTy g ty = ty |> stripTyEqns g |> (function TType_app(tcref, _) -> tyconRefEq g g.nativeptr_tcr tcref | _ -> false) @@ -1825,6 +1826,10 @@ let isRefTy g ty = (isAnonRecdTy g ty && not (isStructAnonRecdTy g ty)) ) +let isForallFunctionTy g ty = + let _, tau = tryDestForallTy g ty + isFunTy g tau + // ECMA C# LANGUAGE SPECIFICATION, 27.2 // An unmanaged-type is any type that isn't a reference-type, a type-parameter, or a generic struct-type and // contains no fields whose type is not an unmanaged-type. In other words, an unmanaged-type is one of the @@ -2745,6 +2750,8 @@ type DisplayEnv = showConstraintTyparAnnotations: bool abbreviateAdditionalConstraints: bool showTyparDefaultConstraints: bool + shrinkOverloads: bool + printVerboseSignatures : bool g: TcGlobals contextAccessibility: Accessibility generatedValueLayout : (Val -> layout option) } @@ -2776,6 +2783,8 @@ type DisplayEnv = showTyparDefaultConstraints = false shortConstraints = false useColonForReturnType = false + shrinkOverloads = true + printVerboseSignatures = false g = tcGlobals contextAccessibility = taccessPublic generatedValueLayout = (fun _ -> None) } @@ -2844,7 +2853,7 @@ let tagEntityRefName (xref: EntityRef) name = elif xref.IsFSharpDelegateTycon then tagDelegate name elif xref.IsILEnumTycon || xref.IsFSharpEnumTycon then tagEnum name elif xref.IsStructOrEnumTycon then tagStruct name - elif xref.IsFSharpInterfaceTycon then tagInterface name + elif isInterfaceTyconRef xref then tagInterface name elif xref.IsUnionTycon then tagUnion name elif xref.IsRecordTycon then tagRecord name else tagClass name diff --git a/src/fsharp/TypedTreeOps.fsi b/src/fsharp/TypedTreeOps.fsi index c209ace4ec6..8554c006b76 100755 --- a/src/fsharp/TypedTreeOps.fsi +++ b/src/fsharp/TypedTreeOps.fsi @@ -979,6 +979,8 @@ type DisplayEnv = showConstraintTyparAnnotations:bool abbreviateAdditionalConstraints: bool showTyparDefaultConstraints: bool + shrinkOverloads: bool + printVerboseSignatures : bool g: TcGlobals contextAccessibility: Accessibility generatedValueLayout:(Val -> layout option) } @@ -1506,6 +1508,9 @@ val isUnitTy : TcGlobals -> TType -> bool /// Determine if a type is the System.Object type val isObjTy : TcGlobals -> TType -> bool +/// Determine if a type is the System.ValueType type +val isValueTypeTy : TcGlobals -> TType -> bool + /// Determine if a type is the System.Void type val isVoidTy : TcGlobals -> TType -> bool @@ -1527,6 +1532,9 @@ val isInterfaceTy : TcGlobals -> TType -> bool /// Determine if a type is a FSharpRef type val isRefTy : TcGlobals -> TType -> bool +/// Determine if a type is a function (including generic). Not the same as isFunTy. +val isForallFunctionTy : TcGlobals -> TType -> bool + /// Determine if a type is a sealed type val isSealedTy : TcGlobals -> TType -> bool diff --git a/src/fsharp/fsc.fs b/src/fsharp/fsc.fs index 0c2f50d04eb..693271a5dd8 100644 --- a/src/fsharp/fsc.fs +++ b/src/fsharp/fsc.fs @@ -333,7 +333,7 @@ module InterfaceFileWriter = for (TImplFile (_, _, mexpr, _, _, _)) in declaredImpls do let denv = BuildInitialDisplayEnvForSigFileGeneration tcGlobals writeViaBuffer os (fun os s -> Printf.bprintf os "%s\n\n" s) - (NicePrint.layoutInferredSigOfModuleExpr true denv infoReader AccessibleFromSomewhere range0 mexpr |> Display.squashTo 80 |> Layout.showL) + (NicePrint.layoutInferredSigOfModuleExpr true { denv with shrinkOverloads = false; printVerboseSignatures = true } infoReader AccessibleFromSomewhere range0 mexpr |> Display.squashTo 80 |> Layout.showL) if tcConfig.printSignatureFile <> "" then os.Dispose() diff --git a/src/fsharp/layout.fs b/src/fsharp/layout.fs index 22c92e56acf..d0aaab9bae9 100644 --- a/src/fsharp/layout.fs +++ b/src/fsharp/layout.fs @@ -62,6 +62,7 @@ module TaggedTextOps = let tagMember = TaggedTextOps.mkTag LayoutTag.Member let tagModule = TaggedTextOps.tagModule let tagModuleBinding = TaggedTextOps.tagModuleBinding + let tagFunction = TaggedTextOps.tagFunction let tagNamespace = TaggedTextOps.tagNamespace let tagNumericLiteral = TaggedTextOps.tagNumericLiteral let tagOperator = TaggedTextOps.tagOperator diff --git a/src/fsharp/layout.fsi b/src/fsharp/layout.fsi index 95f81f6cf83..b7aa6320b3d 100644 --- a/src/fsharp/layout.fsi +++ b/src/fsharp/layout.fsi @@ -103,6 +103,7 @@ module TaggedTextOps = val tagRecordField : (string -> TaggedText) val tagModule : (string -> TaggedText) val tagModuleBinding : (string -> TaggedText) + val tagFunction : (string -> TaggedText) val tagMember : (string -> TaggedText) val tagNamespace : (string -> TaggedText) val tagNumericLiteral : (string -> TaggedText) diff --git a/src/fsharp/service/SemanticClassification.fs b/src/fsharp/service/SemanticClassification.fs index 4159ed8cd7d..89db4acada0 100644 --- a/src/fsharp/service/SemanticClassification.fs +++ b/src/fsharp/service/SemanticClassification.fs @@ -16,7 +16,6 @@ open FSharp.Compiler.Range open FSharp.Compiler.TcGlobals open FSharp.Compiler.TypedTree open FSharp.Compiler.TypedTreeOps -open FSharp.Compiler.SourceCodeServices.SymbolHelpers [] type SemanticClassificationType = @@ -165,7 +164,7 @@ module TcResolutionsExtensions = | Item.Value KeywordIntrinsicValue, ItemOccurence.Use, _, _, _, m -> add m SemanticClassificationType.IntrinsicFunction - | (Item.Value vref), _, _, _, _, m when isFunction g vref.Type -> + | (Item.Value vref), _, _, _, _, m when isForallFunctionTy g vref.Type -> if isDiscard vref.DisplayName then add m SemanticClassificationType.Plaintext elif valRefEq g g.range_op_vref vref || valRefEq g g.range_step_op_vref vref then @@ -295,7 +294,7 @@ module TcResolutionsExtensions = add m SemanticClassificationType.ValueType elif isRefTupleTy g ty then add m SemanticClassificationType.ReferenceType - elif isFunction g ty then + elif isForallFunctionTy g ty then add m SemanticClassificationType.Function elif isTyparTy g ty then add m SemanticClassificationType.ValueType diff --git a/src/fsharp/symbols/SymbolHelpers.fs b/src/fsharp/symbols/SymbolHelpers.fs index f7593d8e0b8..e8e1b067f68 100644 --- a/src/fsharp/symbols/SymbolHelpers.fs +++ b/src/fsharp/symbols/SymbolHelpers.fs @@ -317,11 +317,6 @@ type CompletionItem = [] module internal SymbolHelpers = - - let isFunction g ty = - let _, tau = tryDestForallTy g ty - isFunTy g tau - let OutputFullName isListItem ppF fnF r = // Only display full names in quick info, not declaration lists or method lists if not isListItem then @@ -904,7 +899,7 @@ module internal SymbolHelpers = | Item.AnonRecdField(anon, _argTys, i, _) -> anon.SortedNames.[i] | Item.RecdField rfinfo -> fullDisplayTextOfRecdFieldRef rfinfo.RecdFieldRef | Item.NewDef id -> id.idText - | Item.ILField finfo -> bufs (fun os -> NicePrint.outputILTypeRef denv os finfo.ILTypeRef; bprintf os ".%s" finfo.FieldName) + | Item.ILField finfo -> bufs (fun os -> NicePrint.outputType denv os finfo.ApparentEnclosingType; bprintf os ".%s" finfo.FieldName) | Item.Event einfo -> bufs (fun os -> NicePrint.outputTyconRef denv os einfo.DeclaringTyconRef; bprintf os ".%s" einfo.EventName) | Item.Property(_, (pinfo :: _)) -> bufs (fun os -> NicePrint.outputTyconRef denv os pinfo.DeclaringTyconRef; bprintf os ".%s" pinfo.PropertyName) | Item.CustomOperation (customOpName, _, _) -> customOpName @@ -1141,7 +1136,7 @@ module internal SymbolHelpers = | Item.ILField finfo -> let layout = wordL (tagText (FSComp.SR.typeInfoField())) ^^ - NicePrint.layoutILTypeRef denv finfo.ILTypeRef ^^ + NicePrint.layoutType denv finfo.ApparentEnclosingAppType ^^ SepL.dot ^^ wordL (tagField finfo.FieldName) ^^ RightL.colon ^^ @@ -1528,8 +1523,8 @@ module internal SymbolHelpers = | Item.NewDef _ | Item.ILField _ -> [] | Item.Event _ -> [] - | Item.RecdField rfinfo -> if isFunction g rfinfo.FieldType then [item] else [] - | Item.Value v -> if isFunction g v.Type then [item] else [] + | Item.RecdField rfinfo -> if isForallFunctionTy g rfinfo.FieldType then [item] else [] + | Item.Value v -> if isForallFunctionTy g v.Type then [item] else [] | Item.UnionCase(ucr, _) -> if not ucr.UnionCase.IsNullary then [item] else [] | Item.ExnCase ecr -> if isNil (recdFieldsOfExnDefRef ecr) then [] else [item] | Item.Property(_, pinfos) -> diff --git a/src/fsharp/symbols/SymbolHelpers.fsi b/src/fsharp/symbols/SymbolHelpers.fsi index f5f345e4ef2..20e2a810276 100755 --- a/src/fsharp/symbols/SymbolHelpers.fsi +++ b/src/fsharp/symbols/SymbolHelpers.fsi @@ -156,10 +156,7 @@ module public Tooltips = val Map: f: ('T1 -> 'T2) -> a: Async<'T1> -> Async<'T2> // Implementation details used by other code in the compiler -module internal SymbolHelpers = - - val isFunction : TcGlobals -> TType -> bool - +module internal SymbolHelpers = val ParamNameAndTypesOfUnaryCustomOperation : TcGlobals -> MethInfo -> ParamNameAndType list val GetXmlDocSigOfEntityRef : InfoReader -> range -> EntityRef -> (string option * string) option diff --git a/src/fsharp/symbols/Symbols.fs b/src/fsharp/symbols/Symbols.fs index 59b36bcc0d4..b9959dcbb00 100644 --- a/src/fsharp/symbols/Symbols.fs +++ b/src/fsharp/symbols/Symbols.fs @@ -2059,7 +2059,7 @@ type FSharpMemberOrFunctionOrValue(cenv, d:FSharpMemberOrValData, item) = member x.IsValue = match d with - | V valRef -> not (SymbolHelpers.isFunction cenv.g valRef.Type) + | V valRef -> not (isForallFunctionTy cenv.g valRef.Type) | _ -> false override x.Equals(other: obj) = diff --git a/src/fsharp/utils/sformat.fs b/src/fsharp/utils/sformat.fs index f2192b869a3..50c21b48a07 100644 --- a/src/fsharp/utils/sformat.fs +++ b/src/fsharp/utils/sformat.fs @@ -51,6 +51,7 @@ type LayoutTag = | Method | Member | ModuleBinding + | Function | Module | Namespace | NumericLiteral @@ -124,40 +125,38 @@ module TaggedTextOps = let toText (tt: TaggedText) = tt.Text let tagAlias t = mkTag LayoutTag.Alias t - let keywordFunctions = Set ["raise"; "reraise"; "typeof"; "typedefof"; "sizeof"; "nameof"] - let keywordTypes = + let keywordFunctions = [ - "array" - "bigint" - "bool" - "byref" - "byte" - "char" - "decimal" - "double" - "float" - "float32" - "int" - "int8" - "int16" - "int32" - "int64" - "list" - "nativeint" - "obj" - "sbyte" - "seq" - "single" - "string" - "unit" - "uint" - "uint8" - "uint16" - "uint32" - "uint64" - "unativeint" - ] |> Set.ofList - let tagClass name = if Set.contains name keywordTypes then mkTag LayoutTag.Keyword name else mkTag LayoutTag.Class name + "raise" + "reraise" + "typeof" + "typedefof" + "sizeof" + "nameof" + "char" + "decimal" + "double" + "float" + "float32" + "int" + "int8" + "int16" + "int32" + "int64" + "sbyte" + "seq" // 'seq x' when 'x' is a string works, strangely enough + "single" + "string" + "unit" + "uint" + "uint8" + "uint16" + "uint32" + "uint64" + "unativeint" + ] + |> Set.ofList + let tagClass name = mkTag LayoutTag.Class name let tagUnionCase t = mkTag LayoutTag.UnionCase t let tagDelegate t = mkTag LayoutTag.Delegate t let tagEnum t = mkTag LayoutTag.Enum t @@ -172,6 +171,7 @@ module TaggedTextOps = let tagMethod t = mkTag LayoutTag.Method t let tagModule t = mkTag LayoutTag.Module t let tagModuleBinding name = if keywordFunctions.Contains name then mkTag LayoutTag.Keyword name else mkTag LayoutTag.ModuleBinding name + let tagFunction t = mkTag LayoutTag.Function t let tagNamespace t = mkTag LayoutTag.Namespace t let tagNumericLiteral t = mkTag LayoutTag.NumericLiteral t let tagOperator t = mkTag LayoutTag.Operator t diff --git a/src/fsharp/utils/sformat.fsi b/src/fsharp/utils/sformat.fsi index 9af6458f979..6ef3ff8fcd6 100644 --- a/src/fsharp/utils/sformat.fsi +++ b/src/fsharp/utils/sformat.fsi @@ -70,6 +70,7 @@ namespace Microsoft.FSharp.Text.StructuredPrintfImpl | Method | Member | ModuleBinding + | Function | Module | Namespace | NumericLiteral @@ -125,6 +126,7 @@ namespace Microsoft.FSharp.Text.StructuredPrintfImpl val tagLineBreak: string -> TaggedText val tagMethod: string -> TaggedText val tagModuleBinding: string -> TaggedText + val tagFunction : string -> TaggedText val tagLocal: string -> TaggedText val tagRecord: string -> TaggedText val tagRecordField: string -> TaggedText diff --git a/tests/FSharp.Compiler.Service.Tests/SurfaceArea.netstandard.fs b/tests/FSharp.Compiler.Service.Tests/SurfaceArea.netstandard.fs index c409ba5c82a..d9590f3c95b 100644 --- a/tests/FSharp.Compiler.Service.Tests/SurfaceArea.netstandard.fs +++ b/tests/FSharp.Compiler.Service.Tests/SurfaceArea.netstandard.fs @@ -19330,6 +19330,7 @@ FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System. FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] get_tagMethod() FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] get_tagModule() FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] get_tagModuleBinding() +FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] get_tagFunction() FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] get_tagNamespace() FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] get_tagNumericLiteral() FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] get_tagOperator() @@ -19363,6 +19364,7 @@ FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System. FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] tagMethod FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] tagModule FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] tagModuleBinding +FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] tagFunction FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] tagNamespace FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] tagNumericLiteral FSharp.Compiler.Layout+TaggedTextOps: Microsoft.FSharp.Core.FSharpFunc`2[System.String,Internal.Utilities.StructuredFormat.TaggedText] tagOperator @@ -42194,6 +42196,7 @@ Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 Member Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 Method Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 Module Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 ModuleBinding +Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 Function Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 Namespace Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 NumericLiteral Internal.Utilities.StructuredFormat.LayoutTag+Tags: Int32 Operator @@ -42230,6 +42233,7 @@ Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsMember Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsMethod Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsModule Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsModuleBinding +Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsFunction Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsNamespace Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsNumericLiteral Internal.Utilities.StructuredFormat.LayoutTag: Boolean IsOperator @@ -42263,6 +42267,7 @@ Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsMember() Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsMethod() Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsModule() Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsModuleBinding() +Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsFunction() Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsNamespace() Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsNumericLiteral() Internal.Utilities.StructuredFormat.LayoutTag: Boolean get_IsOperator() @@ -42300,6 +42305,7 @@ Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredForm Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag Method Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag Module Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag ModuleBinding +Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag Function Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag Namespace Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag NumericLiteral Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag Operator @@ -42333,6 +42339,7 @@ Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredForm Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag get_Method() Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag get_Module() Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag get_ModuleBinding() +Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag get_Function() Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag get_Namespace() Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag get_NumericLiteral() Internal.Utilities.StructuredFormat.LayoutTag: Internal.Utilities.StructuredFormat.LayoutTag get_Operator() @@ -42400,6 +42407,7 @@ Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.Structured Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.StructuredFormat.TaggedText tagMethod(System.String) Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.StructuredFormat.TaggedText tagModule(System.String) Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.StructuredFormat.TaggedText tagModuleBinding(System.String) +Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.StructuredFormat.TaggedText tagFunction(System.String) Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.StructuredFormat.TaggedText tagNamespace(System.String) Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.StructuredFormat.TaggedText tagNumericLiteral(System.String) Internal.Utilities.StructuredFormat.TaggedTextOps: Internal.Utilities.StructuredFormat.TaggedText tagOperator(System.String) diff --git a/tests/fsharp/.vscode/settings.json b/tests/fsharp/.vscode/settings.json new file mode 100644 index 00000000000..67c22405bad --- /dev/null +++ b/tests/fsharp/.vscode/settings.json @@ -0,0 +1,3 @@ +{ + "FSharp.suggestGitignore": false +} \ No newline at end of file diff --git a/tests/fsharp/core/printing/z.output.test.1000.stdout.47.bsl b/tests/fsharp/core/printing/z.output.test.1000.stdout.47.bsl index c57d3604170..dd72a02e9d9 100644 --- a/tests/fsharp/core/printing/z.output.test.1000.stdout.47.bsl +++ b/tests/fsharp/core/printing/z.output.test.1000.stdout.47.bsl @@ -217,13 +217,11 @@ val sxs0 : Set = set [] "90"; "91"; "92"; "93"; "94"; "95"; "96"; ...], ..., ...)) end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref = { contents = "value" } @@ -870,10 +868,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C = val csA : C [] = [|; ; @@ -1064,35 +1060,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 = AT4063 null > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -1147,9 +1133,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -1182,9 +1166,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -1193,17 +1175,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -1370,38 +1346,23 @@ val x1564_A2 : int = 2 val x1564_A3 : int = 3 > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int = 1 type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -1409,9 +1370,7 @@ val x1564_A3 : int = 3 { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -1434,22 +1393,15 @@ val x1564_A3 : int = 3 private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int = 1 type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -1457,9 +1409,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -1482,9 +1432,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -1537,37 +1485,29 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) @@ -1576,53 +1516,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -1672,129 +1601,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 = FSI_0107+Regression4469 val it : unit = () @@ -2558,76 +2449,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -2637,10 +2504,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -2680,40 +2545,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharp/core/printing/z.output.test.1000.stdout.50.bsl b/tests/fsharp/core/printing/z.output.test.1000.stdout.50.bsl index d08359162f3..08ac7c4ac0e 100644 --- a/tests/fsharp/core/printing/z.output.test.1000.stdout.50.bsl +++ b/tests/fsharp/core/printing/z.output.test.1000.stdout.50.bsl @@ -217,13 +217,11 @@ val sxs0 : Set = set [] "90"; "91"; "92"; "93"; "94"; "95"; "96"; ...], ..., ...)) end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref = { contents = "value" } @@ -870,10 +868,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C = val csA : C [] = [|; ; @@ -1064,35 +1060,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 = AT4063 null > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -1149,9 +1135,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -1184,9 +1168,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -1195,17 +1177,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -1372,38 +1348,23 @@ val x1564_A2 : int = 2 val x1564_A3 : int = 3 > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int = 1 type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -1411,9 +1372,7 @@ val x1564_A3 : int = 3 { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -1436,22 +1395,15 @@ val x1564_A3 : int = 3 private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int = 1 type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -1459,9 +1411,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -1484,9 +1434,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -1539,37 +1487,29 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) @@ -1578,53 +1518,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -1674,129 +1603,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 = FSI_0107+Regression4469 val it : unit = () @@ -2560,76 +2451,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -2639,10 +2506,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -2682,40 +2547,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharp/core/printing/z.output.test.200.stdout.47.bsl b/tests/fsharp/core/printing/z.output.test.200.stdout.47.bsl index b169a6c9e6f..1a50269bac9 100644 --- a/tests/fsharp/core/printing/z.output.test.200.stdout.47.bsl +++ b/tests/fsharp/core/printing/z.output.test.200.stdout.47.bsl @@ -112,13 +112,11 @@ val sxs0 : Set = set [] "13"; "14"; "15"; "16"; ...], ..., ...)) end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref = { contents = "value" } @@ -310,10 +308,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C = val csA : C [] = [|; ; @@ -384,35 +380,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 = AT4063 null > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -467,9 +453,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -502,9 +486,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -513,17 +495,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -615,38 +591,23 @@ val x1564_A2 : int = 2 val x1564_A3 : int = 3 > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int = 1 type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -654,9 +615,7 @@ val x1564_A3 : int = 3 { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -679,22 +638,15 @@ val x1564_A3 : int = 3 private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int = 1 type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -702,9 +654,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -727,9 +677,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -782,37 +730,29 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) @@ -821,53 +761,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -917,129 +846,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 = FSI_0107+Regression4469 val it : unit = () @@ -1803,76 +1694,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -1882,10 +1749,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -1925,40 +1790,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharp/core/printing/z.output.test.200.stdout.50.bsl b/tests/fsharp/core/printing/z.output.test.200.stdout.50.bsl index 9a31c467346..410c07644ca 100644 --- a/tests/fsharp/core/printing/z.output.test.200.stdout.50.bsl +++ b/tests/fsharp/core/printing/z.output.test.200.stdout.50.bsl @@ -112,13 +112,11 @@ val sxs0 : Set = set [] "13"; "14"; "15"; "16"; ...], ..., ...)) end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref = { contents = "value" } @@ -310,10 +308,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C = val csA : C [] = [|; ; @@ -384,35 +380,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 = AT4063 null > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -469,9 +455,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -504,9 +488,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -515,17 +497,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -617,38 +593,23 @@ val x1564_A2 : int = 2 val x1564_A3 : int = 3 > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int = 1 type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -656,9 +617,7 @@ val x1564_A3 : int = 3 { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -681,22 +640,15 @@ val x1564_A3 : int = 3 private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int = 1 type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -704,9 +656,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -729,9 +679,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -784,37 +732,29 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list = (FSI_0091+Test4343e+C, FSI_0091+Test4343e+C, [FSI_0091+Test4343e+C; FSI_0091+Test4343e+C]) type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) @@ -823,53 +763,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -919,129 +848,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 = FSI_0107+Regression4469 val it : unit = () @@ -1805,76 +1696,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -1884,10 +1751,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -1927,40 +1792,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharp/core/printing/z.output.test.default.stdout.47.bsl b/tests/fsharp/core/printing/z.output.test.default.stdout.47.bsl index 487ce5a7190..4df4b39469e 100644 --- a/tests/fsharp/core/printing/z.output.test.default.stdout.47.bsl +++ b/tests/fsharp/core/printing/z.output.test.default.stdout.47.bsl @@ -232,13 +232,11 @@ val sxs0 : Set = set [] ["70"; "71"; "72"; "73"; "74"; "75"; "76"; "77"]])) end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref = { contents = "value" } @@ -3829,10 +3827,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C = val csA : C [] = [|; ; @@ -4023,35 +4019,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 = AT4063 null > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -4106,9 +4092,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -4141,9 +4125,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -4152,17 +4134,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -4917,38 +4893,23 @@ val x1564_A2 : int = 2 val x1564_A3 : int = 3 > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int = 1 type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -4956,9 +4917,7 @@ val x1564_A3 : int = 3 { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -4981,22 +4940,15 @@ val x1564_A3 : int = 3 private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int = 1 type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -5004,9 +4956,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -5029,9 +4979,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -5084,37 +5032,29 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list = (FSI_0090+Test4343e+C, FSI_0090+Test4343e+C, [FSI_0090+Test4343e+C; FSI_0090+Test4343e+C]) type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list = (FSI_0090+Test4343e+C, FSI_0090+Test4343e+C, [FSI_0090+Test4343e+C; FSI_0090+Test4343e+C]) type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) @@ -5123,53 +5063,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -5219,129 +5148,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 = FSI_0106+Regression4469 val it : unit = () @@ -6105,76 +5996,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -6184,10 +6051,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -6227,40 +6092,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharp/core/printing/z.output.test.default.stdout.50.bsl b/tests/fsharp/core/printing/z.output.test.default.stdout.50.bsl index 5dea2230f51..7d0f21ca77b 100644 --- a/tests/fsharp/core/printing/z.output.test.default.stdout.50.bsl +++ b/tests/fsharp/core/printing/z.output.test.default.stdout.50.bsl @@ -232,13 +232,11 @@ val sxs0 : Set = set [] ["70"; "71"; "72"; "73"; "74"; "75"; "76"; "77"]])) end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref = { contents = "value" } @@ -3829,10 +3827,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C = val csA : C [] = [|; ; @@ -4023,35 +4019,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 = AT4063 null > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -4108,9 +4094,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -4143,9 +4127,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -4154,17 +4136,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -4919,38 +4895,23 @@ val x1564_A2 : int = 2 val x1564_A3 : int = 3 > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int = 1 type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -4958,9 +4919,7 @@ val x1564_A3 : int = 3 { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -4983,22 +4942,15 @@ val x1564_A3 : int = 3 private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int = 1 type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -5006,9 +4958,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -5031,9 +4981,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -5086,37 +5034,29 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list = (FSI_0090+Test4343e+C, FSI_0090+Test4343e+C, [FSI_0090+Test4343e+C; FSI_0090+Test4343e+C]) type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list = (FSI_0090+Test4343e+C, FSI_0090+Test4343e+C, [FSI_0090+Test4343e+C; FSI_0090+Test4343e+C]) type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D = D(1) val dB : D = D(2) val dAB : D * D * D list = (D(1), D(2), [D(1); D(2)]) @@ -5125,53 +5065,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -5221,129 +5150,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 = FSI_0106+Regression4469 val it : unit = () @@ -6107,76 +5998,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -6186,10 +6053,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -6229,40 +6094,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharp/core/printing/z.output.test.off.stdout.47.bsl b/tests/fsharp/core/printing/z.output.test.off.stdout.47.bsl index cd109a34b67..5e4d80425d7 100644 --- a/tests/fsharp/core/printing/z.output.test.off.stdout.47.bsl +++ b/tests/fsharp/core/printing/z.output.test.off.stdout.47.bsl @@ -77,13 +77,11 @@ val sxs0 : Set (string list * string list * string [,]) option end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref @@ -167,10 +165,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C val csA : C [] val csB : C [] @@ -211,35 +207,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -294,9 +280,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -329,9 +313,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -340,17 +322,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -415,38 +391,23 @@ val x1564_A2 : int val x1564_A3 : int > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -454,9 +415,7 @@ val x1564_A3 : int { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -479,22 +438,15 @@ val x1564_A3 : int private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -502,9 +454,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -527,9 +477,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -572,33 +520,25 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D val dB : D val dAB : D * D * D list module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D val dB : D val dAB : D * D * D list @@ -607,53 +547,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -689,129 +618,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 val it : unit @@ -1573,76 +1464,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -1652,10 +1519,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -1695,40 +1560,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharp/core/printing/z.output.test.off.stdout.50.bsl b/tests/fsharp/core/printing/z.output.test.off.stdout.50.bsl index e3c5dbfc970..b1fd18978b7 100644 --- a/tests/fsharp/core/printing/z.output.test.off.stdout.50.bsl +++ b/tests/fsharp/core/printing/z.output.test.off.stdout.50.bsl @@ -77,13 +77,11 @@ val sxs0 : Set (string list * string list * string [,]) option end type T = - class - new : a:int * b:int -> T - member AMethod : x:int -> int - member AProperty : int - static member StaticMethod : x:int -> int - static member StaticProperty : int - end + new : a:int * b:int -> T + member AMethod : x:int -> int + static member StaticMethod : x:int -> int + member AProperty : int + static member StaticProperty : int val f_as_method : x:int -> int val f_as_thunk : (int -> int) val refCell : string ref @@ -167,10 +165,8 @@ val generate : x:int -> X end > type C = - class - new : x:string -> C - override ToString : unit -> string - end + new : x:string -> C + override ToString : unit -> string val c1 : C val csA : C [] val csB : C [] @@ -211,35 +207,25 @@ type 'a T4063 = | AT4063 of 'a > val valAT3063_null : System.Object T4063 > type M4063<'a> = - class - new : x:'a -> M4063<'a> - end + new : x:'a -> M4063<'a> > val v4063 : M4063 > type Taaaaa<'a> = - class - new : unit -> Taaaaa<'a> - end + new : unit -> Taaaaa<'a> > type Taaaaa2<'a> = - class - inherit Taaaaa<'a> - new : unit -> Taaaaa2<'a> - member M : unit -> Taaaaa2<'a> - end + inherit Taaaaa<'a> + new : unit -> Taaaaa2<'a> + member M : unit -> Taaaaa2<'a> > type Tbbbbb<'a> = - class - new : x:'a -> Tbbbbb<'a> - member M : unit -> 'a - end + new : x:'a -> Tbbbbb<'a> + member M : unit -> 'a > type Tbbbbb2 = - class - inherit Tbbbbb - new : x:string -> Tbbbbb2 - end + inherit Tbbbbb + new : x:string -> Tbbbbb2 > val it : (unit -> string) = @@ -296,9 +282,7 @@ end > type internal T3 > type internal T4 = - class - new : unit -> T4 - end + new : unit -> T4 > type T1 = internal | A @@ -331,9 +315,7 @@ end > type private T3 > type private T4 = - class - new : unit -> T4 - end + new : unit -> T4 > exception X1 of int @@ -342,17 +324,11 @@ end > exception internal X3 of int > type T0 = - class - new : unit -> T0 - end + new : unit -> T0 type T1Post<'a> = - class - new : unit -> T1Post<'a> - end + new : unit -> T1Post<'a> type 'a T1Pre = - class - new : unit -> 'a T1Pre - end + new : unit -> 'a T1Pre > type T0 with member M : unit -> T0 list @@ -417,38 +393,23 @@ val x1564_A2 : int val x1564_A3 : int > type internal Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int > module internal InternalM = begin val x : int type Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - private new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member private Prop3 : int - end + private new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member private Prop3 : int type private Foo3 = - class - new : unit -> Foo3 - new : x:int -> Foo3 - new : x:int * y:int -> Foo3 - new : x:int * y:int * z:int -> Foo3 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo3 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -456,9 +417,7 @@ val x1564_A3 : int { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -481,22 +440,15 @@ val x1564_A3 : int private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end module internal PrivateM = begin val private x : int type private Foo2 = - class - new : unit -> Foo2 - new : x:int -> Foo2 - new : x:int * y:int -> Foo2 - new : x:int * y:int * z:int -> Foo2 - member Prop1 : int - member Prop2 : int - member Prop3 : int - end + new : x:int * y:int * z:int -> Foo2 + 3 overloads + member Prop1 : int + member Prop2 : int + member Prop3 : int type T1 = | A | B @@ -504,9 +456,7 @@ module internal PrivateM = begin { x: int } type T3 type T4 = - class - new : unit -> T4 - end + new : unit -> T4 type T5 = | A | B @@ -529,9 +479,7 @@ module internal PrivateM = begin private { x: int } type private T13 type private T14 = - class - new : unit -> T14 - end + new : unit -> T14 end > val it : seq = @@ -574,33 +522,25 @@ module Test4343d = begin end module Test4343e = begin type C = - class - new : x:int -> C - end + new : x:int -> C val cA : C val cB : C val cAB : C * C * C list type D = - class - new : x:int -> D - override ToString : unit -> string - end + new : x:int -> D + override ToString : unit -> string val dA : D val dB : D val dAB : D * D * D list module Generic = begin type CGeneric<'a> = - class - new : x:'a -> CGeneric<'a> - end + new : x:'a -> CGeneric<'a> val cA : C val cB : C val cAB : C * C * C list type D<'a> = - class - new : x:'a -> D<'a> - override ToString : unit -> string - end + new : x:'a -> D<'a> + override ToString : unit -> string val dA : D val dB : D val dAB : D * D * D list @@ -609,53 +549,42 @@ module Test4343e = begin end end type F1 = - class - inherit System.Windows.Forms.Form - interface System.IDisposable - val x: F1 - val x2: F1 - abstract member MMM : bool -> bool - abstract member AAA : int - abstract member ZZZ : int - abstract member BBB : bool with set - member B : unit -> int - member D : unit -> int - member D : x:int -> int - member D : x:int * y:int -> int - override ToString : unit -> string - member D2 : int - member E : int - member D2 : int with set - member E : int with set - static val mutable private sx: F1 - static val mutable private sx2: F1 - static member A : unit -> int - static member C : unit -> int - end + inherit System.Windows.Forms.Form + interface System.IDisposable + val x: F1 + val x2: F1 + member B : unit -> int + member D : x:int -> int + 2 overloads + abstract member MMM : bool -> bool + override ToString : unit -> string + static member A : unit -> int + static member C : unit -> int + abstract member AAA : int + abstract member BBB : bool with set + member D2 : int + member E : int + abstract member ZZZ : int + static val mutable private sx: F1 + static val mutable private sx2: F1 +[] type IP = - struct - new : x:int * y:int -> IP - static val mutable private AA: IP - end + new : x:int * y:int -> IP + static val mutable private AA: IP module Regression4643 = begin + [] type RIP = - struct - new : x:int -> RIP - static val mutable private y: RIP - end + new : x:int -> RIP + static val mutable private y: RIP + [] type arg_unused_is_RIP = - struct - new : x:RIP -> arg_unused_is_RIP - end + new : x:RIP -> arg_unused_is_RIP + [] type arg_used_is_RIP = - struct - new : x:RIP -> arg_used_is_RIP - member X : RIP - end + new : x:RIP -> arg_used_is_RIP + member X : RIP + [] type field_is_RIP = - struct - val x: RIP - end + val x: RIP end type Either<'a,'b> = | This of 'a @@ -691,129 +620,91 @@ end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3739 = begin type IB = - interface - abstract member AbstractMember : int -> int - end + abstract member AbstractMember : int -> int type C<'a when 'a :> IB> = - class - new : unit -> C<'a> - static member StaticMember : x:'a -> int - end + new : unit -> C<'a> + static member StaticMember : x:'a -> int end > module Regression3740 = begin type Writer<'a> = - interface - abstract member get_path : unit -> string - end + abstract member get_path : unit -> string type MyClass = - class - interface Writer - val path: string - end + interface Writer + val path: string end > type Regression4319_T2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> string > type Regression4319_T0 = - class - static member ( +-+-+ ) : string - end + static member ( +-+-+ ) : string > type Regression4319_T1 = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1b = - class - static member ( +-+-+ ) : x:'a -> string - end + static member ( +-+-+ ) : x:'a -> string > type Regression4319_T1c = - class - static member ( +-+-+ ) : x:('a * 'b) -> string - end + static member ( +-+-+ ) : x:('a * 'b) -> string > type Regression4319_T1d = - class - static member ( +-+-+ ) : x:(int * int) -> string - end + static member ( +-+-+ ) : x:(int * int) -> string > type Regression4319_T3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> string > type Regression4319_U1 = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U1b = - class - static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string - end + static member ( +-+-+ ) : x:'a -> moreArgs:'b -> string > type Regression4319_U2 = - class - static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string - end + static member ( +-+-+ ) : x:'a * y:'b -> moreArgs:'c -> string > type Regression4319_U3 = - class - static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string - end + static member ( +-+-+ ) : x:'a * y:'b * z:'c -> moreArgs:'d -> string > type Regression4319_check = - class - static member ( & ) : string - static member ( &^ ) : string - static member ( @ ) : string - static member ( != ) : string - static member ( := ) : string - static member ( ^ ) : string - static member ( / ) : string - static member ( $ ) : string - static member ( ...@ ) : string - static member ( ...!= ) : string - static member ( .../ ) : string - static member ( ...= ) : string - static member ( ...> ) : string - static member ( ...^ ) : string - static member ( ...< ) : string - static member ( ...* ) : string - static member ( ...% ) : string - static member ( = ) : string - static member ( ** ) : string - static member ( > ) : string - static member ( < ) : string - static member ( % ) : string - static member ( * ) : string - static member ( - ) : string - end + static member ( & ) : string + static member ( &^ ) : string + static member ( @ ) : string + static member ( != ) : string + static member ( := ) : string + static member ( ^ ) : string + static member ( / ) : string + static member ( $ ) : string + static member ( ...@ ) : string + static member ( ...!= ) : string + static member ( .../ ) : string + static member ( ...= ) : string + static member ( ...> ) : string + static member ( ...^ ) : string + static member ( ...< ) : string + static member ( ...* ) : string + static member ( ...% ) : string + static member ( = ) : string + static member ( ** ) : string + static member ( > ) : string + static member ( < ) : string + static member ( % ) : string + static member ( * ) : string + static member ( - ) : string > Expect ABC = ABC type Regression4469 = - class - new : unit -> Regression4469 - member ToString : unit -> string - end + new : unit -> Regression4469 + member ToString : unit -> string val r4469 : Regression4469 val it : unit @@ -1575,76 +1466,52 @@ val f : (unit -> int) > > module Regression5265_PriPri = begin type private IAPrivate = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPrivate - abstract member Q : int - end + inherit IAPrivate + abstract member Q : int end > val it : string = "NOTE: Expect IAInternal less accessible IBPublic" > > module Regression5265_IntInt = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_IntPri = begin type internal IAInternal = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAInternal - abstract member Q : int - end + inherit IAInternal + abstract member Q : int end > module Regression5265_PubPub = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type IBPublic = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubInt = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type internal IBInternal = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > module Regression5265_PubPri = begin type IAPublic = - interface - abstract member P : int - end + abstract member P : int type private IBPrivate = - interface - inherit IAPublic - abstract member Q : int - end + inherit IAPublic + abstract member Q : int end > val it : string = @@ -1654,10 +1521,8 @@ end "** Expect AnAxHostSubClass to be accepted. AxHost has a newslot virtual RightToLeft property outscope RightToLeft on Control" > type AnAxHostSubClass = - class - inherit System.Windows.Forms.AxHost - new : x:string -> AnAxHostSubClass - end + inherit System.Windows.Forms.AxHost + new : x:string -> AnAxHostSubClass > val it : string = "** Expect error because the active pattern result contains free type variables" @@ -1697,40 +1562,29 @@ end > > module ReflectionEmit = begin type IA = - interface - abstract member M : #IB -> int - end + abstract member M : #IB -> int and IB = - interface - abstract member M : #IA -> int - end + abstract member M : #IA -> int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = - interface - abstract member M : int - end + abstract member M : int and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = - interface - abstract member M : int - end + abstract member M : int end > val it : string = "Regression_139182: Expect the follow code to be accepted without error" -> type S = - struct - member TheMethod : unit -> int64 - end +> [] +type S = + member TheMethod : unit -> int64 val theMethod : s:S -> int64 type T = - class - new : unit -> T - member Prop5 : int64 - static member Prop1 : int64 - static member Prop2 : int64 - static member Prop3 : int64 - static member Prop4 : string - end + new : unit -> T + member Prop5 : int64 + static member Prop1 : int64 + static member Prop2 : int64 + static member Prop3 : int64 + static member Prop4 : string > val it : System.Threading.ThreadLocal list = [0 {IsValueCreated = false; Values = ?;}] diff --git a/tests/fsharpqa/Source/Conformance/DeclarationElements/MemberDefinitions/MethodsAndProperties/tupledValueProperties02.fsx b/tests/fsharpqa/Source/Conformance/DeclarationElements/MemberDefinitions/MethodsAndProperties/tupledValueProperties02.fsx index e791267da8f..4b6ce48dfb3 100644 --- a/tests/fsharpqa/Source/Conformance/DeclarationElements/MemberDefinitions/MethodsAndProperties/tupledValueProperties02.fsx +++ b/tests/fsharpqa/Source/Conformance/DeclarationElements/MemberDefinitions/MethodsAndProperties/tupledValueProperties02.fsx @@ -4,12 +4,10 @@ // Note: the non-curried syntax ((x:decimal, y:decimal)) is expected // Run thru fsi // type x = -// class -// new : unit -> x -// member Verify : int -// member X : decimal \* decimal with set -// member Y : decimal \* decimal with set -// end +// new : unit -> x +// member Verify : int +// member X : decimal \* decimal with set +// member Y : decimal \* decimal with set #light type x ()= class diff --git a/tests/fsharpqa/Source/InteractiveSession/Misc/DontShowCompilerGenNames01.fsx b/tests/fsharpqa/Source/InteractiveSession/Misc/DontShowCompilerGenNames01.fsx index 9b2bd981e96..07a5daef74d 100644 --- a/tests/fsharpqa/Source/InteractiveSession/Misc/DontShowCompilerGenNames01.fsx +++ b/tests/fsharpqa/Source/InteractiveSession/Misc/DontShowCompilerGenNames01.fsx @@ -3,7 +3,6 @@ // Regression test for FSHARP1.0:2549 // See also CL:14579 //type T = -//class //member M1 : x:int \* y:string -> \('a -> unit\) //member M2 : \(int \* string\) -> \('a -> unit\) //exception ExnType of int \* string diff --git a/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained01.fsx b/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained01.fsx index 430983dd657..6436c722ed8 100644 --- a/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained01.fsx +++ b/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained01.fsx @@ -3,13 +3,9 @@ // Interfaces cross-constrained via method gps //type IA = -// interface -// abstract member M : #IB -> int -// end +// abstract member M : #IB -> int //and IB = -// interface -// abstract member M : #IA -> int -// end +// abstract member M : #IA -> int type IA = abstract M : 'a -> int when 'a :> IB diff --git a/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained02.fsx b/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained02.fsx index 4b87394c7aa..a4fad849e49 100644 --- a/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained02.fsx +++ b/tests/fsharpqa/Source/InteractiveSession/Misc/InterfaceCrossConstrained02.fsx @@ -1,13 +1,9 @@ // #Regression #NoMT #FSI #RequiresENU // Regression test for DEV10#832789 //type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = -// interface -// abstract member M : int -// end +// abstract member M : int //and IB2<'b when 'b :> IA2<'b> and 'b :> IB2<'b>> = -// interface -// abstract member M : int -// end +// abstract member M : int type IA2<'a when 'a :> IB2<'a> and 'a :> IA2<'a>> = abstract M : int diff --git a/tests/fsharpqa/Source/InteractiveSession/Misc/ReflectionTypeNameMangling01.fsx b/tests/fsharpqa/Source/InteractiveSession/Misc/ReflectionTypeNameMangling01.fsx index f58e33aa758..728b9a696b1 100644 --- a/tests/fsharpqa/Source/InteractiveSession/Misc/ReflectionTypeNameMangling01.fsx +++ b/tests/fsharpqa/Source/InteractiveSession/Misc/ReflectionTypeNameMangling01.fsx @@ -13,18 +13,12 @@ // --------------\^\^\^\^\^\^\^\^\^\^\^\^\^\^ //Incomplete pattern matches on this expression\. For example, the value 'None' may indicate a case not covered by the pattern\(s\) //type Planet = -// class -// new : ipx:float \* ivx:float -> Planet -// member VX : float -// member X : float -// member VX : float with set -// member X : float with set -// end +// new : ipx:float \* ivx:float -> Planet +// member VX : float +// member X : float //val paintObjects : Planet list //type Simulator = -// class -// new : unit -> Simulator -// end +// new : unit -> Simulator type Planet(ipx:float,ivx:float) = diff --git a/tests/fsharpqa/Source/InteractiveSession/Misc/SubtypeArgInterfaceWithAbstractMember.fsx b/tests/fsharpqa/Source/InteractiveSession/Misc/SubtypeArgInterfaceWithAbstractMember.fsx index a824235dde4..60e90995809 100644 --- a/tests/fsharpqa/Source/InteractiveSession/Misc/SubtypeArgInterfaceWithAbstractMember.fsx +++ b/tests/fsharpqa/Source/InteractiveSession/Misc/SubtypeArgInterfaceWithAbstractMember.fsx @@ -2,14 +2,10 @@ // Regression test for FSHARP1.0:5825 //type I = -// interface -// abstract member m : unit -// end +// abstract member m : unit //type C = -// class -// interface I -// new : unit -> C -// end +// interface I +// new : unit -> C //val f : c:#C -> unit type I = diff --git a/tests/fsharpqa/Source/Printing/ParamArrayInSignatures.fsx b/tests/fsharpqa/Source/Printing/ParamArrayInSignatures.fsx index c68d6bbb8e2..671066a0709 100644 --- a/tests/fsharpqa/Source/Printing/ParamArrayInSignatures.fsx +++ b/tests/fsharpqa/Source/Printing/ParamArrayInSignatures.fsx @@ -3,9 +3,7 @@ // pretty printing signatures with params arguments //type Heterogeneous = -// class -// static member Echo : \[\] args:obj \[\] -> obj \[\] -// end +// static member Echo : \[\] args:obj \[\] -> obj \[\] type Heterogeneous = static member Echo([] args: obj[]) = args diff --git a/tests/fsharpqa/Source/Printing/SignatureWithOptionalArgs01.fs b/tests/fsharpqa/Source/Printing/SignatureWithOptionalArgs01.fs index 75dd10498ca..c336bc6a1ce 100644 --- a/tests/fsharpqa/Source/Printing/SignatureWithOptionalArgs01.fs +++ b/tests/fsharpqa/Source/Printing/SignatureWithOptionalArgs01.fs @@ -3,13 +3,10 @@ // pretty printing signatures with optional arguments //type AsyncTimer = -// class -// new : f:\(unit -> unit\) \* \?delay:int -> AsyncTimer -// member Start : unit -> unit -// member Stop : unit -> unit -// member Delay : int option -// member Delay : int option with set -// end +// new : f:\(unit -> unit\) \* \?delay:int -> AsyncTimer +// member Start : unit -> unit +// member Stop : unit -> unit +// member Delay : int option open Microsoft.FSharp.Control diff --git a/vsintegration/src/FSharp.Editor/Common/RoslynHelpers.fs b/vsintegration/src/FSharp.Editor/Common/RoslynHelpers.fs index c219d571550..6a905dbab35 100644 --- a/vsintegration/src/FSharp.Editor/Common/RoslynHelpers.fs +++ b/vsintegration/src/FSharp.Editor/Common/RoslynHelpers.fs @@ -51,39 +51,40 @@ module RoslynHelpers = /// maps from `LayoutTag` of the F# Compiler to Roslyn `TextTags` for use in tooltips let roslynTag = function - | LayoutTag.ActivePatternCase - | LayoutTag.ActivePatternResult - | LayoutTag.UnionCase - | LayoutTag.Enum -> TextTags.Enum - | LayoutTag.Alias - | LayoutTag.Class - | LayoutTag.Union - | LayoutTag.Record - | LayoutTag.UnknownType -> TextTags.Class - | LayoutTag.Delegate -> TextTags.Delegate - | LayoutTag.Event -> TextTags.Event - | LayoutTag.Field -> TextTags.Field - | LayoutTag.Interface -> TextTags.Interface - | LayoutTag.Struct -> TextTags.Struct - | LayoutTag.Keyword -> TextTags.Keyword - | LayoutTag.Local -> TextTags.Local - | LayoutTag.Member - | LayoutTag.ModuleBinding - | LayoutTag.RecordField - | LayoutTag.Property -> TextTags.Property - | LayoutTag.Method -> TextTags.Method - | LayoutTag.Namespace -> TextTags.Namespace - | LayoutTag.Module -> TextTags.Module - | LayoutTag.LineBreak -> TextTags.LineBreak - | LayoutTag.Space -> TextTags.Space - | LayoutTag.NumericLiteral -> TextTags.NumericLiteral - | LayoutTag.Operator -> TextTags.Operator - | LayoutTag.Parameter -> TextTags.Parameter - | LayoutTag.TypeParameter -> TextTags.TypeParameter - | LayoutTag.Punctuation -> TextTags.Punctuation - | LayoutTag.StringLiteral -> TextTags.StringLiteral - | LayoutTag.Text - | LayoutTag.UnknownEntity -> TextTags.Text + | LayoutTag.ActivePatternCase + | LayoutTag.ActivePatternResult + | LayoutTag.UnionCase + | LayoutTag.Enum -> TextTags.Enum + | LayoutTag.Struct -> TextTags.Struct + | LayoutTag.TypeParameter -> TextTags.TypeParameter + | LayoutTag.Alias + | LayoutTag.Class + | LayoutTag.Union + | LayoutTag.Record + | LayoutTag.UnknownType // Default to class until/unless we use classification data + | LayoutTag.Module -> TextTags.Class + | LayoutTag.Interface -> TextTags.Interface + | LayoutTag.Keyword -> TextTags.Keyword + | LayoutTag.Member + | LayoutTag.Function + | LayoutTag.Method -> TextTags.Method + | LayoutTag.RecordField + | LayoutTag.Property -> TextTags.Property + | LayoutTag.Parameter // parameter? + | LayoutTag.Local -> TextTags.Local + | LayoutTag.Namespace -> TextTags.Namespace + | LayoutTag.Delegate -> TextTags.Delegate + | LayoutTag.Event -> TextTags.Event + | LayoutTag.Field -> TextTags.Field + | LayoutTag.LineBreak -> TextTags.LineBreak + | LayoutTag.Space -> TextTags.Space + | LayoutTag.NumericLiteral -> TextTags.NumericLiteral + | LayoutTag.Operator -> TextTags.Operator + | LayoutTag.StringLiteral -> TextTags.StringLiteral + | LayoutTag.Punctuation -> TextTags.Punctuation + | LayoutTag.Text + | LayoutTag.ModuleBinding // why no 'Identifier'? Does it matter? + | LayoutTag.UnknownEntity -> TextTags.Text let CollectTaggedText (list: List<_>) (t:TaggedText) = list.Add(TaggedText(roslynTag t.Tag, t.Text)) diff --git a/vsintegration/src/FSharp.Editor/LanguageService/Tokenizer.fs b/vsintegration/src/FSharp.Editor/LanguageService/Tokenizer.fs index ad85da00adf..2881818c446 100644 --- a/vsintegration/src/FSharp.Editor/LanguageService/Tokenizer.fs +++ b/vsintegration/src/FSharp.Editor/LanguageService/Tokenizer.fs @@ -244,7 +244,10 @@ module internal Tokenizer = | Protected -> KnownImageIds.ClassProtected | Private -> KnownImageIds.ClassPrivate | _ -> KnownImageIds.None - ImageId(KnownImageIds.ImageCatalogGuid, imageId) + if imageId = KnownImageIds.None then + None + else + Some(ImageId(KnownImageIds.ImageCatalogGuid, imageId)) let GetGlyphForSymbol (symbol: FSharpSymbol, kind: LexerSymbolKind) = match kind with diff --git a/vsintegration/src/FSharp.Editor/QuickInfo/Views.fs b/vsintegration/src/FSharp.Editor/QuickInfo/Views.fs index 96866890687..6274d9c9346 100644 --- a/vsintegration/src/FSharp.Editor/QuickInfo/Views.fs +++ b/vsintegration/src/FSharp.Editor/QuickInfo/Views.fs @@ -17,40 +17,41 @@ module internal QuickInfoViewProvider = | ActivePatternCase | ActivePatternResult | UnionCase - | Enum -> ClassificationTypeNames.EnumName // Roslyn-style classification name + | Enum -> ClassificationTypeNames.EnumName + | Struct -> ClassificationTypeNames.StructName + | TypeParameter -> ClassificationTypeNames.TypeParameterName | Alias | Class - | Module | Record - | Struct - | TypeParameter | Union - | UnknownType -> PredefinedClassificationTypeNames.Type - | Interface -> ClassificationTypeNames.InterfaceName // Roslyn-style classification name - | Keyword -> PredefinedClassificationTypeNames.Keyword - | Delegate - | Event - | Field - | Local + | UnknownType // Default to class until/unless we use classification data + | Module -> ClassificationTypeNames.ClassName + | Interface -> ClassificationTypeNames.InterfaceName + | Keyword -> ClassificationTypeNames.Keyword | Member - | Method - | ModuleBinding - | Namespace - | Parameter + | Function + | Method -> ClassificationTypeNames.MethodName | Property - | RecordField -> PredefinedClassificationTypeNames.Identifier + | RecordField -> ClassificationTypeNames.PropertyName + | Parameter + | Local -> ClassificationTypeNames.LocalName + | ModuleBinding -> ClassificationTypeNames.Identifier + | Namespace -> ClassificationTypeNames.NamespaceName + | Delegate -> ClassificationTypeNames.DelegateName + | Event -> ClassificationTypeNames.EventName + | Field -> ClassificationTypeNames.FieldName | LineBreak - | Space -> PredefinedClassificationTypeNames.WhiteSpace - | NumericLiteral -> PredefinedClassificationTypeNames.Number - | Operator -> PredefinedClassificationTypeNames.Operator - | StringLiteral -> PredefinedClassificationTypeNames.String - | Punctuation - | Text - | UnknownEntity -> PredefinedClassificationTypeNames.Other + | Space -> ClassificationTypeNames.WhiteSpace + | NumericLiteral -> ClassificationTypeNames.NumericLiteral + | Operator -> ClassificationTypeNames.Operator + | StringLiteral -> ClassificationTypeNames.StringLiteral + | Punctuation -> ClassificationTypeNames.Punctuation + | UnknownEntity + | Text -> ClassificationTypeNames.Text let provideContent ( - imageId:ImageId, + imageId:ImageId option, description:#seq, documentation:#seq, navigation:QuickInfoNavigation @@ -91,9 +92,11 @@ module internal QuickInfoViewProvider = flushContainer() ContainerElement(ContainerElementStyle.Stacked, finalCollection |> Seq.map box) - ContainerElement(ContainerElementStyle.Stacked, - ContainerElement(ContainerElementStyle.Wrapped, - ImageElement(imageId), - buildContainerElement description), - buildContainerElement documentation - ) + let innerElement = + match imageId with + | Some imageId -> + ContainerElement(ContainerElementStyle.Wrapped, ImageElement(imageId), buildContainerElement description) + | None -> + ContainerElement(ContainerElementStyle.Wrapped, buildContainerElement description) + + ContainerElement(ContainerElementStyle.Stacked, innerElement, buildContainerElement documentation) diff --git a/vsintegration/tests/UnitTests/LegacyLanguageService/Tests.LanguageService.QuickInfo.fs b/vsintegration/tests/UnitTests/LegacyLanguageService/Tests.LanguageService.QuickInfo.fs index e1bc4ad18ce..200db7b2727 100644 --- a/vsintegration/tests/UnitTests/LegacyLanguageService/Tests.LanguageService.QuickInfo.fs +++ b/vsintegration/tests/UnitTests/LegacyLanguageService/Tests.LanguageService.QuickInfo.fs @@ -117,26 +117,13 @@ type UsingMSBuild() = MoveCursorToStartOfMarker(file, "(*M*)") let tooltip = time1 GetQuickInfoAtCursor file "Time of first tooltip" AssertContainsInOrder(tooltip, expectedExactOrder) - - - [] - member public this.``EmptyTypeTooltipBody``() = - let content = """ - type X(*M*) = class end""" - this.VerifyQuickInfoDoesNotContainAnyAtStartOfMarker content "(*M*)" "=" [] member public this.``NestedTypesOrder``() = this.VerifyOrderOfNestedTypesInQuickInfo( source = "type t = System.Runtime.CompilerServices.RuntimeHelpers(*M*)", marker = "(*M*)", - expectedExactOrder = ["CleanupCode"; "TryCode"] - ) - - this.VerifyOrderOfNestedTypesInQuickInfo( - source = "type t = System.Collections.Generic.Dictionary(*M*)", - marker = "(*M*)", - expectedExactOrder = ["Enumerator"; "KeyCollection"; "ValueCollection"] + expectedExactOrder = ["GetHashCode"; "GetObjectValue"] ) [] @@ -216,7 +203,7 @@ type UsingMSBuild() = this.AssertQuickInfoContainsAtStartOfMarker( fileContents, marker = "MembersTP(*Marker*)", - expected = "type HiddenBaseMembersTP =\n inherit TPBaseTy\n member ShowThisProp : unit", + expected = "type HiddenBaseMembersTP =\n inherit TPBaseTy", addtlRefAssy = [PathRelativeToTestAssembly(@"DummyProviderForLanguageServiceTesting.dll")]) [] @@ -277,13 +264,13 @@ type Async = static member AsBeginEnd : computation:('Arg -> Async<'T>) -> ('Arg * AsyncCallback * obj -> IAsyncResult) * (IAsyncResult -> 'T) * (IAsyncResult -> unit) static member AwaitEvent : event:IEvent<'Del,'T> * ?cancelAction:(unit -> unit) -> Async<'T> (requires delegate and 'Del :> Delegate) static member AwaitIAsyncResult : iar:IAsyncResult * ?millisecondsTimeout:int -> Async - static member AwaitTask : task:Task -> Async - static member AwaitTask : task:Task<'T> -> Async<'T> + static member AwaitTask : task:Task<'T> -> Async<'T> + 1 overload static member AwaitWaitHandle : waitHandle:WaitHandle * ?millisecondsTimeout:int -> Async static member CancelDefaultToken : unit -> unit static member Catch : computation:Async<'T> -> Async> static member Choice : computations:seq> -> Async<'T option> - static member FromBeginEnd : beginAction:(AsyncCallback * obj -> IAsyncResult) * endAction:(IAsyncResult -> 'T) * ?cancelAction:(unit -> unit) -> Async<'T> + static member FromBeginEnd : beginAction:(AsyncCallback * obj -> IAsyncResult) * endAction:(IAsyncResult -> 'T) * ?cancelAction:(unit -> unit) -> Async<'T> + 3 overloads + static member FromContinuations : callback:(('T -> unit) * (exn -> unit) * (OperationCanceledException -> unit) -> unit) -> Async<'T> ... Full name: Microsoft.FSharp.Control.Async""".TrimStart().Replace("\r\n", "\n") @@ -372,7 +359,7 @@ Full name: Microsoft.FSharp.Control.Async""".TrimStart().Replace("\r\n", "\n") let a = typeof """ this.AssertQuickInfoContainsAtStartOfMarker (fileContents, "T(*Marker*)", - "type T =\n new : unit -> T\n event Event1 : EventHandler\n static member M : unit -> int []\n static member StaticProp : decimal", + "type T =\n new : unit -> T\n static member M : unit -> int []\n static member StaticProp : decimal\n event Event1 : EventHandler", addtlRefAssy = [PathRelativeToTestAssembly( @"XmlDocAttributeWithNullComment.dll")]) [] @@ -385,7 +372,7 @@ Full name: Microsoft.FSharp.Control.Async""".TrimStart().Replace("\r\n", "\n") let a = typeof """ this.AssertQuickInfoContainsAtStartOfMarker (fileContents, "T(*Marker*)", - "type T =\n new : unit -> T\n event Event1 : EventHandler\n static member M : unit -> int []\n static member StaticProp : decimal\nFull name: N.T", + "type T =\n new : unit -> T\n static member M : unit -> int []\n static member StaticProp : decimal\n event Event1 : EventHandler", addtlRefAssy = [PathRelativeToTestAssembly( @"XmlDocAttributeWithEmptyComment.dll")]) @@ -1029,13 +1016,12 @@ let f (tp:ITypeProvider(*$$$*)) = tp.Invalidate this.AssertQuickInfoContainsAtEndOfMarker ("""let f x = x + 1 ""","let f","int") - [] + [] member public this.``FrameworkClass``() = let fileContent = """let l = new System.Collections.Generic.List()""" let marker = "Generic.List" - this.AssertQuickInfoContainsAtEndOfMarker(fileContent,marker,"member Capacity : int with get, set\n") + this.AssertQuickInfoContainsAtEndOfMarker(fileContent,marker,"member Capacity : int\n") this.AssertQuickInfoContainsAtEndOfMarker(fileContent,marker,"member Clear : unit -> unit\n") - //this.AssertQuickInfoContainsAtEndOfMarker(fileContent,marker,"member Item : int -> 'T with get, set\n") // removed because quickinfo is now smaller this.VerifyQuickInfoDoesNotContainAnyAtEndOfMarker fileContent marker "get_Capacity" this.VerifyQuickInfoDoesNotContainAnyAtEndOfMarker fileContent marker "set_Capacity" this.VerifyQuickInfoDoesNotContainAnyAtEndOfMarker fileContent marker "get_Count" @@ -1942,34 +1928,6 @@ let f (tp:ITypeProvider(*$$$*)) = tp.Invalidate "[Signature:M:System.String.Format(System.String,System.Object[])]"; ] ) - - [] - member public this.``Regression.MemberDefinition.DocComments.Bug5856_12``() = - this.AssertMemberDataTipContainsInOrder - ((*code *) - [ - "System." - ] , - (* marker *) - "System.", - (* completed item *) - "Action", - (* expect to see in order... *) - [ - "type Action"; - " delegate of" - "[Filename:"; "mscorlib.dll]"; - "[Signature:T:System.Action]" - "type Action<"; - " delegate of" - "[Filename:"; "mscorlib.dll]"; - "[Signature:T:System.Action`1]" - "type Action<"; - " delegate of" - "[Filename:"; "mscorlib.dll]"; - "[Signature:T:System.Action`2]" - ] - ) [] member public this.``Regression.MemberDefinition.DocComments.Bug5856_13``() = @@ -2097,7 +2055,7 @@ query." /// Bug 4592: Check that ctors are displayed from C# classes, i.e. the "new" lines below. [] - member public this.``Regression.Class.Printing.CSharp.Classes.Only..Bug4592``() = + member public this.``Regression.Class.Printing.CSharp.Classes.Only.Bug4592``() = this.AssertMemberDataTipContainsInOrder ((*code *) ["#light"; @@ -2108,10 +2066,11 @@ query." "Random", (* expect to see in order... *) ["type Random ="; - " new : unit -> Random + 1 overload"; + " new : unit -> unit + 1 overload" " member Next : unit -> int + 2 overloads"; - " member NextBytes : buffer:byte[] -> unit"; (* methods sorted alpha *) - " member NextDouble : unit -> float";] + " member NextBytes : buffer: byte [] -> unit"; + " member NextDouble : unit -> float"; + " member Sample : unit -> float";] ) [] @@ -2144,16 +2103,16 @@ query." (* expect to see in order... *) // Pre fix output is mixed up [ "type CodeConnectAccess ="; - " new : allowScheme:string * allowPort:int -> CodeConnectAccess"; - " member Equals : o:obj -> bool"; - " member GetHashCode : unit -> int"; (* method *) - " member Port : int"; - " member Scheme : string"; - " static val DefaultPort : int"; (* static val after instance, but before static method *) - " static val OriginPort : int"; - " static val OriginScheme : string"; + " new : allowScheme: string * allowPort: int -> unit + 2 overloads"; + " member Equals : o: obj -> bool"; + " member GetHashCode : unit -> int"; + " static member CreateAnySchemeAccess : allowPort: int -> CodeConnectAccess"; + " static member CreateOriginSchemeAccess : allowPort: int -> CodeConnectAccess"; + " static member IsValidScheme : scheme: string -> bool"; + " static val AnyPort : int"; " static val AnyScheme : string"; - " static member CreateAnySchemeAccess : allowPort:int -> CodeConnectAccess"; + " static val DefaultPort : int"; + " static val NoPort : int"; " ..."; ]) @@ -2195,55 +2154,16 @@ query." " inherit Form"; " interface IDisposable"; " new : unit -> F1"; - " val x: F1"; - " abstract member AAA : int"; - " abstract member ZZZ : int"; - " abstract member AAA : bool with set"; + " val x: F1" " member B : unit -> int"; - " member D : unit -> int"; - " member D : x:int -> int"; + " override ToString : unit -> string"; + " static member A : unit -> int"; + " static member C : unit -> int"; + " abstract member AAA : int"; + " member D : int"; " ..."; - //" member D : int"; - //" member D : int with set"; - //" static val x: F1"; - //" static member A : unit -> int"; - //" static member C : unit -> int"; ]) -(* TODO why does this portion not work? specifically, last assert fails - printfn "changing file..." - ReplaceFileInMemory file1 ["#light" - "let xx = \"foo\"" // now x is string - "printfn \"hi\""] - - // assert p1 xx is string - MoveCursorToEndOfMarker(file1,"let x") - TakeCoffeeBreak(this.VS) - let tooltip = GetQuickInfoAtCursor file1 - AssertContains(tooltip,"string") - - // assert p2 yy is int - MoveCursorToEndOfMarker(file2,"let y") - let tooltip = GetQuickInfoAtCursor file2 - AssertContains(tooltip,"int") - - AssertNoErrorsOrWarnings(project1) - AssertNoErrorsOrWarnings(project2) - - printfn "rebuilding dependent project..." - // (re)build p1 (with xx now string) - Build(project1) |> ignore - TakeCoffeeBreak(this.VS) - - AssertNoErrorsOrWarnings(project1) - AssertNoErrorsOrWarnings(project2) - - // assert p2 yy is now string - MoveCursorToEndOfMarker(file2,"let y") - let tooltip = GetQuickInfoAtCursor file2 - AssertContains(tooltip,"string") -*) - (*------------------------------------------IDE automation starts here -------------------------------------------------*) [] member public this.``Automation.Regression.AccessibilityOnTypeMembers.Bug4168``() = @@ -2256,12 +2176,6 @@ query." internal new(x:int,y:int) = new Foo2() private new(x:int,y:int,z:int) = new Foo2()""" this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker*)", "type internal Foo2") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker*)", "private new : x:int * y:int * z:int -> Foo2") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker*)", "new : x:int * y:int -> Foo2") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker*)", "private new") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker*)", "member Prop1") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker*)", "member Prop2") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker*)", "member private Prop3") [] member public this.``Automation.Regression.AccessorsAndMutators.Bug4276``() = @@ -2298,8 +2212,7 @@ query." this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker1*)", "member X : int") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker1*)", "member Y : int") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2*)", "type BitArray") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2*)", "member Length : int") // trimmed quick info doesn't contain all entries - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2*)", "member Count : int") + this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2*)", "member Not : unit -> BitArray") this.VerifyQuickInfoDoesNotContainAnyAtStartOfMarker fileContent "(*Marker2*)" "get_Length" this.VerifyQuickInfoDoesNotContainAnyAtStartOfMarker fileContent "(*Marker2*)" "set_Length" @@ -2767,26 +2680,15 @@ query." let genericClass(*Marker4_2*) = new GenericClass()""" this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker1_1*)", "type MyInt = int") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker1_1*)", "Full name: NS.TypeAbbreviation.MyInt") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker1_2*)", "val myInt : MyInt") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2_1*)", "type PairOfFloat = float * float") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2_1*)", "Full name: NS.TypeAbbreviation.PairOfFloat") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2_2*)", "val MySeq : seq") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker2_2*)", "Full name: NS.TypeAbbreviation.MySeq") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker3_1*)", "type IA =") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker3_1*)", "abstract member AbstractMember : int -> int") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker3_2*)", "type ClassIA =") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker3_2*)", "Full name: NS.TypeAbbreviation.ClassIA") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker3_2*)", "implements: IA") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker4_1*)", "type GenericClass<'a (requires 'a :> IA)> =") - this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker4_1*)", "static member StaticMember : x:'a -> int") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker4_1*)", "Full name: NS.TypeAbbreviation.GenericClass<_>") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker4_2*)", "val genericClass : GenericClass") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker4_2*)", "Full name: NS.TypeAbbreviation.genericClass") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker5_1*)", "type AbAttrName = AbstractClassAttribute") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker5_1*)", "implements: System.Runtime.InteropServices._Attribute") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker5_2*)", "type AbAttrName = AbstractClassAttribute") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker5_2*)", "implements: System.Runtime.InteropServices._Attribute") [] member public this.``Automation.Regression.TypeInferenceSenarios.Bug2362&3538``() = @@ -2844,8 +2746,6 @@ query." let singleton(*MarkerLastLine*) k a = Branch(k,a,Nil,Nil)""" this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*MarkerType*)", "type PriorityQueue") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*MarkerType*)", "Full name: NS.PriorityQueue<_,_>") - //this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*MarkerType*)", "implements: IComparable") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*MarkerDataConstructor*)", "union case PriorityQueue.Nil: PriorityQueue<'k,'a>") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*Marker3*)", "module PriorityQueue") this.AssertQuickInfoContainsAtStartOfMarker (fileContent, "(*MarkerVal*)", "val pq : PriorityQueue<'a,'b>") @@ -3167,7 +3067,6 @@ query." yield a.X(*Marker4*) }""" let queries = [("(*Marker1*)", "val controlEventHandler : ControlEventHandler"); ("(*Marker2*)", "property MyDistance.Event: Event"); -// ("(*Marker2*)", "DocComment: Event"); //Fail: due to DocComments ("(*Marker3*)", "val newDelegate : ControlEventHandler"); ("(*Marker4*)", "property MyPoint.X: float"); ("(*Marker4*)", "Gets and sets X")] @@ -3209,7 +3108,6 @@ query." yield a.X(*Marker4*) }""" let queries = [("(*Marker1*)", "val controlEventHandler : ControlEventHandler"); ("(*Marker2*)", "property MyDistance.Event: Event"); -// ("(*Marker2*)", "DocComment: Event"); //Fail: due to DocComments ("(*Marker3*)", "val newDelegate : ControlEventHandler"); ("(*Marker4*)", "property MyPoint.X: float"); ("(*Marker4*)", "Gets and sets X"); @@ -3259,10 +3157,8 @@ query." | false -> tupley""" let queries = [("(*Marker1*)", "val tuple1 : int * string * float * (int -> string * int)"); ("(*Marker2*)", "type MyEmployee"); -// ("(*Marker2*)", "DocComment: This is my record type."); //Fail: due to DocComments ("(*Marker2*)", "Full name: FSTestLib.MyEmployee"); ("(*Marker3*)", "type MyCar"); -// ("(*Marker3*)", "DocComment: This is my class type"); //Fail: due to DocComments ("(*Marker3*)", "Full name: FSTestLib.MyCar"); ("(*Marker4*)", "val tuplex : 'a * string") ]