3 people like it.

local wireless passwords

dump out saved windows wireless passwords in plaintext. they're stored in xml file, to successfully dump them you must be logged in as the same user who created them (at least in the below code ;)

  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: 
192: 
193: 
194: 
195: 
196: 
197: 
198: 
199: 
200: 
201: 
202: 
203: 
204: 
205: 
206: 
207: 
208: 
209: 
210: 
211: 
212: 
213: 
214: 
215: 
216: 
217: 
218: 
219: 
220: 
221: 
222: 
223: 
224: 
225: 
226: 
227: 
228: 
229: 
230: 
231: 
232: 
233: 
234: 
235: 
236: 
237: 
238: 
239: 
240: 
241: 
242: 
243: 
244: 
245: 
246: 
247: 
248: 
249: 
250: 
251: 
252: 
253: 
254: 
255: 
256: 
257: 
258: 
259: 
260: 
// origional code from http://stackoverflow.com/questions/10765860/decrypt-wep-wlan-profile-key-using-cryptunprotectdata, taken an F#'d up.

open System
open System.Diagnostics
open System.Runtime.InteropServices

let getWinlogonPID name = 
  Process.GetProcessesByName name
  |> Seq.head
  |> fun ps -> ps.Id

let ERROR_SUCCESS                        = 0
let TOKEN_QUERY, TOKEN_ADJUST_PRIVILEGES = 0x0008u, 0x0020u
let MAXIMUM_ALLOWED                      = 0x2000000u

let CRYPT_STRING_HEX                     = 0x00000004u
let CRYPT_STRING_HEXASCII                = 0x00000005u

let SE_PRIVILEGE_ENABLED_BY_DEFAULT      = 0x00000001u
let SE_PRIVILEGE_ENABLED                 = 0x00000002u
let SE_PRIVILEGE_REMOVED                 = 0x00000004u
let SE_PRIVILEGE_USED_FOR_ACCESS         = 0x80000000u

let SE_ASSIGNPRIMARYTOKEN_NAME           = "SeAssignPrimaryTokenPrivilege"
let SE_BACKUP_NAME                       = "SeBackupPrivilege"
let SE_DEBUG_NAME                        = "SeDebugPrivilege"
let SE_INCREASE_QUOTA_NAME               = "SeIncreaseQuotaPrivilege"
let SE_TCB_NAME                          = "SeTcbPrivilege"


[<Struct>]
type DATA_BLOB = 
  val mutable cbData         : uint32
  val mutable bytes          : nativeint

[<Struct>]
type LUID =
  val mutable lowPart        : uint32
  val mutable highPart       : int

[<Struct>]
type LUID_AND_ATTRIBUTES = 
  val mutable luid           : LUID
  val mutable attributes     : uint32

[<Struct>]
type TOKEN_PRIVILEGES =
  val mutable privilegeCount : uint32
  val mutable privileges     : LUID_AND_ATTRIBUTES

[<DllImport "advapi32">]
extern bool LookupPrivilegeValue(
  string            lpSystemName, 
  string            lpName,
  LUID&             lpLuid)

[<DllImport ("advapi32", SetLastError=true)>]
extern bool AdjustTokenPrivileges(
  nativeint         TokenHandle, 
  bool              DisableAllPrivileges, 
  TOKEN_PRIVILEGES& NewState, 
  uint32            Bufferlength, 
  TOKEN_PRIVILEGES& PreviousState, 
  int&              ReturnLength)

[<DllImport "advapi32" >]
extern bool OpenProcessToken(
  nativeint         ProcessHandle,
  uint32            DesiredAccess, 
  nativeint&        TokenHandle)

[<DllImport "kernel32">]
extern nativeint OpenProcess(
  uint32            dwDesiredAccess, 
  bool              bInheritHandle, 
  int               dwProcessId)

[<DllImport( "crypt32", SetLastError=true)>]
extern bool CryptStringToBinary( 
  string            pszString, 
  uint32            cchString, 
  uint32            dwFlags,
  nativeint         pbBinary, 
  uint32&           pcbBinary, 
  uint32&           pdwSkip, 
  uint32&           pdwFlags)


[<DllImport("crypt32", SetLastError=true)>]
extern bool CryptUnprotectData(
    DATA_BLOB&      pDataIn, 
    string          szDataDescr, 
    uint32          pOptionalEntropy, 
    nativeint       pvReserved, 
    uint32          pPromptStruct, 
    uint32          dwFlags, 
    DATA_BLOB&      pDataOut)
    
