提交 05ff1263 编写于 作者: L latkin

Script debugging in VS

See spec at https://gist.github.com/latkin/cba4187a99db9747d0bf
closes #225

commit b8ea6f617f32e44f29a22afd7aa4f2d09bb1a091
Author: latkin <latkin@microsoft.com>
Date:   Tue Feb 24 17:12:04 2015 -0800

    Touch-ups after rebase

commit 26ff24562bfb49de79c44342105f2946898c2f1e
Author: latkin <latkin@microsoft.com>
Date:   Wed Feb 18 12:54:36 2015 -0800

    Add capability to auto-break on first executable line

commit 675a27298d687cb8c3240af64069cc22accefe02
Author: latkin <latkin@microsoft.com>
Date:   Wed Feb 18 12:53:27 2015 -0800

    Change menu text, use more sensible hotkeys

commit ab73f78ca8bfc4b433152aa3e173fc22b74786a0
Author: latkin <latkin@microsoft.com>
Date:   Wed Feb 18 12:52:39 2015 -0800

    Small whitespace alignment

commit f551344b09fdfb94bfd813100d6065032bd92520
Author: latkin <latkin@microsoft.com>
Date:   Thu Feb 12 19:29:16 2015 -0800

    Output symbol info for locals

commit d6a0faac99bd33fec0c4be24d13009127b8ff420
Author: latkin <latkin@microsoft.com>
Date:   Thu Feb 12 18:00:14 2015 -0800

    Use same whitespace style as existing code

commit a4003c17a006d7eeda1c3920ad05aef788db846e
Author: latkin <latkin@microsoft.com>
Date:   Wed Feb 11 11:06:22 2015 -0800

    Add 'detach' item for tool window, and give 'attach'/'detach' smart visibility

commit c5a64605aca53cdfd742975225c8fa4e665b9f84
Author: latkin <latkin@microsoft.com>
Date:   Wed Feb 11 07:39:34 2015 -0800

    Enable basic script debugging
