4 people like it.

Rudimentary IL dissembler for use within FSI.

got distracted and decided I wanted to be able to 'disassemble' a function inside of FSI, much like you can do in many Lisps, this isnt very complete and I think it will only work on the most basic functions, but it was very challenging to get working so I thought I would paste it.

  1: 
  2: 
  3: 
  4: 
  5: 
  6: 
  7: 
  8: 
  9: 
 10: 
 11: 
 12: 
 13: 
 14: 
 15: 
 16: 
 17: 
 18: 
 19: 
 20: 
 21: 
 22: 
 23: 
 24: 
 25: 
 26: 
 27: 
 28: 
 29: 
 30: 
 31: 
 32: 
 33: 
 34: 
 35: 
 36: 
 37: 
 38: 
 39: 
 40: 
 41: 
 42: 
 43: 
 44: 
 45: 
 46: 
 47: 
 48: 
 49: 
 50: 
 51: 
 52: 
 53: 
 54: 
 55: 
 56: 
 57: 
 58: 
 59: 
 60: 
 61: 
 62: 
 63: 
 64: 
 65: 
 66: 
 67: 
 68: 
 69: 
 70: 
 71: 
 72: 
 73: 
 74: 
 75: 
 76: 
 77: 
 78: 
 79: 
 80: 
 81: 
 82: 
 83: 
 84: 
 85: 
 86: 
 87: 
 88: 
 89: 
 90: 
 91: 
 92: 
 93: 
 94: 
 95: 
 96: 
 97: 
 98: 
 99: 
100: 
101: 
102: 
103: 
104: 
105: 
106: 
107: 
108: 
109: 
110: 
111: 
112: 
113: 
114: 
115: 
116: 
117: 
118: 
119: 
120: 
121: 
122: 
123: 
124: 
125: 
126: 
127: 
128: 
129: 
130: 
131: 
132: 
133: 
134: 
135: 
136: 
137: 
138: 
139: 
140: 
141: 
142: 
143: 
144: 
145: 
146: 
147: 
148: 
149: 
150: 
151: 
152: 
153: 
154: 
155: 
156: 
157: 
158: 
159: 
160: 
161: 
162: 
163: 
164: 
165: 
166: 
167: 
168: 
169: 
170: 
171: 
172: 
173: 
174: 
175: 
176: 
177: 
178: 
179: 
180: 
181: 
182: 
183: 
184: 
185: 
186: 
187: 
188: 
189: 
190: 
191: 
open System
open System.IO
open System.Reflection
open System.Reflection.Emit
open System.Collections.Generic

let opcodeMap =
  let fields = typeof<OpCodes>.GetFields(BindingFlags.Public ||| BindingFlags.Static)
  
  fields 
  |> Array.map (fun x -> 
     let opcode = x.GetValue null :?> OpCode
     opcode.Value, opcode)
  |> Map.ofArray

let findOpcode opc = 
  Map.tryFind opc opcodeMap

type OpCodeReturn =
  | IL_Nop
  | IL_Int32    of int
  | IL_Int16    of int16
  | IL_Float    of float
  | IL_Int64    of int64
  | IL_Sbyte    of sbyte
  | IL_Byte     of byte
  | IL_Switch   of int array
  | IL_Sig      of byte array
  | IL_String   of string
  | IL_Field    of MemberInfo
  | IL_LocalVar of LocalVariableInfo
  | IL_Param    of ParameterInfo


//module binary =
let readInt32 (ms : BinaryReader) =
  ms.ReadInt32() 

let readInt16AsInt (ms : BinaryReader) = 
  ms.ReadInt16() |> int

let readInt64 (ms : BinaryReader) = 
  ms.ReadInt64() 

let readFloat (ms : BinaryReader) =
  ms.ReadDouble()

let readByteAsInt (ms : BinaryReader) = 
  ms.ReadByte() |> int

let readBytes (ms : BinaryReader) n =
  ms.ReadBytes n

let streamPos (ms : BinaryReader) = 
  ms.BaseStream.Position |> int

let streamLen (ms : BinaryReader) = 
  ms.BaseStream.Length |> int

let getType (f : MethodBase) = 
  f.GetType() 

let isStatic (f : MethodBase) =
  f.IsStatic