[<DllImport "kernel32">]
extern bool CloseHandle(nativeint hObject)

[<DllImport( "advapi32", SetLastError=true)>]
extern bool ImpersonateLoggedOnUser(nativeint hToken)

let errorHandle s = 
  let err = Marshal.GetLastWin32Error()
  fprintf stdout "%s, error=%d" s err
  exit -1

let SeSetCurrentPrivilege pszPrivilege bEnablePrivilege =
  
  let mutable NULL       = 0
  let mutable nullToken  = Unchecked.defaultof<_>
  let mutable luid       = LUID()
  let mutable hToken     = 0n
  let mutable tp         = TOKEN_PRIVILEGES()
  let mutable tpPrevious = TOKEN_PRIVILEGES()
  let mutable cbPrevious = sizeof<TOKEN_PRIVILEGES>

  let privs = LookupPrivilegeValue(null, pszPrivilege, &luid)

  if not privs then errorHandle "[+] could not lookup privileges, exiting"
    
  let currentPh = Process.GetCurrentProcess().Handle
  let ps        = OpenProcessToken(currentPh,TOKEN_QUERY|||TOKEN_ADJUST_PRIVILEGES,&hToken) 

  if not ps then errorHandle "[+] could not open process."

  tp.privilegeCount <- 1u
  tp.privileges     <- LUID_AND_ATTRIBUTES(luid=luid,attributes=0u)
  
  let dwReturn = 
    AdjustTokenPrivileges(
      hToken, 
      false, 
      &tp, 
      uint32 sizeof<TOKEN_PRIVILEGES>, 
      &tpPrevious, 
      &cbPrevious)

  if dwReturn then 

    let tpa = tpPrevious.privileges.attributes
    let adjustPrivAttr (tk : TOKEN_PRIVILEGES) newval = 
      tk.privileges.attributes <- newval

    tpPrevious.privilegeCount  <- 1u
    tpPrevious.privileges.luid <- luid

    if bEnablePrivilege then
      adjustPrivAttr tpPrevious (tpa ||| SE_PRIVILEGE_ENABLED)
    else
      adjustPrivAttr tpPrevious (tpa ^^^ (SE_PRIVILEGE_ENABLED &&& tpa))

    let dwReturn = 
      AdjustTokenPrivileges(
        hToken,
        false,
        &tpPrevious,
        uint32 cbPrevious,
        &nullToken,
        &NULL)

    if dwReturn then true
    else 
      printfn "AdjustTokenPrivileges failed. 2"
      CloseHandle hToken |> ignore
      false
  else
    printfn "AdjustTokenPrivileges failed. 1"
    CloseHandle hToken |> ignore
    false
    
// whatevs    
let getNameAndPw (s : string) = 
  let x1, x2 = s.IndexOf "<name>"+6, s.IndexOf "</name>"-1
  let y1, y2 = s.IndexOf "<keyMaterial>"+13, s.IndexOf "</keyMaterial>"-1
  try s.[x1..x2],s.[y1..y2] with _ -> "",""

let getXmlSsidAndPass () = 
  let dir = @"C:\ProgramData\Microsoft\Wlansvc\Profiles\Interfaces\"

  let maybe f x y = 
    try f(x,y) |> Seq.cast<string> with _ -> Seq.empty

  let enumFiles = maybe IO.Directory.EnumerateFiles
  let enumDirs  = maybe IO.Directory.EnumerateDirectories

  let rec loop dir pattern =
    seq { yield! enumFiles dir pattern
          for d in enumDirs dir "*" do
            yield! loop d pattern }

  loop dir "*.xml"

