diff --git a/docs/release-notes/.FSharp.Compiler.Service/9.0.100.md b/docs/release-notes/.FSharp.Compiler.Service/9.0.100.md
index 22eee3e2e5b..1455a1f0479 100644
--- a/docs/release-notes/.FSharp.Compiler.Service/9.0.100.md
+++ b/docs/release-notes/.FSharp.Compiler.Service/9.0.100.md
@@ -36,10 +36,11 @@
 * Enable FSharp 9.0 Language Version ([Issue #17497](https://github.com/dotnet/fsharp/issues/17438)), [PR](https://github.com/dotnet/fsharp/pull/17500)))
 * Enable LanguageFeature.EnforceAttributeTargets in F# 9.0. ([Issue #17514](https://github.com/dotnet/fsharp/issues/17558), [PR #17516](https://github.com/dotnet/fsharp/pull/17558))
 * Parser: better recovery for unfinished patterns ([PR #17231](https://github.com/dotnet/fsharp/pull/17231), [PR #17232](https://github.com/dotnet/fsharp/pull/17232)))
-* Enable consuming generic arguments defined as `allows ref struct` in C# ([Issue #17597](https://github.com/dotnet/fsharp/issues/17597)
+* Enable consuming generic arguments defined as `allows ref struct` in C# ([Issue #17597](https://github.com/dotnet/fsharp/issues/17597), display them in tooltips [PR #17706](https://github.com/dotnet/fsharp/pull/17706))
 * Trivia for SynTypeConstraint.WhereTyparNotSupportsNull. ([Issue #17721](https://github.com/dotnet/fsharp/issues/17721), [PR #17745](https://github.com/dotnet/fsharp/pull/17745))
 * Trivia for SynType.WithNull. ([Issue #17720](https://github.com/dotnet/fsharp/issues/17720), [PR #17745](https://github.com/dotnet/fsharp/pull/17745))
 
+
 ### Changed
 
 * Change compiler default setting realsig+ when building assemblies ([Issue #17384](https://github.com/dotnet/fsharp/issues/17384), [PR #17378](https://github.com/dotnet/fsharp/pull/17385))
diff --git a/src/Compiler/Checking/ConstraintSolver.fs b/src/Compiler/Checking/ConstraintSolver.fs
index 196a62c3fec..f9ed37fe9ca 100644
--- a/src/Compiler/Checking/ConstraintSolver.fs
+++ b/src/Compiler/Checking/ConstraintSolver.fs
@@ -1024,6 +1024,7 @@ and SolveTypMeetsTyparConstraints (csenv: ConstraintSolverEnv) ndeep m2 trace ty
         | TyparConstraint.IsDelegate(aty, bty, m2)       -> SolveTypeIsDelegate                 csenv ndeep m2 trace ty aty bty
         | TyparConstraint.IsNonNullableStruct m2         -> SolveTypeIsNonNullableValueType     csenv ndeep m2 trace ty
         | TyparConstraint.IsUnmanaged m2                 -> SolveTypeIsUnmanaged                csenv ndeep m2 trace ty
+        | TyparConstraint.AllowsRefStruct _              -> CompleteD
         | TyparConstraint.IsReferenceType m2             -> SolveTypeIsReferenceType            csenv ndeep m2 trace ty
         | TyparConstraint.RequiresDefaultConstructor m2  -> SolveTypeRequiresDefaultConstructor csenv ndeep m2 trace ty
         | TyparConstraint.SimpleChoice(tys, m2)          -> SolveTypeChoice                     csenv ndeep m2 trace ty tys
@@ -2465,6 +2466,7 @@ and CheckConstraintImplication (csenv: ConstraintSolverEnv) tpc1 tpc2 =
     | TyparConstraint.NotSupportsNull _, TyparConstraint.NotSupportsNull _
     | TyparConstraint.IsNonNullableStruct _, TyparConstraint.IsNonNullableStruct _
     | TyparConstraint.IsUnmanaged _, TyparConstraint.IsUnmanaged _
+    | TyparConstraint.AllowsRefStruct _, TyparConstraint.AllowsRefStruct _
     | TyparConstraint.IsReferenceType _, TyparConstraint.IsReferenceType _
     | TyparConstraint.RequiresDefaultConstructor _, TyparConstraint.RequiresDefaultConstructor _ -> true
     | TyparConstraint.SimpleChoice (tys1, _), TyparConstraint.SimpleChoice (tys2, _) -> ListSet.isSubsetOf (typeEquiv g) tys1 tys2
diff --git a/src/Compiler/Checking/Expressions/CheckExpressions.fs b/src/Compiler/Checking/Expressions/CheckExpressions.fs
index 615e4251893..b5cc414e721 100644
--- a/src/Compiler/Checking/Expressions/CheckExpressions.fs
+++ b/src/Compiler/Checking/Expressions/CheckExpressions.fs
@@ -5163,6 +5163,7 @@ and TcPatLongIdentActivePatternCase warnOnUpper (cenv: cenv) (env: TcEnv) vFlags
                         | TyparConstraint.SupportsComparison _
                         | TyparConstraint.SupportsEquality _
                         | TyparConstraint.DefaultsTo (ty = Unit)
+                        | TyparConstraint.AllowsRefStruct _
                         | TyparConstraint.MayResolveMember _ -> true
 
                         // Any other kind of constraint is incompatible with unit.
diff --git a/src/Compiler/Checking/NicePrint.fs b/src/Compiler/Checking/NicePrint.fs
index ccb99f12139..812837a3edd 100644
--- a/src/Compiler/Checking/NicePrint.fs
+++ b/src/Compiler/Checking/NicePrint.fs
@@ -773,8 +773,13 @@ module PrintTypes =
         | _ -> 
             if denv.abbreviateAdditionalConstraints then 
                 wordL (tagKeyword "when") ^^ wordL(tagText "<constraints>")
-            elif denv.shortConstraints then 
-                LeftL.leftParen ^^ wordL (tagKeyword "requires") ^^ sepListL (wordL (tagKeyword "and")) cxsL ^^ RightL.rightParen
+            elif denv.shortConstraints then
+                match cxs with
+                | (_,TyparConstraint.AllowsRefStruct _) :: _ ->
+                    // If the first constraint is 'allows ref struct', we do not want to prefix it with 'requires', because that just reads wrong.
+                    LeftL.leftParen ^^ sepListL (wordL (tagKeyword "and")) cxsL ^^ RightL.rightParen
+                | _ ->
+                    LeftL.leftParen ^^ wordL (tagKeyword "requires") ^^ sepListL (wordL (tagKeyword "and")) cxsL ^^ RightL.rightParen
             else
                 wordL (tagKeyword "when") ^^ sepListL (wordL (tagKeyword "and")) cxsL
 
@@ -834,6 +839,12 @@ module PrintTypes =
                 [wordL (tagKeyword "unmanaged")]
             else
                 [wordL (tagKeyword "unmanaged") |> longConstraintPrefix]
+                
+        | TyparConstraint.AllowsRefStruct _ ->
+            if denv.shortConstraints then
+                [wordL (tagKeyword "allows ref struct")]
+            else
+                [wordL (tagKeyword "allows ref struct") |> longConstraintPrefix]
 
         | TyparConstraint.IsReferenceType _ ->
             if denv.shortConstraints then 
diff --git a/src/Compiler/Checking/PostInferenceChecks.fs b/src/Compiler/Checking/PostInferenceChecks.fs
index 06ef1b9766a..e9860a76efa 100644
--- a/src/Compiler/Checking/PostInferenceChecks.fs
+++ b/src/Compiler/Checking/PostInferenceChecks.fs
@@ -448,6 +448,7 @@ and CheckTypeConstraintDeep cenv f g env x =
      | TyparConstraint.NotSupportsNull _
      | TyparConstraint.IsNonNullableStruct _
      | TyparConstraint.IsUnmanaged _
+     | TyparConstraint.AllowsRefStruct _
      | TyparConstraint.IsReferenceType _
      | TyparConstraint.RequiresDefaultConstructor _ -> ()
 
diff --git a/src/Compiler/Checking/SignatureHash.fs b/src/Compiler/Checking/SignatureHash.fs
index f3f81b2fee3..66aeb0912c7 100644
--- a/src/Compiler/Checking/SignatureHash.fs
+++ b/src/Compiler/Checking/SignatureHash.fs
@@ -165,6 +165,7 @@ module rec HashTypes =
         | TyparConstraint.SimpleChoice(tys, _) -> tpHash @@ 12 @@ (tys |> hashListOrderIndependent (hashTType g))
         | TyparConstraint.RequiresDefaultConstructor _ -> tpHash @@ 13
         | TyparConstraint.NotSupportsNull(_) -> tpHash @@ 14
+        | TyparConstraint.AllowsRefStruct _ -> tpHash @@ 15
 
     /// Hash type parameter constraints
     let private hashConstraints (g: TcGlobals) cxs =
diff --git a/src/Compiler/Checking/TypeHierarchy.fs b/src/Compiler/Checking/TypeHierarchy.fs
index 102f36908fe..1ccde31b75e 100644
--- a/src/Compiler/Checking/TypeHierarchy.fs
+++ b/src/Compiler/Checking/TypeHierarchy.fs
@@ -285,6 +285,7 @@ let FoldHierarchyOfTypeAux followInterfaces allowMultiIntfInst skipUnref visitor
                           | TyparConstraint.NotSupportsNull _
                           | TyparConstraint.IsNonNullableStruct _
                           | TyparConstraint.IsUnmanaged _
+                          | TyparConstraint.AllowsRefStruct _
                           | TyparConstraint.IsReferenceType _
                           | TyparConstraint.SimpleChoice _
                           | TyparConstraint.RequiresDefaultConstructor _ -> vacc
@@ -412,7 +413,9 @@ let ImportReturnTypeFromMetadata amap m nullnessSource ilTy scoref tinst minst =
 
 let CopyTyparConstraints m tprefInst (tporig: Typar) =
     tporig.Constraints
-    |>  List.map (fun tpc ->
+    // F# does not have escape analysis for authoring 'allows ref struct' generic code. Therefore, typar is not copied, can only come from C# authored code
+    |> List.filter (fun tp -> match tp with | TyparConstraint.AllowsRefStruct _ -> false | _ -> true)
+    |> List.map (fun tpc ->
            match tpc with
            | TyparConstraint.CoercesTo(ty, _) ->
                TyparConstraint.CoercesTo (instType tprefInst ty, m)
@@ -434,6 +437,7 @@ let CopyTyparConstraints m tprefInst (tporig: Typar) =
                TyparConstraint.IsNonNullableStruct m
            | TyparConstraint.IsUnmanaged _ ->
                TyparConstraint.IsUnmanaged m
+           | TyparConstraint.AllowsRefStruct _ -> failwith "impossible, filtered above"
            | TyparConstraint.IsReferenceType _ ->
                TyparConstraint.IsReferenceType m
            | TyparConstraint.SimpleChoice (tys, _) ->
diff --git a/src/Compiler/Checking/TypeRelations.fs b/src/Compiler/Checking/TypeRelations.fs
index 16ed5e9f9d3..b52a1da1574 100644
--- a/src/Compiler/Checking/TypeRelations.fs
+++ b/src/Compiler/Checking/TypeRelations.fs
@@ -151,19 +151,13 @@ let ChooseTyparSolutionAndRange (g: TcGlobals) amap (tp:Typar) =
              match tpc with 
              | TyparConstraint.CoercesTo(x, m) -> 
                  join m x, m
-             | TyparConstraint.MayResolveMember(_traitInfo, m) -> 
-                 (maxTy, isRefined), m
              | TyparConstraint.SimpleChoice(_, m) -> 
                  errorR(Error(FSComp.SR.typrelCannotResolveAmbiguityInPrintf(), m))
                  (maxTy, isRefined), m
              | TyparConstraint.SupportsNull m -> 
                  ((addNullnessToTy KnownWithNull maxTy), isRefined), m
-             | TyparConstraint.NotSupportsNull m -> 
-                 (maxTy, isRefined), m // NOTE: this doesn't "force" non-nullness, since it is the default choice in 'obj' or 'int'
              | TyparConstraint.SupportsComparison m -> 
                  join m g.mk_IComparable_ty, m
-             | TyparConstraint.SupportsEquality m -> 
-                 (maxTy, isRefined), m
              | TyparConstraint.IsEnum(_, m) -> 
                  errorR(Error(FSComp.SR.typrelCannotResolveAmbiguityInEnum(), m))
                  (maxTy, isRefined), m
@@ -175,12 +169,15 @@ let ChooseTyparSolutionAndRange (g: TcGlobals) amap (tp:Typar) =
              | TyparConstraint.IsUnmanaged m ->
                  errorR(Error(FSComp.SR.typrelCannotResolveAmbiguityInUnmanaged(), m))
                  (maxTy, isRefined), m
-             | TyparConstraint.RequiresDefaultConstructor m -> 
-                 (maxTy, isRefined), m
-             | TyparConstraint.IsReferenceType m -> 
+             | TyparConstraint.NotSupportsNull m // NOTE: this doesn't "force" non-nullness, since it is the default choice in 'obj' or 'int'
+             | TyparConstraint.SupportsEquality m
+             | TyparConstraint.AllowsRefStruct m
+             | TyparConstraint.RequiresDefaultConstructor m
+             | TyparConstraint.IsReferenceType m
+             | TyparConstraint.MayResolveMember(_, m)
+             | TyparConstraint.DefaultsTo(_,_, m) -> 
                  (maxTy, isRefined), m
-             | TyparConstraint.DefaultsTo(_priority, _ty, m) -> 
-                 (maxTy, isRefined), m)
+             )
 
     if g.langVersion.SupportsFeature LanguageFeature.DiagnosticForObjInference then
         match tp.Kind with
diff --git a/src/Compiler/Checking/import.fs b/src/Compiler/Checking/import.fs
index 68e3512864b..1c1b0ed9ea1 100644
--- a/src/Compiler/Checking/import.fs
+++ b/src/Compiler/Checking/import.fs
@@ -653,6 +653,8 @@ let ImportILGenericParameters amap m scoref tinst (nullableFallback:Nullness.Nul
                     TyparConstraint.IsNonNullableStruct(m)
                   if gp.HasReferenceTypeConstraint then
                     TyparConstraint.IsReferenceType(m)
+                  if gp.HasAllowsRefStruct then
+                    TyparConstraint.AllowsRefStruct(m)
                   for ilTy in gp.Constraints do
                     TyparConstraint.CoercesTo(ImportILType amap m importInst (rescopeILType scoref ilTy), m) ]            
 
diff --git a/src/Compiler/TypedTree/TypedTree.fs b/src/Compiler/TypedTree/TypedTree.fs
index daf31357df3..b948e91fb65 100644
--- a/src/Compiler/TypedTree/TypedTree.fs
+++ b/src/Compiler/TypedTree/TypedTree.fs
@@ -2531,6 +2531,9 @@ type TyparConstraint =
     
     /// A constraint that a type is .NET unmanaged type
     | IsUnmanaged of range: range
+    
+    /// An anti-constraint indicating that ref structs (e.g. Span<>) are allowed here
+    | AllowsRefStruct of range:range
 
     // %+A formatting is used, so this is not needed
     //[<DebuggerBrowsable(DebuggerBrowsableState.Never)>]
diff --git a/src/Compiler/TypedTree/TypedTree.fsi b/src/Compiler/TypedTree/TypedTree.fsi
index 3ba4f5c12ba..d357895728d 100644
--- a/src/Compiler/TypedTree/TypedTree.fsi
+++ b/src/Compiler/TypedTree/TypedTree.fsi
@@ -1694,6 +1694,9 @@ type TyparConstraint =
     /// A constraint that a type is .NET unmanaged type
     | IsUnmanaged of range: range
 
+    /// An anti-constraint indicating that ref structs (e.g. Span<>) are allowed here
+    | AllowsRefStruct of range: range
+
     override ToString: unit -> string
 
 [<NoEquality; NoComparison; StructuredFormatDisplay("{DebugText}")>]
diff --git a/src/Compiler/TypedTree/TypedTreeOps.fs b/src/Compiler/TypedTree/TypedTreeOps.fs
index 333b29cd78f..e7c4576b24e 100644
--- a/src/Compiler/TypedTree/TypedTreeOps.fs
+++ b/src/Compiler/TypedTree/TypedTreeOps.fs
@@ -272,7 +272,8 @@ and remapTyparConstraintsAux tyenv cs =
          | TyparConstraint.SupportsEquality _ 
          | TyparConstraint.SupportsNull _ 
          | TyparConstraint.NotSupportsNull _ 
-         | TyparConstraint.IsUnmanaged _ 
+         | TyparConstraint.IsUnmanaged _
+         | TyparConstraint.AllowsRefStruct _
          | TyparConstraint.IsNonNullableStruct _ 
          | TyparConstraint.IsReferenceType _ 
          | TyparConstraint.RequiresDefaultConstructor _ -> Some x)
@@ -1039,6 +1040,7 @@ and typarConstraintsAEquivAux erasureFlag g aenv tpc1 tpc2 =
     | TyparConstraint.IsNonNullableStruct _, TyparConstraint.IsNonNullableStruct _
     | TyparConstraint.IsReferenceType _, TyparConstraint.IsReferenceType _ 
     | TyparConstraint.IsUnmanaged _, TyparConstraint.IsUnmanaged _
+    | TyparConstraint.AllowsRefStruct _, TyparConstraint.AllowsRefStruct _
     | TyparConstraint.RequiresDefaultConstructor _, TyparConstraint.RequiresDefaultConstructor _ -> true
     | _ -> false
 
@@ -2345,6 +2347,7 @@ and accFreeInTyparConstraint opts tpc acc =
     | TyparConstraint.IsNonNullableStruct _ 
     | TyparConstraint.IsReferenceType _ 
     | TyparConstraint.IsUnmanaged _
+    | TyparConstraint.AllowsRefStruct _
     | TyparConstraint.RequiresDefaultConstructor _ -> acc
 
 and accFreeInTrait opts (TTrait(tys, _, _, argTys, retTy, _, sln)) acc = 
@@ -2480,6 +2483,7 @@ and accFreeInTyparConstraintLeftToRight g cxFlag thruFlag acc tpc =
     | TyparConstraint.NotSupportsNull _ 
     | TyparConstraint.IsNonNullableStruct _ 
     | TyparConstraint.IsUnmanaged _
+    | TyparConstraint.AllowsRefStruct _
     | TyparConstraint.IsReferenceType _ 
     | TyparConstraint.RequiresDefaultConstructor _ -> acc
 
@@ -4223,6 +4227,8 @@ module DebugPrint =
             wordL (tagText "not null") |> constraintPrefix
         | TyparConstraint.IsUnmanaged _ ->
             wordL (tagText "unmanaged") |> constraintPrefix
+        | TyparConstraint.AllowsRefStruct _ ->
+            wordL (tagText "allows ref struct") |> constraintPrefix
         | TyparConstraint.SimpleChoice(tys, _) ->
             bracketL (sepListL (sepL (tagText "|")) (List.map (auxTypeL env) tys)) |> constraintPrefix
         | TyparConstraint.RequiresDefaultConstructor _ ->
diff --git a/src/Compiler/TypedTree/TypedTreePickle.fs b/src/Compiler/TypedTree/TypedTreePickle.fs
index 9ade306d77c..9515d49b80d 100644
--- a/src/Compiler/TypedTree/TypedTreePickle.fs
+++ b/src/Compiler/TypedTree/TypedTreePickle.fs
@@ -1612,19 +1612,22 @@ let p_tyar_constraint x st =
     | TyparConstraint.SupportsComparison _          -> p_byte 10 st
     | TyparConstraint.SupportsEquality _            -> p_byte 11 st
     | TyparConstraint.IsUnmanaged _                 -> p_byte 12 st
-    | TyparConstraint.NotSupportsNull _             -> 
-        failwith "NotSupportsNull constraints should only be emitted to streamB"
+    
+    | TyparConstraint.NotSupportsNull _
+    | TyparConstraint.AllowsRefStruct _ -> 
+        failwith $"%A{x} constraints should only be emitted to streamB"
 
-// Some extra F# 5.0 constraints are stored in stream B, these will be ignored by earlier F# compilers
+// Some extra F#9+ constraints are stored in stream B, these will be ignored by earlier F# compilers
 let p_tyar_constraintB x st = 
     match x with 
     | TyparConstraint.NotSupportsNull _             -> p_byteB 1 st
-    | _ -> failwith "only NotSupportsNull constraints should be emitted to streamB"
+    | TyparConstraint.AllowsRefStruct _             -> p_byteB 2 st
+    | _ -> failwith "only NotSupportsNull and AllowsRefStruct constraints should be emitted to streamB"
 
 let p_tyar_constraints cxs st = 
-    let cxs1, cxs2 = cxs |> List.partition (function TyparConstraint.NotSupportsNull _ -> false | _ -> true)
+    let cxs1, cxs2 = cxs |> List.partition (function TyparConstraint.NotSupportsNull _ | TyparConstraint.AllowsRefStruct _ -> false | _ -> true)
     p_list p_tyar_constraint cxs1 st
-    // Some extra F# 5.0 constraints are stored in stream B, these will be ignored by earlier F# compilers
+    // Some extra F#9+ constraints are stored in stream B, these will be ignored by earlier F# compilers
     p_listB p_tyar_constraintB cxs2 st
 
 let u_tyar_constraint st =
@@ -1645,16 +1648,17 @@ let u_tyar_constraint st =
     | 12 ->                         (fun       _ -> TyparConstraint.IsUnmanaged range0)
     | _ -> ufailwith st "u_tyar_constraint"
 
-// Some extra F# 5.0 constraints are stored in stream B, these will be ignored by earlier F# compilers
+// Some extra F#9+ constraints are stored in stream B, these will be ignored by earlier F# compilers
 let u_tyar_constraintB st = 
     let tag = u_byteB st
     match tag with
-    | 1 ->  TyparConstraint.NotSupportsNull range0
+    | 1 -> TyparConstraint.NotSupportsNull range0
+    | 2 -> TyparConstraint.AllowsRefStruct range0
     | _ -> ufailwith st "u_tyar_constraintB - unexpected constraint in streamB" 
 
 let u_tyar_constraints st =
     let cxs1 = u_list_revi u_tyar_constraint st
-    // Some extra F# 5.0 constraints are stored in stream B, these will be ignored by earlier F# compilers
+    // Some extra F#9+ constraints are stored in stream B, these will be ignored by earlier F# compilers
     //
     // If the B stream is not present (e.g. reading F# 4.5 components) then this list will be empty
     // via the implementation of u_listB.
diff --git a/tests/FSharp.Compiler.Service.Tests/TooltipTests.fs b/tests/FSharp.Compiler.Service.Tests/TooltipTests.fs
index e9ce93a37cd..0b30a5a61e8 100644
--- a/tests/FSharp.Compiler.Service.Tests/TooltipTests.fs
+++ b/tests/FSharp.Compiler.Service.Tests/TooltipTests.fs
@@ -514,4 +514,49 @@ let success,version = System.Version.TryParse(null)
     checkResults.GetToolTip(2, 45, "let success,version = System.Version.TryParse(null)", [ "TryParse" ], FSharpTokenTag.Identifier,width=100)   
     |> assertAndGetSingleToolTipText
     |> Assert.shouldBeEquivalentTo ("""System.Version.TryParse([<NotNullWhenAttribute (true)>] input: string | null,
-                        [<NotNullWhenAttribute (true)>] result: byref<System.Version | null>) : bool""" |> normalize)
\ No newline at end of file
+                        [<NotNullWhenAttribute (true)>] result: byref<System.Version | null>) : bool""" |> normalize)
+    
+[<FactForNETCOREAPP>]
+let ``Allows ref struct is shown on BCL interface declaration`` () =   
+    let source = """module Foo
+open System
+let myAction : Action<int> | null = null
+"""
+    let checkResults = getCheckResults source [|"--checknulls+";"--langversion:preview"|]
+    checkResults.GetToolTip(3, 21, "let myAction : Action<int> | null = null", [ "Action" ], FSharpTokenTag.Identifier)   
+    |> assertAndGetSingleToolTipText
+    |> Assert.shouldStartWith ("""type Action<'T (allows ref struct)>""" |> normalize)
+    
+[<FactForNETCOREAPP>]
+let ``Allows ref struct is shown for each T on BCL interface declaration`` () =   
+    let source = """module Foo
+open System
+let myAction : Action<int,_,_,_> | null = null
+"""
+    let checkResults = getCheckResults source [|"--checknulls+";"--langversion:preview"|]
+    checkResults.GetToolTip(3, 21, "let myAction : Action<int,_,_,_> | null = null", [ "Action" ], FSharpTokenTag.Identifier)   
+    |> assertAndGetSingleToolTipText
+    |> Assert.shouldStartWith ("""type Action<'T1,'T2,'T3,'T4 (allows ref struct and allows ref struct and allows ref struct and allows ref struct)>""" |> normalize)
+    
+[<FactForNETCOREAPP>]
+let ``Allows ref struct is shown on BCL method usage`` () =
+    let source = """module Foo
+open System
+open System.Collections.Generic
+let doIt (dict:Dictionary<'a,'b>) = dict.GetAlternateLookup<'a,'b,ReadOnlySpan<char>>()
+"""
+    let checkResults = getCheckResults source [|"--langversion:preview"|]
+    checkResults.GetToolTip(4, 59, "let doIt (dict:Dictionary<'a,'b>) = dict.GetAlternateLookup<'a,'b,ReadOnlySpan<char>>()", [ "GetAlternateLookup" ], FSharpTokenTag.Identifier)   
+    |> assertAndGetSingleToolTipText
+    |> Assert.shouldContain ("""'TAlternateKey (allows ref struct)""" |> normalize)
+    
+[<FactForNETCOREAPP>]
+let ``Allows ref struct is not shown on BCL interface usage`` () =   
+    let source = """module Foo
+open System
+let doIt(myAction : Action<int>) = myAction.Invoke(42)
+"""
+    let checkResults = getCheckResults source [|"--langversion:preview"|]
+    checkResults.GetToolTip(3, 43, "let doIt(myAction : Action<int>) = myAction.Invoke(42)", [ "myAction" ], FSharpTokenTag.Identifier)   
+    |> assertAndGetSingleToolTipText
+    |> Assert.shouldBeEquivalentTo ("""val myAction: Action<int>""" |> normalize)
\ No newline at end of file
diff --git a/tests/FSharp.Test.Utilities/Assert.fs b/tests/FSharp.Test.Utilities/Assert.fs
index dfed4bf123e..fc36129666f 100644
--- a/tests/FSharp.Test.Utilities/Assert.fs
+++ b/tests/FSharp.Test.Utilities/Assert.fs
@@ -11,6 +11,12 @@ module Assert =
 
     let inline shouldBeEquivalentTo (expected : ^T) (actual : ^U) =
         actual.Should().BeEquivalentTo(expected, "") |> ignore
+        
+    let inline shouldStartWith (expected : string) (actual : string) =
+        actual.Should().StartWith(expected) |> ignore
+        
+    let inline shouldContain (needle : string) (haystack : string) =
+        haystack.Should().Contain(needle) |> ignore    
 
     let inline shouldBe (expected : ^T) (actual : ^U) =
         actual.Should().Be(expected, "") |> ignore