// thank you to the below author, i wouldn't have been able to get this without copying his code
// ref: https://github.com/jbevain/mono.reflection/blob/master/Mono.Reflection/MethodBodyReader.cs

// can be 1byte or 2byte opcode, 2 byte opcodes ALWAYS start with 0xfe.
let readOpcode (ms : BinaryReader) = 
  let op = readByteAsInt ms
  if  op <> 254 then
      int16 op |> findOpcode 
  else 
      BitConverter.ToInt16(Array.append [| 0xfeuy |] (readBytes ms 1), 0)
      |> findOpcode

let getInlineSwitch (ms : BinaryReader) = 
  let length = readInt32 ms
  let offset = streamPos ms + (4 * length)
  [| for i in 0 .. length - 1 -> readInt32 ms + offset |]

let walkBranches (ms : BinaryReader) =
  let len = readInt32 ms
  [| 0 .. len - 1 |]
  |> Array.map (fun x ->
     readInt32 ms |> fun offset -> streamPos ms + offset)

let checkByteSignLd (ms : BinaryReader) opcode =
  if opcode = OpCodes.Ldc_I4_S then
    readByteAsInt ms + streamPos ms |> sbyte |> IL_Sbyte
  else
    readByteAsInt ms |> byte |> IL_Byte

type instructionModel = {
  func   : MethodBase
  mbytes : byte array
  modulx : Module
  locals : LocalVariableInfo array
  paramx : ParameterInfo array
  gener1 : Type []
  gener2 : Type []
}

let createInstructionModel (f : MethodBase) =
  { func   = f
    mbytes = f.GetMethodBody().GetILAsByteArray()
    modulx = f.Module
    locals = f.GetMethodBody().LocalVariables |> Seq.toArray
    paramx = f.GetParameters()
    gener1 = 
      if getType f <> typeof<ConstructorInfo> then 
        f.GetGenericArguments() else [||]

    gener2 = 
      if f.DeclaringType <> null then 
        f.DeclaringType.GetGenericArguments() else [||]
  }

let resolveToken IM token =
  match IM.gener1, IM.gener2 with
  | ([||],[||]) -> IM.func.Module.ResolveMember  token
  | (a,b)       -> IM.func.Module.ResolveMember (token,a,b)

let resolveVariable IM (opcode : OpCode) index =
 
  let p n = IM.paramx.[index-n] |> IL_Param
  let l _ = IM.locals.[index  ] |> IL_LocalVar

  if opcode.Name.Contains "loc" then l ()
  else    if isStatic IM.func then p 0
  else    if index <> 0 then p 1
  else       IL_Nop    

let test (f : MethodBase) = 
  
  let IM = createInstructionModel f

  use ms = BinaryReader (MemoryStream IM.mbytes)

  let parseOpcode (opcode : OpCode) =
    match opcode.OperandType  with
    | OperandType.InlineNone          -> IL_Nop
    | OperandType.InlineSwitch        -> walkBranches  ms |> IL_Switch
    | OperandType.ShortInlineBrTarget -> readByteAsInt ms + streamPos ms |> IL_Int32
    | OperandType.InlineBrTarget      -> readInt32 ms     + streamPos ms |> IL_Int32
    | OperandType.ShortInlineI        -> checkByteSignLd ms opcode
    | OperandType.InlineI             -> readInt32 ms  |> IL_Int32
    | OperandType.ShortInlineR        
    | OperandType.InlineR             -> readFloat ms  |> IL_Float
    | OperandType.InlineI8            -> readInt64 ms  |> IL_Int64
    | OperandType.InlineSig           -> readInt32 ms  |> IM.modulx.ResolveSignature |> IL_Sig
    | OperandType.InlineString        -> readInt32 ms  |> IM.modulx.ResolveString    |> IL_String
    | OperandType.InlineTok 
    | OperandType.InlineType
    | OperandType.InlineMethod
    | OperandType.InlineField         -> resolveToken IM (readInt32 ms) |> IL_Field
    | OperandType.ShortInlineVar      -> resolveVariable  IM opcode (readByteAsInt ms)
    | OperandType.InlineVar           -> resolveVariable  IM opcode (readInt16AsInt ms)

  let rec loop L = 
    if streamPos ms = streamLen ms then L
    else
      match readOpcode ms  with
      | Some code -> loop ((code, parseOpcode code)::L)
      | None      -> loop ((OpCodes.Nop, IL_Nop)::L)

  loop [] 