let decodeWifiKey szKey = 

  let mutable hProcessToken = 0n
  let mutable dwFlags       = 0u
  let mutable dwSkip        = 0u
 
  let dwProcessId = getWinlogonPID "winlogon"

  if dwProcessId = 0 then
    errorHandle "couldn't get winlogon.exe process Id"

  let bIsSuccess = SeSetCurrentPrivilege SE_DEBUG_NAME true
  if not bIsSuccess then
    errorHandle "couldn't set SeDebugPrivilege" 

  let hProcess = OpenProcess(MAXIMUM_ALLOWED,false,dwProcessId)
  if hProcess = 0n then 
    errorHandle (sprintf "couldnt OpenProcess on %d" hProcess)

  let bIsSuccess = OpenProcessToken(hProcess,MAXIMUM_ALLOWED,&hProcessToken)
  if not bIsSuccess && hProcessToken = 0n then
    errorHandle "could not OpenProcessToken"
  
  let bIsSuccess = ImpersonateLoggedOnUser hProcessToken
  if not bIsSuccess then
    errorHandle "could not ImpersonateLoggedOnUser"
 
  let mutable cbBinary = 1024u
  
  let mutable byKey = Marshal.AllocHGlobal (int cbBinary)
  if byKey = 0n then errorHandle "could not Alloc"
  
  let bIsSuccess = 
    CryptStringToBinary(
      szKey, uint32 szKey.Length, 
      CRYPT_STRING_HEX,byKey,&cbBinary,&dwSkip,&dwFlags)

  if not bIsSuccess then
    errorHandle "could not CryptStringToBinary"

  let mutable dataOut = DATA_BLOB()
  dataOut.cbData     <- cbBinary
  dataOut.bytes      <- byKey

  let mutable dataVerify = DATA_BLOB()
  let bIsSuccess = CryptUnprotectData(&dataOut,null,0u,0n,0u,0u,&dataVerify)
  if not bIsSuccess then 
    errorHandle "could not CryptUnprotectData"
    
  else
    if dataVerify.bytes <> 0n then
      Marshal.PtrToStringAnsi dataVerify.bytes
    else
      "couldnt get password"

  
// todo: need to check if elevated.
[<EntryPoint>]
let main _ = 
  getXmlSsidAndPass () 
  |> Seq.map (IO.File.ReadAllText >> getNameAndPw)
  |> Seq.filter (fun (x,y) -> x <> "")
  |> Seq.map (fun (x,y) -> x, decodeWifiKey y)
  |> Seq.iter (printfn "%A")
  0
namespace System
namespace System.Diagnostics
namespace System.Runtime
namespace System.Runtime.InteropServices
val getWinlogonPID : name:string -> int

Full name: Script.getWinlogonPID
val name : string
Multiple items
type Process =
  inherit Component
  new : unit -> Process
  member BasePriority : int
  member BeginErrorReadLine : unit -> unit
  member BeginOutputReadLine : unit -> unit
  member CancelErrorRead : unit -> unit
  member CancelOutputRead : unit -> unit
  member Close : unit -> unit
  member CloseMainWindow : unit -> bool
  member EnableRaisingEvents : bool with get, set
  member ExitCode : int
  ...

Full name: System.Diagnostics.Process

--------------------
Process() : unit
Process.GetProcessesByName(processName: string) : Process []
Process.GetProcessesByName(processName: string, machineName: string) : Process []
module Seq

from Microsoft.FSharp.Collections
val head : source:seq<'T> -> 'T

Full name: Microsoft.FSharp.Collections.Seq.head
val ps : Process
property Process.Id: int
val ERROR_SUCCESS : int

Full name: Script.ERROR_SUCCESS
val TOKEN_QUERY : uint32

Full name: Script.TOKEN_QUERY
val TOKEN_ADJUST_PRIVILEGES : uint32

Full name: Script.TOKEN_ADJUST_PRIVILEGES
val MAXIMUM_ALLOWED : uint32

Full name: Script.MAXIMUM_ALLOWED
val CRYPT_STRING_HEX : uint32

Full name: Script.CRYPT_STRING_HEX
val CRYPT_STRING_HEXASCII : uint32

Full name: Script.CRYPT_STRING_HEXASCII
val SE_PRIVILEGE_ENABLED_BY_DEFAULT : uint32

Full name: Script.SE_PRIVILEGE_ENABLED_BY_DEFAULT
val SE_PRIVILEGE_ENABLED : uint32

Full name: Script.SE_PRIVILEGE_ENABLED
val SE_PRIVILEGE_REMOVED : uint32

Full name: Script.SE_PRIVILEGE_REMOVED
val SE_PRIVILEGE_USED_FOR_ACCESS : uint32

Full name: Script.SE_PRIVILEGE_USED_FOR_ACCESS
val SE_ASSIGNPRIMARYTOKEN_NAME : string

Full name: Script.SE_ASSIGNPRIMARYTOKEN_NAME
val SE_BACKUP_NAME : string

Full name: Script.SE_BACKUP_NAME
val SE_DEBUG_NAME : string

Full name: Script.SE_DEBUG_NAME
val SE_INCREASE_QUOTA_NAME : string

Full name: Script.SE_INCREASE_QUOTA_NAME
val SE_TCB_NAME : string