上级 959b10f9
......@@ -1185,7 +1185,8 @@ and ILFilterBlock =
[<NoComparison; NoEquality>]
type ILLocal =
{ Type: ILType;
IsPinned: bool }
IsPinned: bool;
DebugInfo: (string * int * int) option }
type ILLocals = ILList<ILLocal>
let emptyILLocals = (ILList.empty : ILLocals)
......@@ -3022,9 +3023,10 @@ let mkILReturn ty : ILReturn =
Type=ty;
CustomAttrs=emptyILCustomAttrs }
let mkILLocal ty =
let mkILLocal ty dbgInfo =
{ IsPinned=false;
Type=ty; }
Type=ty;
DebugInfo=dbgInfo }
type ILFieldSpec with
member fr.ActualType =
......
......@@ -970,7 +970,8 @@ type ILNativeType =
[<NoComparison; NoEquality>]
type ILLocal =
{ Type: ILType;
IsPinned: bool }
IsPinned: bool;
DebugInfo: (string * int * int) option }
type ILLocals = ILList<ILLocal>
......@@ -1955,7 +1956,7 @@ val mkILParam: string option * ILType -> ILParameter
val mkILParamAnon: ILType -> ILParameter
val mkILParamNamed: string * ILType -> ILParameter
val mkILReturn: ILType -> ILReturn
val mkILLocal: ILType -> ILLocal
val mkILLocal: ILType -> (string * int * int) option -> ILLocal
val mkILLocals : ILLocal list -> ILLocals
val emptyILLocals : ILLocals
......
......@@ -2206,7 +2206,8 @@ and sigptrGetLocal ctxt numtypars bytes sigptr =
false, sigptr
let typ, sigptr = sigptrGetTy ctxt numtypars bytes sigptr
{ IsPinned = pinned;
Type = typ }, sigptr
Type = typ;
DebugInfo = None }, sigptr
and readBlobHeapAsMethodSig ctxt numtypars blobIdx =
ctxt.readBlobHeapAsMethodSig (BlobAsMethodSigIdx (numtypars,blobIdx))
......
......@@ -1252,7 +1252,11 @@ let emitCode cenv modB emEnv (ilG:ILGenerator) code =
let emitLocal cenv emEnv (ilG : ILGenerator) (local: ILLocal) =
let ty = convType cenv emEnv local.Type
ilG.DeclareLocalAndLog(ty,local.IsPinned)
let locBuilder = ilG.DeclareLocalAndLog(ty, local.IsPinned)
match local.DebugInfo with
| Some(nm, start, finish) -> locBuilder.SetLocalSymInfo(nm, start, finish)
| None -> ()
locBuilder
let emitILMethodBody cenv modB emEnv (ilG:ILGenerator) ilmbody =
// XXX - REVIEW:
......
......@@ -733,7 +733,8 @@ type internal FsiDynamicCompilerState =
tcState : Build.TcState
ilxGenerator : Ilxgen.IlxAssemblyGenerator
// Why is this not in FsiOptions?
timing : bool }
timing : bool
debugBreak : bool }
let internal WithImplicitHome (tcConfigB, dir) f =
let old = tcConfigB.implicitIncludeDir
......@@ -986,13 +987,22 @@ type internal FsiDynamicCompiler
let mkBind pat expr = Binding (None, DoBinding, false, (*mutable*)false, [], PreXmlDoc.Empty, SynInfo.emptySynValData, pat, None, expr, m, NoSequencePointAtInvisibleBinding)
let bindingA = mkBind (mkSynPatVar None itID) expr (* let it = <expr> *) // NOTE: the generalizability of 'expr' must not be damaged, e.g. this can't be an application
let saverPath = ["Microsoft";"FSharp";"Compiler";"Interactive";"RuntimeHelpers";"SaveIt"]
let dots = List.replicate (saverPath.Length - 1) rangeStdin
let bindingB = mkBind (SynPat.Wild m) (SynExpr.App(ExprAtomicFlag.NonAtomic, false, SynExpr.LongIdent(false, LongIdentWithDots(List.map (mkSynId rangeStdin) saverPath,dots),None,m), itExp,m)) (* let _ = saverPath it *)
let dots = List.replicate (saverPath.Length - 1) m
let bindingB = mkBind (SynPat.Wild m) (SynExpr.App(ExprAtomicFlag.NonAtomic, false, SynExpr.LongIdent(false, LongIdentWithDots(List.map (mkSynId m) saverPath,dots),None,m), itExp,m)) (* let _ = saverPath it *)
let defA = SynModuleDecl.Let (false, [bindingA], m)
let defB = SynModuleDecl.Let (false, [bindingB], m)
[defA; defB]
// construct an invisible call to Debugger.Break(), in the specified range
member __.CreateDebuggerBreak (m : range) =
let breakPath = ["System";"Diagnostics";"Debugger";"Break"]
let dots = List.replicate (breakPath.Length - 1) m
let methCall = SynExpr.LongIdent(false, LongIdentWithDots(List.map (mkSynId m) breakPath, dots), None, m)
let args = SynExpr.Const(SynConst.Unit, m)
let breakStatement = SynExpr.App(ExprAtomicFlag.Atomic, false, methCall, args, m)
SynModuleDecl.DoExpr(SequencePointInfoForBinding.NoSequencePointAtDoBinding, breakStatement, m)
member __.EvalRequireReference istate m path =
if Path.IsInvalidPath(path) then
error(Error(FSIstrings.SR.fsiInvalidAssembly(path),m))
......@@ -1080,6 +1090,7 @@ type internal FsiDynamicCompiler
tcState = tcState;
ilxGenerator = ilxGenerator;
timing = false;
debugBreak = false;
}
......@@ -1619,7 +1630,10 @@ type internal FsiInteractionProcessor
| IHash (ParsedHashDirective("silentCd",[path],m),_) ->
ChangeDirectory path m;
fsiConsolePrompt.SkipNext(); (* "silent" directive *)
istate,Completed
istate,Completed
| IHash (ParsedHashDirective("dbgbreak",[],_),_) ->
{istate with debugBreak = true},Completed
| IHash (ParsedHashDirective("time",[],_),_) ->
if istate.timing then
......@@ -1678,19 +1692,37 @@ type internal FsiInteractionProcessor
/// #directive comes through with other definitions as a SynModuleDecl.HashDirective.
/// We split these out for individual processing.
let rec ExecInteractions (exitViaKillThread, tcConfig, istate, action:ParsedFsiInteraction option) =
let action,nextAction =
let action,nextAction,istate =
match action with
| None -> None ,None
| Some (IHash _) -> action,None
| Some (IDefns ([],_)) -> None ,None
| None -> None ,None,istate
| Some (IHash _) -> action,None,istate
| Some (IDefns ([],_)) -> None ,None,istate
| Some (IDefns (SynModuleDecl.HashDirective(hash,mh)::defs,m)) ->
Some (IHash(hash,mh)),Some (IDefns(defs,m))
Some (IHash(hash,mh)),Some (IDefns(defs,m)),istate
| Some (IDefns (defs,m)) ->
let isDefHash = function SynModuleDecl.HashDirective(_,_) -> true | _ -> false
let isBreakable def =
// only add automatic debugger breaks before 'let' or 'do' expressions with sequence points
match def with
| SynModuleDecl.DoExpr (SequencePointInfoForBinding.SequencePointAtBinding _, _, _)
| SynModuleDecl.Let (_, SynBinding.Binding(_, _, _, _, _, _, _, _ ,_ ,_ ,_ , SequencePointInfoForBinding.SequencePointAtBinding _) :: _, _) -> true
| _ -> false
let defsA = Seq.takeWhile (isDefHash >> not) defs |> Seq.toList
let defsB = Seq.skipWhile (isDefHash >> not) defs |> Seq.toList
// If user is debugging their script interactively, inject call
// to Debugger.Break() at the first "breakable" line.
// Update istate so that more Break() calls aren't injected when recursing
let defsA,istate =
if istate.debugBreak then
let preBreak = Seq.takeWhile (isBreakable >> not) defsA |> Seq.toList
let postBreak = Seq.skipWhile (isBreakable >> not) defsA |> Seq.toList
match postBreak with
| h :: _ -> preBreak @ (fsiDynamicCompiler.CreateDebuggerBreak(h.Range) :: postBreak), { istate with debugBreak = false }
| _ -> defsA, istate
else defsA,istate
// When the last declaration has a shape of DoExp (i.e., non-binding),
// transform it to a shape of "let it = <exp>", so we can refer it.
let defsA = if defsA.Length <= 1 || defsB.Length > 0 then defsA else
......@@ -1698,7 +1730,7 @@ type internal FsiInteractionProcessor
| SynModuleDecl.DoExpr(_,exp,_), rest -> (rest |> List.rev) @ (fsiDynamicCompiler.BuildItBinding exp)
| _ -> defsA
Some (IDefns(defsA,m)),Some (IDefns(defsB,m))
Some (IDefns(defsA,m)),Some (IDefns(defsB,m)),istate
match action with
| None -> assert(nextAction.IsNone); istate,Completed
......
......@@ -1534,7 +1534,7 @@ let discardAndReturnVoid = DiscardThen ReturnVoid
// the bodies of methods in a couple of places
//-------------------------------------------------------------------------
let CodeGenThen mgbuf (zapFirstSeqPointToStart,entryPointInfo,methodName,eenv,alreadyUsedArgs,alreadyUsedLocals,codeGenFunction,m) =
let CodeGenThen cenv mgbuf (zapFirstSeqPointToStart,entryPointInfo,methodName,eenv,alreadyUsedArgs,alreadyUsedLocals,codeGenFunction,m) =
let cgbuf = new CodeGenBuffer(m,mgbuf,methodName,alreadyUsedArgs,alreadyUsedLocals,zapFirstSeqPointToStart)
let start = CG.GenerateMark cgbuf "mstart"
let innerVals = entryPointInfo |> List.map (fun (v,kind) -> (v,(kind,start)))
......@@ -1554,7 +1554,21 @@ let CodeGenThen mgbuf (zapFirstSeqPointToStart,entryPointInfo,methodName,eenv,al
{ locRange=(start.CodeLabel, finish.CodeLabel);
locInfos= [{ LocalIndex=i; LocalName=nm }] })
(List.map (snd >> mkILLocal) locals,
let ilLocals =
locals
|> List.map (fun (infos, ty) ->
// in interactive environment, attach name and range info to locals to improve debug experience
if cenv.opts.isInteractive && cenv.opts.generateDebugSymbols then
match infos with
| [(nm, (start, finish))] -> mkILLocal ty (Some(nm, start.CodeLabel, finish.CodeLabel))
// REVIEW: what do these cases represent?
| _ :: _
| [] -> mkILLocal ty None
// if not interactive, don't bother adding this info
else
mkILLocal ty None)
(ilLocals,
maxStack,
computeCodeLabelToPC,
code,
......@@ -1566,7 +1580,7 @@ let CodeGenMethod cenv mgbuf (zapFirstSeqPointToStart,entryPointInfo,methodName,
(* Codegen the method. REVIEW: change this to generate the AbsIL code tree directly... *)
let locals,maxStack,computeCodeLabelToPC,instrs,exns,localDebugSpecs,hasSequencePoints =
CodeGenThen mgbuf (zapFirstSeqPointToStart,entryPointInfo,methodName,eenv,alreadyUsedArgs,alreadyUsedLocals,codeGenFunction,m)
CodeGenThen cenv mgbuf (zapFirstSeqPointToStart,entryPointInfo,methodName,eenv,alreadyUsedArgs,alreadyUsedLocals,codeGenFunction,m)
let dump() =
instrs |> Array.iteri (fun i instr -> dprintf "%s: %d: %A\n" methodName i instr);
......
......@@ -733,6 +733,7 @@ type internal LineTokenizer(text:string,
| true,"I"
| true,"load"
| true,"time"
| true,"dbgbreak"
| true,"cd"
#if DEBUG
| true,"terms"
......
......@@ -377,7 +377,7 @@ let rec convInstr cenv (tmps: ILLocalsAllocator) inplab outlab instr =
InstrMorph [ AI_pop; (AI_ldc (DT_I4, ILConst.I4 0)) ]
| RuntimeTypes ->
let baseTy = baseTyOfUnionSpec cuspec
let locn = tmps.AllocLocal (mkILLocal baseTy)
let locn = tmps.AllocLocal (mkILLocal baseTy None)
let mkCase last inplab cidx failLab =
let alt = altOfUnionSpec cuspec cidx
......@@ -495,7 +495,7 @@ let rec convInstr cenv (tmps: ILLocalsAllocator) inplab outlab instr =
match cuspecRepr.DiscriminationTechnique cuspec with
| RuntimeTypes ->
let locn = tmps.AllocLocal (mkILLocal baseTy)
let locn = tmps.AllocLocal (mkILLocal baseTy None)
let mkCase _last inplab (cidx,tg) failLab =
let alt = altOfUnionSpec cuspec cidx
let altTy = tyForAlt cuspec alt
......
......@@ -226,7 +226,7 @@ let rec convInstr cenv (tmps: ILLocalsAllocator, thisGenParams: ILGenericParamet
| Apps_app (arg,rest) ->
let storers, loaders = unwind rest
let argStorers,argLoaders =
let locn = tmps.AllocLocal (mkILLocal arg)
let locn = tmps.AllocLocal (mkILLocal arg None)
[mkStloc locn], [mkLdloc locn]
argStorers :: storers, argLoaders :: loaders
| Apps_done _ ->
......@@ -348,7 +348,7 @@ let mkILFreeVarForParam (p : ILParameter) =
let nm = (match p.Name with Some x -> x | None -> failwith "closure parameters must be given names")
mkILFreeVar(nm, false,p.Type)
let mkILLocalForFreeVar (p: IlxClosureFreeVar) = mkILLocal p.fvType
let mkILLocalForFreeVar (p: IlxClosureFreeVar) = mkILLocal p.fvType None
let mkILCloFldSpecs _cenv flds =
flds |> Array.map (fun fv -> (fv.fvName,fv.fvType)) |> Array.toList
......
......@@ -64,16 +64,20 @@ public class ViewFilter : IVsTextViewFilter, IVsTextViewEvents, IOleCommandTarge
private IntPtr pvaChar;
private bool gotEnterKey;
private bool snippetBound;
private VsCommands gotoCmd;
private VsCommands gotoCmd;
private readonly Guid guidInteractive = new Guid("8B9BF77B-AF94-4588-8847-2EB2BFFD29EB");
private readonly uint cmdIDDebugSelection = 0x01;
/// <include file='doc\ViewFilter.uex' path='docs/doc[@for="ViewFilter.SnippetBound"]/*' />
protected bool SnippetBound {
get { return snippetBound; }
set { snippetBound = value; }
}
private NativeMethods.ConnectionPointCookie expansionEvents;
#if FX_ATLEAST_45
private Microsoft.VisualStudio.Shell.Package projectSystemPackage = null;
private Microsoft.VisualStudio.Shell.Package GetProjectSystemPackage()
{
// Ideally the FsiToolWindow would be a part of the language service, but right now its code lives in the
......@@ -89,7 +93,7 @@ private Microsoft.VisualStudio.Shell.Package GetProjectSystemPackage()
}
return this.projectSystemPackage;
}
#endif
/// <include file='doc\ViewFilter.uex' path='docs/doc[@for="ViewFilter.ViewFilter"]/*' />
internal ViewFilter(CodeWindowManager mgr, IVsTextView view) {
this.pvaChar = IntPtr.Zero;
......@@ -204,16 +208,16 @@ private Microsoft.VisualStudio.Shell.Package GetProjectSystemPackage()
get { return this.textView; }
}
/// <include file='doc\ExpansionProvider.uex' path='docs/doc[@for="ViewFilter.IsExpansionUIActive"]/*' />
public virtual bool IsExpansionUIActive {
get {
IVsTextViewEx tve = this.textView as IVsTextViewEx;
if (tve != null && tve.IsExpansionUIActive() == VSConstants.S_OK) {
return true;
}
return false;
}
}
/// <include file='doc\ExpansionProvider.uex' path='docs/doc[@for="ViewFilter.IsExpansionUIActive"]/*' />
public virtual bool IsExpansionUIActive {
get {
IVsTextViewEx tve = this.textView as IVsTextViewEx;
if (tve != null && tve.IsExpansionUIActive() == VSConstants.S_OK) {
return true;
}
return false;
}
}
#region IVsTextViewFilter methods
/// <include file='doc\ViewFilter.uex' path='docs/doc[@for="ViewFilter.GetWordExtent"]/*' />
......@@ -344,79 +348,88 @@ internal void GetDataTipResponse(BackgroundRequest req)
/// OLECMDF_ENABLED | OLECMDF_SUPPORTED.
/// Return E_FAIL if want to delegate to the next command target.
/// </returns>
protected virtual int QueryCommandStatus(ref Guid guidCmdGroup, uint nCmdId) {
protected virtual int QueryCommandStatus(ref Guid guidCmdGroup, uint nCmdId)
{
ExpansionProvider ep = GetExpansionProvider();
if (ep != null && ep.InTemplateEditingMode) {
if (ep != null && ep.InTemplateEditingMode)
{
int hr = 0;
if (ep.HandleQueryStatus(ref guidCmdGroup, nCmdId, out hr))
return hr;
}
if (guidCmdGroup == typeof(VsCommands).GUID) {
if (guidCmdGroup == typeof(VsCommands).GUID)
{
VsCommands cmd = (VsCommands)nCmdId;
switch (cmd) {
case VsCommands.GotoDefn:
case VsCommands.GotoDecl:
case VsCommands.GotoRef:
case VsCommands.Goto:
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
switch (cmd)
{
case VsCommands.GotoDefn:
case VsCommands.GotoDecl:
case VsCommands.GotoRef:
case VsCommands.Goto:
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
}
} else if (guidCmdGroup == typeof(VsCommands2K).GUID) {
}
else if (guidCmdGroup == typeof(VsCommands2K).GUID)
{
VsCommands2K cmd = (VsCommands2K)nCmdId;
switch (cmd) {
case VsCommands2K.FORMATDOCUMENT:
if (this.CanReformat())
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
break;
case VsCommands2K.FORMATSELECTION:
if (this.CanReformat())
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
break;
case VsCommands2K.COMMENT_BLOCK:
case VsCommands2K.UNCOMMENT_BLOCK:
if (this.commentSupported)
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
break;
case VsCommands2K.SHOWMEMBERLIST:
case VsCommands2K.COMPLETEWORD:
case VsCommands2K.PARAMINFO:
switch (cmd)
{
case VsCommands2K.FORMATDOCUMENT:
if (this.CanReformat())
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
break;
case VsCommands2K.FORMATSELECTION:
if (this.CanReformat())
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
break;
case VsCommands2K.QUICKINFO:
if (this.service.Preferences.EnableQuickInfo) {
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
}
break;
case VsCommands2K.COMMENT_BLOCK:
case VsCommands2K.UNCOMMENT_BLOCK:
if (this.commentSupported)
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
break;
// case VsCommands2K.HANDLEIMEMESSAGE:
// return 0;
// Let the core editor handle this. Stop outlining also removes user
// defined hidden sections so it is handy to keep this enabled.
// case VsCommands2K.OUTLN_STOP_HIDING_ALL:
// int rc = (int)OLECMDF.OLECMDF_SUPPORTED;
// if (this.source.OutliningEnabled) {
// rc |= (int)OLECMDF.OLECMDF_ENABLED;
// }
// return rc;
case VsCommands2K.SHOWMEMBERLIST:
case VsCommands2K.COMPLETEWORD:
case VsCommands2K.PARAMINFO:
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
case VsCommands2K.OUTLN_START_AUTOHIDING:
if (this.source.OutliningEnabled) {
return (int)OleConstants.OLECMDERR_E_NOTSUPPORTED;
}
case VsCommands2K.QUICKINFO:
if (this.service.Preferences.EnableQuickInfo)
{
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
case VsCommands2K.OUTLN_STOP_HIDING_ALL: //"stop outlining" on context menu
if (this.source.OutliningEnabled) {
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
}
}
break;
// case VsCommands2K.HANDLEIMEMESSAGE:
// return 0;
// Let the core editor handle this. Stop outlining also removes user
// defined hidden sections so it is handy to keep this enabled.
// case VsCommands2K.OUTLN_STOP_HIDING_ALL:
// int rc = (int)OLECMDF.OLECMDF_SUPPORTED;
// if (this.source.OutliningEnabled) {
// rc |= (int)OLECMDF.OLECMDF_ENABLED;
// }
// return rc;
case VsCommands2K.OUTLN_START_AUTOHIDING:
if (this.source.OutliningEnabled)
{
return (int)OleConstants.OLECMDERR_E_NOTSUPPORTED;
}
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
case VsCommands2K.OUTLN_STOP_HIDING_ALL: //"stop outlining" on context menu
if (this.source.OutliningEnabled)
{
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
}
return (int)OleConstants.OLECMDERR_E_NOTSUPPORTED;
}
}
#if FX_ATLEAST_45
else if (guidCmdGroup == Microsoft.VisualStudio.VSConstants.VsStd11)
{
if (nCmdId == (uint)Microsoft.VisualStudio.VSConstants.VSStd11CmdID.ExecuteSelectionInInteractive)
......@@ -424,7 +437,19 @@ internal void GetDataTipResponse(BackgroundRequest req)
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
}
}
#endif
else if (guidCmdGroup == guidInteractive)
{
if (nCmdId == cmdIDDebugSelection)
{
var dbgState = Interactive.Hooks.GetDebuggerState(GetProjectSystemPackage());
if (dbgState == Interactive.FsiDebuggerState.AttachedNotToFSI)
return (int)OLECMDF.OLECMDF_INVISIBLE;
else
return (int)OLECMDF.OLECMDF_SUPPORTED | (int)OLECMDF.OLECMDF_ENABLED;
}
}
return (int)NativeMethods.E_FAIL; // delegate to next command target.
}
......@@ -541,16 +566,23 @@ internal void GetDataTipResponse(BackgroundRequest req)
}
}
#if FX_ATLEAST_45
else if (guidCmdGroup == Microsoft.VisualStudio.VSConstants.VsStd11)
{
if (nCmdId == (uint)Microsoft.VisualStudio.VSConstants.VSStd11CmdID.ExecuteSelectionInInteractive)
{
Microsoft.VisualStudio.FSharp.Interactive.Hooks.OnMLSend(GetProjectSystemPackage(), null, null);
Interactive.Hooks.OnMLSend(GetProjectSystemPackage(), false, null, null);
return true;
}
}
#endif
else if (guidCmdGroup == guidInteractive)
{
if (nCmdId == cmdIDDebugSelection)
{
Interactive.Hooks.OnMLSend(GetProjectSystemPackage(), true, null, null);
return true;
}
}
return false;
}
......
......@@ -42,30 +42,22 @@ module internal Guids =
#endif
// FSI Session command set
let cmdIDFsiConsoleContextMenu = 0x2100
let guidFsiConsoleCmdSet = Guid("0E455B35-F2EB-431b-A0BE-B268D8A7D17F")
#if FX_ATLEAST_45
let guidInteractiveCommands = Microsoft.VisualStudio.VSConstants.VsStd11
let cmdIDSessionInterrupt = int Microsoft.VisualStudio.VSConstants.VSStd11CmdID.InteractiveSessionInterrupt
let cmdIDSessionRestart = int Microsoft.VisualStudio.VSConstants.VSStd11CmdID.InteractiveSessionRestart
#else
let guidInteractiveCommands = guidFsiConsoleCmdSet
let cmdIDSessionInterrupt = 0x102
let cmdIDSessionRestart = 0x103
#endif
let guidFsiConsoleCmdSet = Guid("0E455B35-F2EB-431b-A0BE-B268D8A7D17F")
let cmdIDAttachDebugger = 0x104
let cmdIDDetachDebugger = 0x105
let cmdIDFsiConsoleContextMenu = 0x2100
// Command set for SendToInteractive
#if FX_ATLEAST_45
// commands moved to VS Shell
let guidInteractive = Microsoft.VisualStudio.VSConstants.VsStd11
// some commands moved to VS Shell
let guidInteractiveShell = Microsoft.VisualStudio.VSConstants.VsStd11
let cmdIDSendSelection = int Microsoft.VisualStudio.VSConstants.VSStd11CmdID.ExecuteSelectionInInteractive
let guidInteractive2 = Microsoft.VisualStudio.VSConstants.VsStd11
#else
// hybrid still uses own commands
// some commands not in VS Shell
let guidInteractive = Guid("8B9BF77B-AF94-4588-8847-2EB2BFFD29EB")
let cmdIDSendSelection = 0x01
let guidInteractive2 = Guid("B607E86C-A761-4685-8D98-71A3BB73233A")
#endif
let cmdIDDebugSelection = 0x01
let guidFsiPackage = "eeeeeeee-9342-42f1-8ea9-42f0e8a6be55" // FSI-LINKAGE-POINT: when packaged here
let guidFSharpProjectPkgString = "91A04A73-4F2C-4E7C-AD38-C1A68E7DA05C" // FSI-LINKAGE-POINT: when packaged in project system
......
......@@ -92,43 +92,37 @@
</Strings>
</Button>
<!-- In Dev11, shell now has
<!-- In Dev11+, shell now has
<Button guid ="guidVSStd11" id ="cmdidInteractiveSessionInterrupt" priority ="0x100" type ="Button">
<Button guid ="guidVSStd11" id ="cmdidInteractiveSessionRestart" priority ="0x105" type ="Button">
-->
<!-- In Dev10 hybrid, we need buttons below -->
<Button Condition="!Defined(FX_ATLEAST_45)" guid="guidFsiConsoleCmdSet" id="cmdidSessionInterrupt" priority="0x0100" type="Button">
<Parent guid="guidFsiConsoleCmdSet" id="IDG_VS_WNDO_OTRWNDWS1"/>
<!-- Icon guid="guidImages" id="bmpPic2" /-->
<Icon guid="guidCancelEvaluationBmp" id="bmpConsole" />
<Button guid="guidFsiConsoleCmdSet" id="cmdidAttachDebugger" priority="0x0100" type="Button">
<Strings>
<CommandName>FSharp.Interactive.Interrupt</CommandName>
<ButtonText>Cancel Evaluation</ButtonText> <!-- This was called "Interrupt Session" -->
<CommandName>FSharp.Interactive.AttachDebugger</CommandName>
<ButtonText>Start Debugging</ButtonText>
</Strings>
<CommandFlag>DynamicVisibility | DefaultInvisible</CommandFlag>
</Button>
<Button Condition="!Defined(FX_ATLEAST_45)" guid="guidFsiConsoleCmdSet" id="cmdidSessionRestart" priority="0x0100" type="Button">
<Parent guid="guidFsiConsoleCmdSet" id="IDG_VS_WNDO_OTRWNDWS1"/>
<!-- Icon guid="guidImages" id="bmpPic2" /-->
<Icon guid="guidResetSessionBmp" id="bmpConsole" />
<Button guid="guidFsiConsoleCmdSet" id="cmdidDetachDebugger" priority="0x0101" type="Button">
<Strings>
<CommandName>FSharp.Interactive.Restart</CommandName>
<ButtonText>Reset Session</ButtonText>
<CommandName>FSharp.Interactive.DetachDebugger</CommandName>
<ButtonText>Stop Debugging</ButtonText>
</Strings>
<CommandFlag>DynamicVisibility | DefaultInvisible</CommandFlag>
</Button>
<!-- The following places a button on the F# Editor Context Menu -->
<!-- In Dev11, shell now has
<!-- In Dev11+, shell now has
<Button guid ="guidVSStd11" id ="cmdidExecuteSelectionInInteractive" priority ="0x100" type ="Button">
-->
<!-- In Dev10 hybrid, we need buttons below -->
<Button Condition="!Defined(FX_ATLEAST_45)" guid ="guidInteractive" id ="cmdidSendSelection" priority ="0x100" type ="Button">
<Parent guid="guidSHLMainMenu" id="IDG_VS_CODEWIN_LANGUAGE"/>
<Icon guid="guidFsiConsoleBmp" id="bmpConsole"/>
<Button guid ="guidInteractive" id ="cmdidDebugSelection" priority ="0x106" type ="Button">
<Parent guid="guidSHLMainMenu" id="IDG_VS_CODEWIN_LANGUAGE"/>
<Strings>
<ButtonText>Send To Interactive</ButtonText>
<CommandName>Interactive.Send.Selection.Context</CommandName>
<ButtonText>Debug in F# Interactive</ButtonText>
<CommandName>Interactive.Debug.Selection.Context</CommandName>
</Strings>
<CommandFlag>DynamicVisibility | DefaultInvisible</CommandFlag>
<CommandFlag>DynamicVisibility | DefaultInvisible</CommandFlag>
</Button>
</Buttons>
......@@ -177,20 +171,21 @@
<CommandPlacement guid="guidVSStd97" id="cmdidClearPane" priority="0x0200">
<Parent guid="guidFsiConsoleCmdSet" id="FsiConsoleClearGrp"/>
</CommandPlacement>
<!-- Context menu, session group: Hybrid -->
<CommandPlacement Condition="!Defined(FX_ATLEAST_45)" guid="guidFsiConsoleCmdSet" id="cmdidSessionInterrupt" priority="0x0100">
<!-- Context menu, session group -->
<CommandPlacement guid="guidVSStd11" id="cmdidInteractiveSessionInterrupt" priority="0x0100">
<Parent guid="guidFsiConsoleCmdSet" id="FsiConsoleSessionsGrp"/>
</CommandPlacement>
<CommandPlacement Condition="!Defined(FX_ATLEAST_45)" guid="guidFsiConsoleCmdSet" id="cmdidSessionRestart" priority="0x0300">
<CommandPlacement guid="guidVSStd11" id="cmdidInteractiveSessionRestart" priority="0x0300">
<Parent guid="guidFsiConsoleCmdSet" id="FsiConsoleSessionsGrp"/>
</CommandPlacement>
<!-- Context menu, session group: Dev11 -->
<CommandPlacement Condition="Defined(FX_ATLEAST_45)" guid="guidVSStd11" id="cmdidInteractiveSessionInterrupt" priority="0x0100">
<CommandPlacement guid="guidFsiConsoleCmdSet" id="cmdidAttachDebugger" priority="0x0700">
<Parent guid="guidFsiConsoleCmdSet" id="FsiConsoleSessionsGrp"/>
</CommandPlacement>
<CommandPlacement Condition="Defined(FX_ATLEAST_45)" guid="guidVSStd11" id="cmdidInteractiveSessionRestart" priority="0x0300">
<CommandPlacement guid="guidFsiConsoleCmdSet" id="cmdidDetachDebugger" priority="0x0800">
<Parent guid="guidFsiConsoleCmdSet" id="FsiConsoleSessionsGrp"/>
</CommandPlacement>
<!-- Adds MLSend to the context menu:
<CommandPlacement guid="guidFsiConsoleCmdSet" id="cmdidMLSendSelection" priority="0x0500">
<Parent guid="guidFsiConsoleCmdSet" id="FsiConsoleSessionsGrp"/>
......@@ -226,24 +221,27 @@
ALT-ENTER is globally bound to Diagram.Property.
Here we bind it in the Editor context of the standard TextEditor.
Ideally, we would bind it for F# only editor.
Both Hybrid and Dev11 are used here, to build both ways.
-->
<KeyBinding Condition="!Defined(FX_ATLEAST_45)" guid="guidInteractive" id="cmdidSendSelection" editor="GUID_TextEditorFactory" key1="VK_RETURN" mod1="Alt" />
<KeyBinding Condition="Defined(FX_ATLEAST_45)" guid ="guidVSStd11" id ="cmdidExecuteSelectionInInteractive" editor="GUID_TextEditorFactory" key1="VK_RETURN" mod1="Alt" />
<KeyBinding guid ="guidInteractive" id ="cmdidDebugSelection" editor="GUID_TextEditorFactory" key1="D" mod1="Alt" key2="VK_RETURN" mod2="Alt" />
<KeyBinding guid ="guidVSStd11" id ="cmdidExecuteSelectionInInteractive" editor="GUID_TextEditorFactory" key1="VK_RETURN" mod1="Alt" />
<!-- CRTL-ALT-F for FSI window - following similar bindings for "other windows" -->
<KeyBinding guid="guidFsiPackageCmdSet" id="cmdidFsiToolWindow" editor="guidVSStd97" key1="F" mod1="Control Alt" />
<!-- CRTL-Break when in FSI ToolWindow is Interrupt -->
<KeyBinding Condition="!Defined(FX_ATLEAST_45)" guid="guidFsiConsoleCmdSet" id="cmdidSessionInterrupt" editor="guidFsiToolWindow" key1="VK_CANCEL" mod1="Control" />
<KeyBinding Condition="Defined(FX_ATLEAST_45)" guid="guidVSStd11" id="cmdidInteractiveSessionInterrupt" editor="guidFsiToolWindow" key1="VK_CANCEL" mod1="Control" />
<!-- CRTL-Break when in FSI ToolWindow is Interrupt -->
<KeyBinding guid="guidVSStd11" id="cmdidInteractiveSessionInterrupt" editor="guidFsiToolWindow" key1="VK_CANCEL" mod1="Control" />
<!-- CRTL-Alt-R when in FSI ToolWindow is Reset -->
<KeyBinding Condition="!Defined(FX_ATLEAST_45)" guid="guidFsiConsoleCmdSet" id="cmdidSessionRestart" editor="guidFsiToolWindow" key1="R" mod1="Control Alt" />
<KeyBinding Condition="Defined(FX_ATLEAST_45)" guid="guidVSStd11" id="cmdidInteractiveSessionRestart" editor="guidFsiToolWindow" key1="R" mod1="Control Alt" />
<!-- CRTL-Alt-R when in FSI ToolWindow is Reset -->
<KeyBinding guid="guidVSStd11" id="cmdidInteractiveSessionRestart" editor="guidFsiToolWindow" key1="R" mod1="Control Alt" />
<!-- CRTL-Alt-C when in FSI ToolWindow is Clear All -->
<KeyBinding guid="guidVSStd97" id="cmdidClearPane" editor="guidFsiToolWindow" key1="C" mod1="Control Alt" />
<!-- CRTL-Alt-D when in FSI ToolWindow is attach debugger -->
<KeyBinding guid="guidFsiConsoleCmdSet" id="cmdidAttachDebugger" editor="guidFsiToolWindow" key1="D" mod1="Control Alt" />
<!-- CRTL-Shift-D when in FSI ToolWindow is detach debugger -->
<KeyBinding guid="guidFsiConsoleCmdSet" id="cmdidDetachDebugger" editor="guidFsiToolWindow" key1="D" mod1="Control Shift" />
</KeyBindings>
<Symbols>
......@@ -279,9 +277,8 @@
<IDSymbol name="FsiConsoleClearGrp" value="0x1040" />
<IDSymbol name="FsiConsoleSessionsGrp" value="0x1050" />
<IDSymbol name="cmdidFsiConsole" value="0x101" />
<!-- below is only used by hybrid -->
<IDSymbol Condition="!Defined(FX_ATLEAST_45)" name="cmdidSessionInterrupt" value="0x102" />
<IDSymbol Condition="!Defined(FX_ATLEAST_45)" name="cmdidSessionRestart" value="0x103" />
<IDSymbol name="cmdidAttachDebugger" value="0x104" />
<IDSymbol name="cmdidDetachDebugger" value="0x105" />
</GuidSymbol>
<GuidSymbol name="guidFsiConsoleBmp" value="{9074CE8B-8F1E-4c23-8EDC-82C25E0323A8}" >
......@@ -301,12 +298,11 @@
<IDSymbol name="cmdidInteractiveSessionInterrupt" value ="0x01A"/>
<IDSymbol name="cmdidInteractiveSessionRestart" value ="0x01B"/>
</GuidSymbol>
<!-- below is only used by hybrid -->
<GuidSymbol Condition="!Defined(FX_ATLEAST_45)" name="guidInteractive" value="{8B9BF77B-AF94-4588-8847-2EB2BFFD29EB}" >
<IDSymbol name="cmdidSendSelection" value ="0x01"/>
</GuidSymbol>
<GuidSymbol name="guidInteractive" value="{8B9BF77B-AF94-4588-8847-2EB2BFFD29EB}" >
<IDSymbol name="cmdidDebugSelection" value ="0x01"/>
</GuidSymbol>
</Symbols>
</CommandTable>
......
......@@ -56,25 +56,34 @@ module internal Hooks =
with e2 ->
(System.Windows.Forms.MessageBox.Show(e2.ToString()) |> ignore)
let private withFSIToolWindow (this:Package) f =
let private queryFSIToolWindow (this:Package) (f : FsiToolWindow -> 't) (dflt : 't) =
try
let window = this.FindToolWindow(typeof<FsiToolWindow>, 0, true)
let windowFrame = window.Frame :?> IVsWindowFrame
if windowFrame.IsVisible() <> VSConstants.S_OK then
windowFrame.Show() |> throwOnFailure0
match window with
| null -> ()
| :? FsiToolWindow as window -> f window
| _ -> ()
| _ -> dflt
with e2 ->
(System.Windows.Forms.MessageBox.Show(VFSIstrings.SR.exceptionRaisedWhenRequestingToolWindow(e2.ToString())) |> ignore)
dflt
let private withFSIToolWindow (this:Package) f =
queryFSIToolWindow this f ()
let OnMLSend (this:Package) (sender:obj) (e:EventArgs) =
withFSIToolWindow this (fun window -> window.MLSend(sender, e))
let OnMLSend (this:Package) (debug : bool) (sender:obj) (e:EventArgs) =
withFSIToolWindow this (fun window ->
if debug then window.MLDebug(sender, e)
else window.MLSend(sender, e)
)
let AddReferencesToFSI (this:Package) references =
withFSIToolWindow this (fun window -> window.AddReferences references)
let GetDebuggerState (this:Package) =
queryFSIToolWindow this (fun window -> window.GetDebuggerState()) FsiDebuggerState.AttachedNotToFSI
// FxCop request this function not be public
let private supportWhenFSharpDocument (sender:obj) (e:EventArgs) =
let command = sender :?> OleMenuCommand
......@@ -124,16 +133,3 @@ module internal Hooks =
let id = new CommandID(Guids.guidFsiPackageCmdSet,int32 Guids.cmdIDLaunchFsiToolWindow)
let cmd = new MenuCommand(new EventHandler(ShowToolWindow this), id)
commandService.AddCommand(cmd)
#if FX_ATLEAST_45
// Dev11 handles FSI commands in LS ViewFilter
#else
// See VS SDK docs on "Command Routing Algorithm".
// Add OLECommand to OleCommandTarget at the package level,
// for when it is fired from other contexts, e.g. text editor.
let id = new CommandID(Guids.guidInteractive,int32 Guids.cmdIDSendSelection)
let cmd = new OleMenuCommand(new EventHandler(OnMLSend this), id)
cmd.BeforeQueryStatus.AddHandler(new EventHandler(supportWhenFSharpDocument))
commandService.AddCommand(cmd)
#endif
......@@ -70,6 +70,12 @@ module internal Locals =
open Util
open Locals
// consumed by C#, so enum type used instead of union
type internal FsiDebuggerState =
| NotRunning = 0
| AttachedToFSI = 1
| AttachedNotToFSI = 2
[<Guid("dee22b65-9761-4a26-8fb2-759b971d6dfc")>] //REVIEW: double check fresh guid! IIRC it is.
type internal FsiToolWindow() as this =
inherit ToolWindowPane(null)
......@@ -431,6 +437,63 @@ type internal FsiToolWindow() as this =
let showNoActivate() =
let frame = this.Frame :?> IVsWindowFrame
frame.ShowNoActivate() |> ignore
let getDebuggerState () =
let fsiProcId = sessions.ProcessID
let dte = provider.GetService(typeof<DTE>) :?> DTE
if dte.Debugger.DebuggedProcesses = null || dte.Debugger.DebuggedProcesses.Count = 0 then
FsiDebuggerState.NotRunning, None
else
let debuggedFsi =
dte.Debugger.DebuggedProcesses
|> Seq.cast<Process>
|> Seq.tryFind (fun p -> p.ProcessID = fsiProcId)
match debuggedFsi with
| Some _ -> FsiDebuggerState.AttachedToFSI, debuggedFsi
| None -> FsiDebuggerState.AttachedNotToFSI, None
let getDebugAttachedFSIProcess () =
match getDebuggerState () with
| FsiDebuggerState.AttachedToFSI, opt -> opt
| _ -> None
let debuggerIsRunning () =
match getDebuggerState () with
| FsiDebuggerState.NotRunning, _ -> false
| _ -> true
// noop if debugger isn't attached to FSI
let detachDebugger () =
try
match getDebugAttachedFSIProcess () with
| Some(p) -> p.Detach(true)
| _ -> ()
with _ -> ()
// noop if debugger is already running
let attachDebugger () =
if not (debuggerIsRunning ()) then
let fsiProcId = sessions.ProcessID
let dte = provider.GetService(typeof<DTE>) :?> DTE
let fsiProc =
if dte.Debugger.LocalProcesses = null then None else
dte.Debugger.LocalProcesses
|> Seq.cast<Process>
|> Seq.tryFind (fun p -> p.ProcessID = fsiProcId)
try
match fsiProc with
| Some(p) -> p.Attach()
| _ -> ()
with _ -> ()
let onAttachDebugger (sender:obj) (args:EventArgs) =
attachDebugger()
showNoActivate()
let onDetachDebugger (sender:obj) (args:EventArgs) =
detachDebugger()
showNoActivate()
let sendTextToFSI text =
try
......@@ -440,15 +503,20 @@ type internal FsiToolWindow() as this =
executeTextNoHistory text
with _ -> ()
let executeInteraction dir filename topLine text =
let executeInteraction dbgBreak dir filename topLine text =
// Preserving previous functionality, including the #directives...
let directiveA = sprintf "# silentCd @\"%s\" ;; " dir
let directiveB = sprintf "# %d @\"%s\" " topLine filename
let directiveC = sprintf "# 1 \"stdin\"" (* stdin line number reset code *)
let interaction = "\n" + directiveA + "\n" + directiveB + "\n" + text + "\n" + directiveC + "\n;;\n"
let interaction =
"\n"
+ (sprintf "# silentCd @\"%s\" ;; " dir) + "\n"
+ (if dbgBreak then "# dbgbreak\n" else "")
+ (sprintf "# %d @\"%s\" " topLine filename) + "\n"
+ text + "\n"
+ "# 1 \"stdin\"" + "\n" (* stdin line number reset code *)
+ ";;" + "\n"
executeTextNoHistory interaction
let sendSelectionToFSI() =
let sendSelectionToFSI dbgBreak =
try
// REVIEW: See supportWhenFSharpDocument for alternative way of obtaining selection, via IVs APIs.
// Change post CTP.
......@@ -458,13 +526,13 @@ type internal FsiToolWindow() as this =
| :? TextSelection as selection when selection.Text = "" ->
selection.SelectLine()
showNoActivate()
executeInteraction (System.IO.Path.GetDirectoryName(activeD.FullName)) activeD.FullName selection.TopLine selection.Text
executeInteraction dbgBreak (System.IO.Path.GetDirectoryName(activeD.FullName)) activeD.FullName selection.TopLine selection.Text
// This has the effect of moving the line and de-selecting it.
selection.LineDown(false, 0)
selection.StartOfLine(vsStartOfLineOptions.vsStartOfLineOptionsFirstColumn, false)
| :? TextSelection as selection ->
showNoActivate()
executeInteraction (System.IO.Path.GetDirectoryName(activeD.FullName)) activeD.FullName selection.TopLine selection.Text
executeInteraction dbgBreak (System.IO.Path.GetDirectoryName(activeD.FullName)) activeD.FullName selection.TopLine selection.Text
| _ ->
()
with
......@@ -473,22 +541,12 @@ type internal FsiToolWindow() as this =
// Example errors include no active document.
let onMLSend (sender:obj) (e:EventArgs) =
sendSelectionToFSI()
(*
// Remove: after next submit (passing through SD)
// The below did not work, so move to use Automatic API via DTE above...
let vsTextManager = Util.CreateObjectT<VsTextManagerClass,VsTextManager> provider
let res,view = vsTextManager.GetActiveView(0(*<--fMustHaveFocus=0/1*),null) //
if res = VSConstants.S_OK then
let span = Array.zeroCreate<TextSpan> 1
view.GetSelectionSpan(span) |> throwOnFailure0
let span = span.[0]
let text = view.GetTextStream(span.iStartLine,span.iStartIndex,span.iEndLine,span.iEndIndex) |> throwOnFailure1
Windows.Forms.MessageBox.Show("EXEC:\n" + text) |> ignore
else
Windows.Forms.MessageBox.Show("Could not find the 'active text view', error code = " + sprintf "0x%x" res) |> ignore
*)
sendSelectionToFSI false
let onMLDebug (sender:obj) (e:EventArgs) =
attachDebugger ()
sendSelectionToFSI true
/// Handle UP and DOWN. Cycle history.
let onHistory (sender:obj) (e:EventArgs) =
let command = sender :?> OleMenuCommand
......@@ -526,6 +584,12 @@ type internal FsiToolWindow() as this =
do this.Caption <- VFSIstrings.SR.fsharpInteractive()
member this.MLSend(obj,e) = onMLSend obj e
member this.MLDebug(obj,e) = onMLDebug obj e
member this.GetDebuggerState() =
let (state, _) = getDebuggerState ()
state
member this.AddReferences(references : string[]) =
let text =
references
......@@ -594,8 +658,11 @@ type internal FsiToolWindow() as this =
addCommand guidVSStd2KCmdID (int32 VSStd2KCmdID.SHOWCONTEXTMENU) showContextMenu None
addCommand Guids.guidInteractiveCommands Guids.cmdIDSessionInterrupt onInterrupt None
addCommand Guids.guidInteractiveCommands Guids.cmdIDSessionRestart onRestart None
addCommand Guids.guidFsiConsoleCmdSet Guids.cmdIDAttachDebugger onAttachDebugger None
addCommand Guids.guidFsiConsoleCmdSet Guids.cmdIDDetachDebugger onDetachDebugger None
addCommand Guids.guidInteractive Guids.cmdIDSendSelection onMLSend None
addCommand Guids.guidInteractiveShell Guids.cmdIDSendSelection onMLSend None
addCommand Guids.guidInteractive Guids.cmdIDDebugSelection onMLDebug None
addCommand guidVSStd2KCmdID (int32 VSConstants.VSStd2KCmdID.UP) onHistory (Some supportWhenInInputArea)
addCommand guidVSStd2KCmdID (int32 VSConstants.VSStd2KCmdID.DOWN) onHistory (Some supportWhenInInputArea)
......@@ -615,11 +682,23 @@ type internal FsiToolWindow() as this =
context.AddAttribute(VSUSERCONTEXTATTRIBUTEUSAGE.VSUC_Usage_LookupF1, "Keyword", "VS.FSharpInteractive") |> ignore
| _ -> Debug.Assert(false)
member __.QueryCommandStatus(guidCmdGroup:Guid, nCmdId:uint32) =
match () with
| _ when guidCmdGroup = Guids.guidFsiConsoleCmdSet && nCmdId = uint32 Guids.cmdIDAttachDebugger ->
if debuggerIsRunning () then Some(OLECMDF.OLECMDF_INVISIBLE)
else Some(OLECMDF.OLECMDF_SUPPORTED ||| OLECMDF.OLECMDF_ENABLED)
| _ when guidCmdGroup = Guids.guidFsiConsoleCmdSet && nCmdId = uint32 Guids.cmdIDDetachDebugger ->
if getDebugAttachedFSIProcess () |> Option.isSome then Some(OLECMDF.OLECMDF_SUPPORTED ||| OLECMDF.OLECMDF_ENABLED)
else Some(OLECMDF.OLECMDF_INVISIBLE)
| _ -> None
interface ITestVFSI with
/// Send a string; the ';;' will be added to the end; does not interact with history
member this.SendTextInteraction(s:string) =
let dummyLineNum = 1
executeInteraction (System.IO.Path.GetTempPath()) "DummyTestFilename.fs" 1 s
executeInteraction false (System.IO.Path.GetTempPath()) "DummyTestFilename.fs" 1 s
/// Returns the n most recent lines in the view. After SendTextInteraction, can poll for a prompt to know when interaction finished.
member this.GetMostRecentLines(n:int) : string[] =
lock textLines (fun () ->
......@@ -667,6 +746,15 @@ type internal FsiToolWindow() as this =
if not (wpfTextView.HasAggregateFocus) || isFocusedElementInterceptsCommandRouting() then
(int Microsoft.VisualStudio.OLE.Interop.Constants.OLECMDERR_E_NOTSUPPORTED)
else
let mutable allHandled = true
for i = 0 to ((int cCmds) - 1) do
match this.QueryCommandStatus(guid, prgCmds.[i].cmdID) with
| Some(commandStatus) ->
prgCmds.[i].cmdf <- uint32 commandStatus
| None ->
allHandled <- false
if allHandled then 0 else
let target : IOleCommandTarget = upcast commandService
target.QueryStatus(&guid, cCmds, prgCmds, pCmdText)
......
Markdown is supported
0% .
You are about to add 0 people to the discussion. Proceed with caution.
先完成此消息的编辑!
想要评论请 注册