let print_instruction_fields ( xs : (OpCode * OpCodeReturn) list ) =
  xs |> Seq.iter (fun (opcode,mapping) -> printfn " %-5s | %A" opcode.Name mapping)

let disassemble f =
  (f.GetType().GetMethod "Invoke").MethodHandle
  |> MethodBase.GetMethodFromHandle
  |> test


(* testing*)
let myfunc1() = 
  let testfunc = "this is a test"
  testfunc ^ " abc"

disassemble myfunc1 |> List.rev |> print_instruction_fields
(* 
 nop   | IL_Nop
 ldstr | IL_String "this is a test"
 ldstr | IL_String " abc"
 call  | IL_Field System.String Concat(System.String, System.String)
 ret   | IL_Nop
 *)
namespace System
namespace System.IO
namespace System.Reflection
namespace System.Reflection.Emit
namespace System.Collections
namespace System.Collections.Generic
val opcodeMap : Map<int16,OpCode>

Full name: Script.opcodeMap
val fields : FieldInfo []
val typeof<'T> : Type

Full name: Microsoft.FSharp.Core.Operators.typeof
type OpCodes =
  static val Nop : OpCode
  static val Break : OpCode
  static val Ldarg_0 : OpCode
  static val Ldarg_1 : OpCode
  static val Ldarg_2 : OpCode
  static val Ldarg_3 : OpCode
  static val Ldloc_0 : OpCode
  static val Ldloc_1 : OpCode
  static val Ldloc_2 : OpCode
  static val Ldloc_3 : OpCode
  ...

Full name: System.Reflection.Emit.OpCodes
type BindingFlags =
  | Default = 0
  | IgnoreCase = 1
  | DeclaredOnly = 2
  | Instance = 4
  | Static = 8
  | Public = 16
  | NonPublic = 32
  | FlattenHierarchy = 64
  | InvokeMethod = 256
  | CreateInstance = 512
  ...

Full name: System.Reflection.BindingFlags
field BindingFlags.Public = 16
field BindingFlags.Static = 8
type Array =
  member Clone : unit -> obj
  member CopyTo : array:Array * index:int -> unit + 1 overload
  member GetEnumerator : unit -> IEnumerator
  member GetLength : dimension:int -> int
  member GetLongLength : dimension:int -> int64
  member GetLowerBound : dimension:int -> int
  member GetUpperBound : dimension:int -> int
  member GetValue : [<ParamArray>] indices:int[] -> obj + 7 overloads
  member Initialize : unit -> unit
  member IsFixedSize : bool
  ...

Full name: System.Array
val map : mapping:('T -> 'U) -> array:'T [] -> 'U []

Full name: Microsoft.FSharp.Collections.Array.map
val x : FieldInfo
val opcode : OpCode
FieldInfo.GetValue(obj: obj) : obj
type OpCode =
  struct
    member Equals : obj:obj -> bool + 1 overload
    member FlowControl : FlowControl
    member GetHashCode : unit -> int
    member Name : string
    member OpCodeType : OpCodeType
    member OperandType : OperandType
    member Size : int
    member StackBehaviourPop : StackBehaviour
    member StackBehaviourPush : StackBehaviour
    member ToString : unit -> string
    ...
  end

Full name: System.Reflection.Emit.OpCode
property OpCode.Value: int16
Multiple items
module Map

from Microsoft.FSharp.Collections

--------------------
type Map<'Key,'Value (requires comparison)> =
  interface IEnumerable
  interface IComparable
  interface IEnumerable<KeyValuePair<'Key,'Value>>
  interface ICollection<KeyValuePair<'Key,'Value>>
  interface IDictionary<'Key,'Value>
  new : elements:seq<'Key * 'Value> -> Map<'Key,'Value>
  member Add : key:'Key * value:'Value -> Map<'Key,'Value>
  member ContainsKey : key:'Key -> bool
  override Equals : obj -> bool
  member Remove : key:'Key -> Map<'Key,'Value>
  ...