Full name: Script.SE_TCB_NAME
Multiple items
type StructAttribute =
  inherit Attribute
  new : unit -> StructAttribute

Full name: Microsoft.FSharp.Core.StructAttribute

--------------------
new : unit -> StructAttribute
type DATA_BLOB =
  struct
    val mutable cbData: uint32
    val mutable bytes: nativeint
  end

Full name: Script.DATA_BLOB
DATA_BLOB.cbData: uint32
Multiple items
val uint32 : value:'T -> uint32 (requires member op_Explicit)

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

--------------------
type uint32 = UInt32

Full name: Microsoft.FSharp.Core.uint32
DATA_BLOB.bytes: nativeint
Multiple items
val nativeint : value:'T -> nativeint (requires member op_Explicit)

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

--------------------
type nativeint = IntPtr

Full name: Microsoft.FSharp.Core.nativeint
type LUID =
  struct
    val mutable lowPart: uint32
    val mutable highPart: int
  end

Full name: Script.LUID
LUID.lowPart: uint32
LUID.highPart: int
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<_>
type LUID_AND_ATTRIBUTES =
  struct
    val mutable luid: LUID
    val mutable attributes: uint32
  end

Full name: Script.LUID_AND_ATTRIBUTES
LUID_AND_ATTRIBUTES.luid: LUID
LUID_AND_ATTRIBUTES.attributes: uint32
type TOKEN_PRIVILEGES =
  struct
    val mutable privilegeCount: uint32
    val mutable privileges: LUID_AND_ATTRIBUTES
  end

Full name: Script.TOKEN_PRIVILEGES
TOKEN_PRIVILEGES.privilegeCount: uint32
TOKEN_PRIVILEGES.privileges: LUID_AND_ATTRIBUTES
Multiple items
type DllImportAttribute =
  inherit Attribute
  new : dllName:string -> DllImportAttribute
  val EntryPoint : string
  val CharSet : CharSet
  val SetLastError : bool
  val ExactSpelling : bool
  val PreserveSig : bool
  val CallingConvention : CallingConvention
  val BestFitMapping : bool
  val ThrowOnUnmappableChar : bool
  member Value : string

Full name: System.Runtime.InteropServices.DllImportAttribute

--------------------
DllImportAttribute(dllName: string) : unit
type bool = Boolean

Full name: Microsoft.FSharp.Core.bool
val LookupPrivilegeValue : lpSystemName:string * lpName:string * lpLuid:byref<LUID> -> bool

Full name: Script.LookupPrivilegeValue
Multiple items
val string : value:'T -> string

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

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

Full name: Microsoft.FSharp.Core.string
val lpSystemName : string
val lpName : string
val lpLuid : byref<LUID>
val AdjustTokenPrivileges : TokenHandle:nativeint * DisableAllPrivileges:bool * NewState:byref<TOKEN_PRIVILEGES> * Bufferlength:uint32 * PreviousState:byref<TOKEN_PRIVILEGES> * ReturnLength:byref<int> -> bool

Full name: Script.AdjustTokenPrivileges
val TokenHandle : nativeint
val DisableAllPrivileges : bool
val NewState : byref<TOKEN_PRIVILEGES>
val Bufferlength : uint32
val PreviousState : byref<TOKEN_PRIVILEGES>
val ReturnLength : byref<int>
val OpenProcessToken : ProcessHandle:nativeint * DesiredAccess:uint32 * TokenHandle:byref<nativeint> -> bool

Full name: Script.OpenProcessToken
val ProcessHandle : nativeint
val DesiredAccess : uint32
val TokenHandle : byref<nativeint>
val OpenProcess : dwDesiredAccess:uint32 * bInheritHandle:bool * dwProcessId:int -> nativeint

Full name: Script.OpenProcess
val dwDesiredAccess : uint32
val bInheritHandle : bool
val dwProcessId : int
val CryptStringToBinary : pszString:string * cchString:uint32 * dwFlags:uint32 * pbBinary:nativeint * pcbBinary:byref<uint32> * pdwSkip:byref<uint32> * pdwFlags:byref<uint32> -> bool

Full name: Script.CryptStringToBinary
val pszString : string
val cchString : uint32
val dwFlags : uint32
val pbBinary : nativeint
val pcbBinary : byref<uint32>
val pdwSkip : byref<uint32>
val pdwFlags : byref<uint32>
val CryptUnprotectData : pDataIn:byref<DATA_BLOB> * szDataDescr:string * pOptionalEntropy:uint32 * pvReserved:nativeint * pPromptStruct:uint32 * dwFlags:uint32 * pDataOut:byref<DATA_BLOB> -> bool

Full name: Script.CryptUnprotectData
val pDataIn : byref<DATA_BLOB>
val szDataDescr : string
val pOptionalEntropy : uint32
val pvReserved : nativeint
val pPromptStruct : uint32
val pDataOut : byref<DATA_BLOB>
val CloseHandle : hObject:nativeint -> bool

Full name: Script.CloseHandle
val hObject : nativeint
val ImpersonateLoggedOnUser : hToken:nativeint -> bool

Full name: Script.ImpersonateLoggedOnUser
val hToken : nativeint
val errorHandle : s:string -> 'a

Full name: Script.errorHandle
val s : string
val err : int
type Marshal =
  static val SystemDefaultCharSize : int
  static val SystemMaxDBCSCharSize : int
  static member AddRef : pUnk:nativeint -> int
  static member AllocCoTaskMem : cb:int -> nativeint
  static member AllocHGlobal : cb:nativeint -> nativeint + 1 overload
  static member AreComObjectsAvailableForCleanup : unit -> bool
  static member BindToMoniker : monikerName:string -> obj
  static member ChangeWrapperHandleStrength : otp:obj * fIsWeak:bool -> unit
  static member CleanupUnusedObjectsInCurrentContext : unit -> unit
  static member Copy : source:int[] * startIndex:int * destination:nativeint * length:int -> unit + 15 overloads
  ...

Full name: System.Runtime.InteropServices.Marshal
Marshal.GetLastWin32Error() : int
val fprintf : textWriter:IO.TextWriter -> format:Printf.TextWriterFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.fprintf
val stdout<'T> : IO.TextWriter

Full name: Microsoft.FSharp.Core.Operators.stdout
val exit : exitcode:int -> 'T

Full name: Microsoft.FSharp.Core.Operators.exit
val SeSetCurrentPrivilege : pszPrivilege:string -> bEnablePrivilege:bool -> bool

Full name: Script.SeSetCurrentPrivilege
val pszPrivilege : string
val bEnablePrivilege : bool
val mutable NULL : int
val mutable nullToken : TOKEN_PRIVILEGES
module Unchecked

from Microsoft.FSharp.Core.Operators
val defaultof<'T> : 'T

Full name: Microsoft.FSharp.Core.Operators.Unchecked.defaultof
val mutable luid : LUID
val mutable hToken : nativeint
val mutable tp : TOKEN_PRIVILEGES
val mutable tpPrevious : TOKEN_PRIVILEGES
val mutable cbPrevious : int
val sizeof<'T> : int

Full name: Microsoft.FSharp.Core.Operators.sizeof
val privs : bool
val not : value:bool -> bool

Full name: Microsoft.FSharp.Core.Operators.not
val currentPh : nativeint
Process.GetCurrentProcess() : Process
val ps : bool
val dwReturn : bool
val tpa : uint32
val adjustPrivAttr : (TOKEN_PRIVILEGES -> uint32 -> unit)
val tk : TOKEN_PRIVILEGES
val newval : uint32
val printfn : format:Printf.TextWriterFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.printfn
val ignore : value:'T -> unit

Full name: Microsoft.FSharp.Core.Operators.ignore
val getNameAndPw : s:string -> string * string

Full name: Script.getNameAndPw
val x1 : int
val x2 : int
String.IndexOf(value: string) : int
String.IndexOf(value: char) : int
String.IndexOf(value: string, comparisonType: StringComparison) : int
String.IndexOf(value: string, startIndex: int) : int
String.IndexOf(value: char, startIndex: int) : int
String.IndexOf(value: string, startIndex: int, comparisonType: StringComparison) : int
String.IndexOf(value: string, startIndex: int, count: int) : int
String.IndexOf(value: char, startIndex: int, count: int) : int
String.IndexOf(value: string, startIndex: int, count: int, comparisonType: StringComparison) : int
val y1 : int
val y2 : int
val getXmlSsidAndPass : unit -> seq<string>