Full name: Microsoft.FSharp.Collections.Map<_,_>

--------------------
new : elements:seq<'Key * 'Value> -> Map<'Key,'Value>
val ofArray : elements:('Key * 'T) [] -> Map<'Key,'T> (requires comparison)

Full name: Microsoft.FSharp.Collections.Map.ofArray
val findOpcode : opc:int16 -> OpCode option

Full name: Script.findOpcode
val opc : int16
val tryFind : key:'Key -> table:Map<'Key,'T> -> 'T option (requires comparison)

Full name: Microsoft.FSharp.Collections.Map.tryFind
type OpCodeReturn =
  | IL_Nop
  | IL_Int32 of int
  | IL_Int16 of int16
  | IL_Float of float
  | IL_Int64 of int64
  | IL_Sbyte of sbyte
  | IL_Byte of byte
  | IL_Switch of int array
  | IL_Sig of byte array
  | IL_String of string
  ...

Full name: Script.OpCodeReturn
union case OpCodeReturn.IL_Nop: OpCodeReturn
union case OpCodeReturn.IL_Int32: int -> OpCodeReturn
Multiple items
val int : value:'T -> int (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.int

--------------------
type int = int32

Full name: Microsoft.FSharp.Core.int

--------------------
type int<'Measure> = int

Full name: Microsoft.FSharp.Core.int<_>
union case OpCodeReturn.IL_Int16: int16 -> OpCodeReturn
Multiple items
val int16 : value:'T -> int16 (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.int16

--------------------
type int16 = Int16

Full name: Microsoft.FSharp.Core.int16

--------------------
type int16<'Measure> = int16

Full name: Microsoft.FSharp.Core.int16<_>
union case OpCodeReturn.IL_Float: float -> OpCodeReturn
Multiple items
val float : value:'T -> float (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.float

--------------------
type float = Double

Full name: Microsoft.FSharp.Core.float

--------------------
type float<'Measure> = float

Full name: Microsoft.FSharp.Core.float<_>
union case OpCodeReturn.IL_Int64: int64 -> OpCodeReturn
Multiple items
val int64 : value:'T -> int64 (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.int64

--------------------
type int64 = Int64

Full name: Microsoft.FSharp.Core.int64

--------------------
type int64<'Measure> = int64

Full name: Microsoft.FSharp.Core.int64<_>
union case OpCodeReturn.IL_Sbyte: sbyte -> OpCodeReturn
Multiple items
val sbyte : value:'T -> sbyte (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.sbyte

--------------------
type sbyte = SByte

Full name: Microsoft.FSharp.Core.sbyte

--------------------
type sbyte<'Measure> = sbyte

Full name: Microsoft.FSharp.Core.sbyte<_>
union case OpCodeReturn.IL_Byte: byte -> OpCodeReturn
Multiple items
val byte : value:'T -> byte (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.byte

--------------------
type byte = Byte

Full name: Microsoft.FSharp.Core.byte
union case OpCodeReturn.IL_Switch: int array -> OpCodeReturn
type 'T array = 'T []

Full name: Microsoft.FSharp.Core.array<_>
union case OpCodeReturn.IL_Sig: byte array -> OpCodeReturn
union case OpCodeReturn.IL_String: string -> OpCodeReturn
Multiple items
val string : value:'T -> string

Full name: Microsoft.FSharp.Core.Operators.string

--------------------
type string = String

Full name: Microsoft.FSharp.Core.string
union case OpCodeReturn.IL_Field: MemberInfo -> OpCodeReturn
type MemberInfo =
  member DeclaringType : Type
  member Equals : obj:obj -> bool
  member GetCustomAttributes : inherit:bool -> obj[] + 1 overload
  member GetCustomAttributesData : unit -> IList<CustomAttributeData>
  member GetHashCode : unit -> int
  member IsDefined : attributeType:Type * inherit:bool -> bool
  member MemberType : MemberTypes
  member MetadataToken : int
  member Module : Module
  member Name : string
  ...

Full name: System.Reflection.MemberInfo
union case OpCodeReturn.IL_LocalVar: LocalVariableInfo -> OpCodeReturn
type LocalVariableInfo =
  member IsPinned : bool
  member LocalIndex : int
  member LocalType : Type
  member ToString : unit -> string

Full name: System.Reflection.LocalVariableInfo
union case OpCodeReturn.IL_Param: ParameterInfo -> OpCodeReturn
type ParameterInfo =
  member Attributes : ParameterAttributes
  member DefaultValue : obj
  member GetCustomAttributes : inherit:bool -> obj[] + 1 overload
  member GetCustomAttributesData : unit -> IList<CustomAttributeData>
  member GetOptionalCustomModifiers : unit -> Type[]
  member GetRealObject : context:StreamingContext -> obj
  member GetRequiredCustomModifiers : unit -> Type[]
  member IsDefined : attributeType:Type * inherit:bool -> bool
  member IsIn : bool
  member IsLcid : bool
  ...

Full name: System.Reflection.ParameterInfo
val readInt32 : ms:BinaryReader -> int

Full name: Script.readInt32
val ms : BinaryReader
Multiple items
type BinaryReader =
  new : input:Stream -> BinaryReader + 1 overload
  member BaseStream : Stream
  member Close : unit -> unit
  member Dispose : unit -> unit
  member PeekChar : unit -> int
  member Read : unit -> int + 2 overloads
  member ReadBoolean : unit -> bool
  member ReadByte : unit -> byte
  member ReadBytes : count:int -> byte[]
  member ReadChar : unit -> char
  ...

Full name: System.IO.BinaryReader

--------------------
BinaryReader(input: Stream) : unit
BinaryReader(input: Stream, encoding: Text.Encoding) : unit
BinaryReader.ReadInt32() : int
val readInt16AsInt : ms:BinaryReader -> int

Full name: Script.readInt16AsInt
BinaryReader.ReadInt16() : int16
val readInt64 : ms:BinaryReader -> int64

Full name: Script.readInt64
BinaryReader.ReadInt64() : int64
val readFloat : ms:BinaryReader -> float

Full name: Script.readFloat
BinaryReader.ReadDouble() : float
val readByteAsInt : ms:BinaryReader -> int

Full name: Script.readByteAsInt
BinaryReader.ReadByte() : byte
val readBytes : ms:BinaryReader -> n:int -> byte []

Full name: Script.readBytes
val n : int
BinaryReader.ReadBytes(count: int) : byte []
val streamPos : ms:BinaryReader -> int

Full name: Script.streamPos
property BinaryReader.BaseStream: Stream
property Stream.Position: int64
val streamLen : ms:BinaryReader -> int

Full name: Script.streamLen
property Stream.Length: int64
val getType : f:MethodBase -> Type

Full name: Script.getType
val f : MethodBase
type MethodBase =
  inherit MemberInfo
  member Attributes : MethodAttributes
  member CallingConvention : CallingConventions
  member ContainsGenericParameters : bool
  member Equals : obj:obj -> bool
  member GetGenericArguments : unit -> Type[]
  member GetHashCode : unit -> int
  member GetMethodBody : unit -> MethodBody
  member GetMethodImplementationFlags : unit -> MethodImplAttributes
  member GetParameters : unit -> ParameterInfo[]
  member Invoke : obj:obj * parameters:obj[] -> obj + 1 overload
  ...

Full name: System.Reflection.MethodBase
Object.GetType() : Type
val isStatic : f:MethodBase -> bool

Full name: Script.isStatic
property MethodBase.IsStatic: bool
val readOpcode : ms:BinaryReader -> OpCode option

Full name: Script.readOpcode
val op : int
type BitConverter =
  static val IsLittleEndian : bool
  static member DoubleToInt64Bits : value:float -> int64
  static member GetBytes : value:bool -> byte[] + 9 overloads
  static member Int64BitsToDouble : value:int64 -> float
  static member ToBoolean : value:byte[] * startIndex:int -> bool
  static member ToChar : value:byte[] * startIndex:int -> char
  static member ToDouble : value:byte[] * startIndex:int -> float
  static member ToInt16 : value:byte[] * startIndex:int -> int16
  static member ToInt32 : value:byte[] * startIndex:int -> int
  static member ToInt64 : value:byte[] * startIndex:int -> int64
  ...

Full name: System.BitConverter
BitConverter.ToInt16(value: byte [], startIndex: int) : int16
val append : array1:'T [] -> array2:'T [] -> 'T []