Full name: Script.getXmlSsidAndPass
val dir : string
val maybe : (('a * 'b -> #Collections.IEnumerable) -> 'a -> 'b -> seq<string>)
val f : ('a * 'b -> #Collections.IEnumerable)
val x : 'a
val y : 'b
val cast : source:Collections.IEnumerable -> seq<'T>

Full name: Microsoft.FSharp.Collections.Seq.cast
val empty<'T> : seq<'T>

Full name: Microsoft.FSharp.Collections.Seq.empty
val enumFiles : (string -> string -> seq<string>)
namespace System.IO
type Directory =
  static member CreateDirectory : path:string -> DirectoryInfo + 1 overload
  static member Delete : path:string -> unit + 1 overload
  static member EnumerateDirectories : path:string -> IEnumerable<string> + 2 overloads
  static member EnumerateFileSystemEntries : path:string -> IEnumerable<string> + 2 overloads
  static member EnumerateFiles : path:string -> IEnumerable<string> + 2 overloads
  static member Exists : path:string -> bool
  static member GetAccessControl : path:string -> DirectorySecurity + 1 overload
  static member GetCreationTime : path:string -> DateTime
  static member GetCreationTimeUtc : path:string -> DateTime
  static member GetCurrentDirectory : unit -> string
  ...

Full name: System.IO.Directory
IO.Directory.EnumerateFiles(path: string) : Collections.Generic.IEnumerable<string>
IO.Directory.EnumerateFiles(path: string, searchPattern: string) : Collections.Generic.IEnumerable<string>
IO.Directory.EnumerateFiles(path: string, searchPattern: string, searchOption: IO.SearchOption) : Collections.Generic.IEnumerable<string>
val enumDirs : (string -> string -> seq<string>)
IO.Directory.EnumerateDirectories(path: string) : Collections.Generic.IEnumerable<string>
IO.Directory.EnumerateDirectories(path: string, searchPattern: string) : Collections.Generic.IEnumerable<string>
IO.Directory.EnumerateDirectories(path: string, searchPattern: string, searchOption: IO.SearchOption) : Collections.Generic.IEnumerable<string>
val loop : (string -> string -> seq<string>)
val pattern : string
Multiple items
val seq : sequence:seq<'T> -> seq<'T>

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

--------------------
type seq<'T> = Collections.Generic.IEnumerable<'T>

Full name: Microsoft.FSharp.Collections.seq<_>
val d : string
val decodeWifiKey : szKey:string -> string

Full name: Script.decodeWifiKey
val szKey : string
val mutable hProcessToken : nativeint
val mutable dwFlags : uint32
val mutable dwSkip : uint32
val bIsSuccess : bool
val hProcess : nativeint
val sprintf : format:Printf.StringFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.sprintf
val mutable cbBinary : uint32
val mutable byKey : nativeint
Marshal.AllocHGlobal(cb: int) : nativeint
Marshal.AllocHGlobal(cb: nativeint) : nativeint
property String.Length: int
val mutable dataOut : DATA_BLOB
val mutable dataVerify : DATA_BLOB
Marshal.PtrToStringAnsi(ptr: nativeint) : string
Marshal.PtrToStringAnsi(ptr: nativeint, len: int) : string
Multiple items
type EntryPointAttribute =
  inherit Attribute
  new : unit -> EntryPointAttribute

Full name: Microsoft.FSharp.Core.EntryPointAttribute

--------------------
new : unit -> EntryPointAttribute
val main : string [] -> int

Full name: Script.main
val map : mapping:('T -> 'U) -> source:seq<'T> -> seq<'U>

Full name: Microsoft.FSharp.Collections.Seq.map
type File =
  static member AppendAllLines : path:string * contents:IEnumerable<string> -> unit + 1 overload
  static member AppendAllText : path:string * contents:string -> unit + 1 overload
  static member AppendText : path:string -> StreamWriter
  static member Copy : sourceFileName:string * destFileName:string -> unit + 1 overload
  static member Create : path:string -> FileStream + 3 overloads
  static member CreateText : path:string -> StreamWriter
  static member Decrypt : path:string -> unit
  static member Delete : path:string -> unit
  static member Encrypt : path:string -> unit
  static member Exists : path:string -> bool
  ...

Full name: System.IO.File
IO.File.ReadAllText(path: string) : string
IO.File.ReadAllText(path: string, encoding: Text.Encoding) : string
val filter : predicate:('T -> bool) -> source:seq<'T> -> seq<'T>

Full name: Microsoft.FSharp.Collections.Seq.filter
val x : string
val y : string
val iter : action:('T -> unit) -> source:seq<'T> -> unit

Full name: Microsoft.FSharp.Collections.Seq.iter
Raw view Test code New version

More information

Link:http://fssnip.net/hU
Posted:10 years ago
Author:David Klein
Tags: pinvoke , security