Full name: Microsoft.FSharp.Collections.Array.append
val getInlineSwitch : ms:BinaryReader -> int []

Full name: Script.getInlineSwitch
val length : int
val offset : int
val i : int
val walkBranches : ms:BinaryReader -> int []

Full name: Script.walkBranches
val len : int
val x : int
val checkByteSignLd : ms:BinaryReader -> opcode:OpCode -> OpCodeReturn

Full name: Script.checkByteSignLd
field OpCodes.Ldc_I4_S
type instructionModel =
  {func: MethodBase;
   mbytes: byte array;
   modulx: Module;
   locals: LocalVariableInfo array;
   paramx: ParameterInfo array;
   gener1: Type [];
   gener2: Type [];}

Full name: Script.instructionModel
instructionModel.func: MethodBase
instructionModel.mbytes: byte array
instructionModel.modulx: Module
type Module =
  member Assembly : Assembly
  member Equals : o:obj -> bool
  member FindTypes : filter:TypeFilter * filterCriteria:obj -> Type[]
  member FullyQualifiedName : string
  member GetCustomAttributes : inherit:bool -> obj[] + 1 overload
  member GetCustomAttributesData : unit -> IList<CustomAttributeData>
  member GetField : name:string -> FieldInfo + 1 overload
  member GetFields : unit -> FieldInfo[] + 1 overload
  member GetHashCode : unit -> int
  member GetMethod : name:string -> MethodInfo + 2 overloads
  ...

Full name: System.Reflection.Module
instructionModel.locals: LocalVariableInfo array
instructionModel.paramx: ParameterInfo array
instructionModel.gener1: Type []
type Type =
  inherit MemberInfo
  member Assembly : Assembly
  member AssemblyQualifiedName : string
  member Attributes : TypeAttributes
  member BaseType : Type
  member ContainsGenericParameters : bool
  member DeclaringMethod : MethodBase
  member DeclaringType : Type
  member Equals : o:obj -> bool + 1 overload
  member FindInterfaces : filter:TypeFilter * filterCriteria:obj -> Type[]
  member FindMembers : memberType:MemberTypes * bindingAttr:BindingFlags * filter:MemberFilter * filterCriteria:obj -> MemberInfo[]
  ...

Full name: System.Type
instructionModel.gener2: Type []
val createInstructionModel : f:MethodBase -> instructionModel

Full name: Script.createInstructionModel
MethodBase.GetMethodBody() : MethodBody
property MemberInfo.Module: Module
module Seq

from Microsoft.FSharp.Collections
val toArray : source:seq<'T> -> 'T []

Full name: Microsoft.FSharp.Collections.Seq.toArray
MethodBase.GetParameters() : ParameterInfo []
type ConstructorInfo =
  inherit MethodBase
  member Equals : obj:obj -> bool
  member GetHashCode : unit -> int
  member Invoke : parameters:obj[] -> obj + 1 overload
  member MemberType : MemberTypes
  static val ConstructorName : string
  static val TypeConstructorName : string

Full name: System.Reflection.ConstructorInfo
MethodBase.GetGenericArguments() : Type []
property MemberInfo.DeclaringType: Type
Type.GetGenericArguments() : Type []
val resolveToken : IM:instructionModel -> token:int -> MemberInfo

Full name: Script.resolveToken
val IM : instructionModel
val token : int
Module.ResolveMember(metadataToken: int) : MemberInfo
Module.ResolveMember(metadataToken: int, genericTypeArguments: Type [], genericMethodArguments: Type []) : MemberInfo
val a : Type []
val b : Type []
val resolveVariable : IM:instructionModel -> opcode:OpCode -> index:int -> OpCodeReturn

Full name: Script.resolveVariable
val index : int
val p : (int -> OpCodeReturn)
val l : ('a -> OpCodeReturn)
property OpCode.Name: string
String.Contains(value: string) : bool
val test : f:MethodBase -> (OpCode * OpCodeReturn) list

Full name: Script.test
Multiple items
type MemoryStream =
  inherit Stream
  new : unit -> MemoryStream + 6 overloads
  member CanRead : bool
  member CanSeek : bool
  member CanWrite : bool
  member Capacity : int with get, set
  member Flush : unit -> unit
  member GetBuffer : unit -> byte[]
  member Length : int64
  member Position : int64 with get, set
  member Read : buffer:byte[] * offset:int * count:int -> int
  ...

Full name: System.IO.MemoryStream

--------------------
MemoryStream() : unit
MemoryStream(capacity: int) : unit
MemoryStream(buffer: byte []) : unit
MemoryStream(buffer: byte [], writable: bool) : unit
MemoryStream(buffer: byte [], index: int, count: int) : unit
MemoryStream(buffer: byte [], index: int, count: int, writable: bool) : unit
MemoryStream(buffer: byte [], index: int, count: int, writable: bool, publiclyVisible: bool) : unit
val parseOpcode : (OpCode -> OpCodeReturn)
property OpCode.OperandType: OperandType
type OperandType =
  | InlineBrTarget = 0
  | InlineField = 1
  | InlineI = 2
  | InlineI8 = 3
  | InlineMethod = 4
  | InlineNone = 5
  | InlinePhi = 6
  | InlineR = 7
  | InlineSig = 9
  | InlineString = 10
  ...

Full name: System.Reflection.Emit.OperandType
field OperandType.InlineNone = 5
field OperandType.InlineSwitch = 11
field OperandType.ShortInlineBrTarget = 15
field OperandType.InlineBrTarget = 0
field OperandType.ShortInlineI = 16
field OperandType.InlineI = 2
field OperandType.ShortInlineR = 17
field OperandType.InlineR = 7
field OperandType.InlineI8 = 3
field OperandType.InlineSig = 9
Module.ResolveSignature(metadataToken: int) : byte []
field OperandType.InlineString = 10
Module.ResolveString(metadataToken: int) : string
field OperandType.InlineTok = 12
field OperandType.InlineType = 13
field OperandType.InlineMethod = 4
field OperandType.InlineField = 1
field OperandType.ShortInlineVar = 18
field OperandType.InlineVar = 14
val loop : ((OpCode * OpCodeReturn) list -> (OpCode * OpCodeReturn) list)
val L : (OpCode * OpCodeReturn) list
union case Option.Some: Value: 'T -> Option<'T>
val code : OpCode
union case Option.None: Option<'T>
field OpCodes.Nop
val print_instruction_fields : xs:(OpCode * OpCodeReturn) list -> unit

Full name: Script.print_instruction_fields
val xs : (OpCode * OpCodeReturn) list
type 'T list = List<'T>

Full name: Microsoft.FSharp.Collections.list<_>
val iter : action:('T -> unit) -> source:seq<'T> -> unit

Full name: Microsoft.FSharp.Collections.Seq.iter
val mapping : OpCodeReturn
val printfn : format:Printf.TextWriterFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.printfn
val disassemble : f:'a -> (OpCode * OpCodeReturn) list

Full name: Script.disassemble
val f : 'a
MethodBase.GetMethodFromHandle(handle: RuntimeMethodHandle) : MethodBase
MethodBase.GetMethodFromHandle(handle: RuntimeMethodHandle, declaringType: RuntimeTypeHandle) : MethodBase
val myfunc1 : unit -> string

Full name: Script.myfunc1
val testfunc : string
Multiple items
type List<'T> =
  new : unit -> List<'T> + 2 overloads
  member Add : item:'T -> unit
  member AddRange : collection:IEnumerable<'T> -> unit
  member AsReadOnly : unit -> ReadOnlyCollection<'T>
  member BinarySearch : item:'T -> int + 2 overloads
  member Capacity : int with get, set
  member Clear : unit -> unit
  member Contains : item:'T -> bool
  member ConvertAll<'TOutput> : converter:Converter<'T, 'TOutput> -> List<'TOutput>
  member CopyTo : array:'T[] -> unit + 2 overloads
  ...
  nested type Enumerator

Full name: System.Collections.Generic.List<_>

--------------------
List() : unit
List(capacity: int) : unit
List(collection: IEnumerable<'T>) : unit
val rev : list:'T list -> 'T list

Full name: Microsoft.FSharp.Collections.List.rev

More information

Link:http://fssnip.net/fY
Posted:11 years ago
Author:David Klein
Tags: reflection , dissembler