4 people like it.
Like the snippet!
ByteString
An initial attempt at creating a ByteString type based on the Haskell version.
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:
|
/// An ArraySegment with structural comparison and equality.
/// An ArraySegment with structural comparison and equality.
[<CustomEquality; CustomComparison>]
[<SerializableAttribute>]
type BS =
struct
val Array: byte[]
val Offset: int
val Count: int
new (array: byte[]) = { Array = array; Offset = 0; Count = array.Length }
new (array: byte[], offset: int, count: int) = { Array = array; Offset = offset; Count = count }
static member Compare (a:BS, b:BS) =
let x,o,l = a.Array, a.Offset, a.Count
let x',o',l' = b.Array, b.Offset, b.Count
if x = x' && o = o' && l = l' then 0
elif x = x' then
if o = o' then if l < l' then -1 else 1
else if o < o' then -1 else 1
else let foldr res b b' =
if res <> 0 then res
else if b = b' then 0
elif b < b' then -1
else 1
let left = [| for i in o..(o+l-1) -> x.[i] |]
let right = [| for i' in o'..(o'+l'-1) -> x'.[i'] |]
Array.fold2 foldr 0 left right
override x.Equals(other) =
match other with
| :? BS as other' -> BS.Compare(x, other') = 0
| _ -> false
override x.GetHashCode() = hash x
interface System.IComparable with
member x.CompareTo(other) =
match other with
| :? BS as other' -> BS.Compare(x, other')
| _ -> invalidArg "other" "Cannot compare a value of another type."
end
module ByteString =
/// An active pattern for conveniently retrieving the properties of a BS.
let (|BS|) (x:BS) = x.Array, x.Offset, x.Count
let empty = BS()
let singleton c = BS(Array.create 1 c, 0, 1)
let create arr = BS(arr, 0, arr.Length)
let ofArraySegment (segment:ArraySegment<byte>) = BS(segment.Array, segment.Offset, segment.Count)
let ofSeq s = let arr = Array.ofSeq s in BS(arr, 0, arr.Length)
let ofList l = BS(Array.ofList l, 0, l.Length)
let ofString (s:string) = s.ToCharArray() |> Array.map byte |> create
let toSeq (bs:BS) =
seq { for i in bs.Offset..(bs.Offset + bs.Count - 1) do yield bs.Array.[i] }
let toList (bs:BS) =
[ for i in bs.Offset..(bs.Offset + bs.Count - 1) -> bs.Array.[i] ]
let toString (bs:BS) =
System.Text.Encoding.ASCII.GetString(bs.Array, bs.Offset, bs.Count)
let isEmpty (bs:BS) = Contract.Requires(bs.Count >= 0); bs.Count <= 0
let length (bs:BS) = Contract.Requires(bs.Count >= 0); bs.Count
let index (bs:BS) pos =
Contract.Requires(bs.Offset + pos <= bs.Count)
bs.Array.[bs.Offset + pos]
let head (bs:BS) =
if bs.Count <= 0 then
failwith "Cannot take the head of an empty byte string."
else bs.Array.[bs.Offset]
let tail (bs:BS) =
Contract.Requires(bs.Count >= 1)
if bs.Count = 1 then empty
else BS(bs.Array, bs.Offset+1, bs.Count-1)
/// cons uses Buffer.SetByte and Buffer.BlockCopy for efficient array operations.
/// Please note that a new array is created and both the head and tail are copied in,
/// disregarding any additional bytes in the original tail array.
let cons hd (bs:BS) =
let x,o,l = bs.Array, bs.Offset, bs.Count in
if l = 0 then singleton hd
else let buffer = Array.init (l + 1) byte
Buffer.SetByte(buffer,0,hd)
Buffer.BlockCopy(x,o,buffer,1,l)
BS(buffer,0,l+1)
/// append uses Buffer.BlockCopy for efficient array operations.
/// Please note that a new array is created and both arrays are copied in,
/// disregarding any additional bytes in the original, underlying arrays.
let append a b =
if isEmpty a then b
elif isEmpty b then a
else let x,o,l = a.Array, a.Offset, a.Count
let x',o',l' = b.Array, b.Offset, b.Count
let buffer = Array.init (l + l') byte
Buffer.BlockCopy(x,o,buffer,0,l)
Buffer.BlockCopy(x',o',buffer,l,l')
BS(buffer,0,l+l')
let fold f seed bs =
let rec loop bs acc =
if isEmpty bs then acc
else
let hd, tl = head bs, tail bs
loop tl (f acc hd)
loop bs seed
let span pred (bs:BS) =
if isEmpty bs then empty, empty
else
let x,o,l = bs.Array, bs.Offset, bs.Count
let rec loop acc =
if l = acc + 1 && pred x.[o+acc] then bs, empty
elif not (pred x.[o+acc]) then BS(x,o,acc), BS(x,o+acc,l-acc)
else loop (acc+1)
loop 0
let split pred bs = span (not << pred) bs
let splitAt n (bs:BS) =
Contract.Requires(n >= 0)
if isEmpty bs then empty, empty
elif n = 0 then empty, bs
elif n >= bs.Count then bs, empty
else let x,o,l = bs.Array, bs.Offset, bs.Count in BS(x,o,n), BS(x,o+n,l-n)
let skip n bs = splitAt n bs |> snd
let skipWhile pred bs = span pred bs |> snd
let skipUntil pred bs = split pred bs |> snd
let take n bs = splitAt n bs |> fst
let takeWhile pred bs = span pred bs |> fst
let takeUntil pred bs = split pred bs |> fst
|
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:
|
open System
open FSharp.Collections
open FSharp.Collections.ByteString
open NUnit.Framework
open FsUnit
[<Test>]
let ``test ByteString_length should return the length of the byte string``() =
let input = create "Hello, world!"B
let actual = length input
actual |> should equal 13
let spanAndSplitTests = [|
[| box "Howdy! Want to play?"B; box ' 'B; box 6 |]
[| box "Howdy! Want to play?"B; box '?'B; box 19 |]
[| box "Howdy! Want to play?"B; box '\r'B; box 20 |]
|]
[<Test>]
[<TestCaseSource("spanAndSplitTests")>]
let ``test ByteString_span correctly breaks the ByteString on the specified predicate``(input:byte [], breakChar:byte, breakIndex:int) =
let str = create input
let expected = if input.Length = breakIndex then str, empty
else BS(input, 0, breakIndex), BS(input, breakIndex, input.Length - breakIndex)
let actual = span ((<>) breakChar) str
actual |> should equal expected
[<Test>]
[<TestCaseSource("spanAndSplitTests")>]
let ``test ByteString_split correctly breaks the ByteString on the specified predicate``(input:byte [], breakChar:byte, breakIndex:int) =
let str = create input
let expected = if input.Length = breakIndex then str, empty
else BS(input, 0, breakIndex), BS(input, breakIndex, input.Length - breakIndex)
let actual = split ((=) breakChar) str
actual |> should equal expected
[<Test>]
let ``test ByteString_span correctly breaks the ByteString on \r``() =
let input = "test\r\ntest"B
let str = create input
let expected = BS(input, 0, 4), BS(input, 4, 6)
let actual = span (fun c -> c <> '\r'B && c <> '\n'B) str
actual |> should equal expected
[<Test>]
let ``test ByteString_split correctly breaks the ByteString on \r``() =
let input = "test\r\ntest"B
let str = create input
let expected = BS(input, 0, 4), BS(input, 4, 6)
let actual = split (fun c -> c = '\r'B || c = '\n'B) str
actual |> should equal expected
[<Test>]
let ``test ByteString_splitAt correctly breaks the ByteString on the specified index``() =
let input = "Howdy! Want to play?"B
let str = create input
let expected = BS(input, 0, 6), BS(input, 6, 14)
let actual = splitAt 6 str
actual |> should equal expected
[<Test>]
let ``test ByteString_fold should concatenate bytes into a string``() =
create "Howdy"B
|> fold (fun a b -> a + (char b).ToString()) ""
|> should equal "Howdy"
[<Test>]
let ``test ByteString_take correctly truncates the ByteString at the selected index``() =
let input = "Howdy! Want to play?"B
let str = create input
let expected = BS(input, 0, 6)
let actual = take 6 str
actual |> should equal expected
[<Test>]
[<Sequential>]
let ``test drop should drop the first n items``([<Values(0,1,2,3,4,5,6,7,8,9)>] x) =
let input = "Howdy! Want to play?"B
let actual = skip 7 (create input)
actual |> should equal (BS(input,7,13))
[<Test>]
let ``test dropWhile should drop anything before the first space``() =
let input = create "Howdy! Want to play?"B
let dropWhile2Head = skipWhile ((<>) ' 'B) >> head
let actual = dropWhile2Head input
actual |> should equal ' 'B
[<Test>]
let ``test take should return an empty ArraySegment when asked to take 0``() =
let actual = take 0 (create "Nothing should be taken"B)
actual |> should equal empty
[<Test>]
let ``test take should return an empty ArraySegment when given an empty ArraySegment``() =
let actual = take 4 empty
actual |> should equal empty
[<Test>]
[<Sequential>]
let ``test take should take the first n items``([<Values(1,2,3,4,5,6,7,8,9,10)>] x) =
let input = [|0uy..9uy|]
let expected = BS(input,0,x)
let actual = take x (create input)
actual |> should equal expected
[<Test>]
let ``test takeWhile should return an empty ArraySegment when given an empty ArraySegment``() =
let actual = takeWhile ((<>) ' 'B) empty
actual |> should equal empty
[<Test>]
let ``test takeWhile should take anything before the first space``() =
let input = "Hello world"B
let actual = takeWhile ((<>) ' 'B) (create input)
actual |> should equal (BS(input, 0, 5))
[<Test>]
let ``test takeUntil should return an empty ArraySegment when given an empty ArraySegment``() =
let actual = takeUntil ((=) ' 'B) empty
actual |> should equal empty
[<Test>]
let ``test takeUntil should correctly split the input``() =
let input = "abcde"B
let actual = takeUntil ((=) 'c'B) (create input)
actual |> should equal (BS(input, 0, 2))
|
Multiple items
type CustomEqualityAttribute =
inherit Attribute
new : unit -> CustomEqualityAttribute
Full name: Microsoft.FSharp.Core.CustomEqualityAttribute
--------------------
new : unit -> CustomEqualityAttribute
Multiple items
type CustomComparisonAttribute =
inherit Attribute
new : unit -> CustomComparisonAttribute
Full name: Microsoft.FSharp.Core.CustomComparisonAttribute
--------------------
new : unit -> CustomComparisonAttribute
Multiple items
type SerializableAttribute =
inherit Attribute
new : unit -> SerializableAttribute
Full name: System.SerializableAttribute
--------------------
SerializableAttribute() : unit
Multiple items
type BS =
struct
interface IComparable
new : array:byte [] -> BS
new : array:byte [] * offset:int * count:int -> BS
val Array: byte []
val Offset: int
val Count: int
override Equals : other:obj -> bool
override GetHashCode : unit -> int
static member Compare : a:BS * b:BS -> int
end
Full name: FSharp.Collections.BS
An ArraySegment with structural comparison and equality.
An ArraySegment with structural comparison and equality.
--------------------
BS()
new : array:byte [] -> BS
new : array:byte [] * offset:int * count:int -> BS
Multiple items
BS.Array: byte []
--------------------
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
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
BS.Offset: 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<_>
BS.Count: int
Multiple items
val array : byte []
--------------------
type 'T array = 'T []
Full name: Microsoft.FSharp.Core.array<_>
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
property Array.Length: int
val offset : int
val count : int
static member BS.Compare : a:BS * b:BS -> int
Full name: FSharp.Collections.BS.Compare
val a : BS
val b : BS
val x : byte []
val o : int
val l : int
BS.Array: byte []
val x' : byte []
val o' : int
val l' : int
val foldr : (int -> 'a -> 'a -> int) (requires comparison)
val res : int
val b : 'a (requires comparison)
val b' : 'a (requires comparison)
val left : byte []
val i : int
val right : byte []
val i' : int
val fold2 : folder:('State -> 'T1 -> 'T2 -> 'State) -> state:'State -> array1:'T1 [] -> array2:'T2 [] -> 'State
Full name: Microsoft.FSharp.Collections.Array.fold2
val x : byref<BS>
override BS.Equals : other:obj -> bool
Full name: FSharp.Collections.BS.Equals
val other : obj
val other' : BS
static member BS.Compare : a:BS * b:BS -> int
override BS.GetHashCode : unit -> int
Full name: FSharp.Collections.BS.GetHashCode
val hash : obj:'T -> int (requires equality)
Full name: Microsoft.FSharp.Core.Operators.hash
namespace System
Multiple items
type IComparable<'T> =
member CompareTo : other:'T -> int
Full name: System.IComparable<_>
--------------------
type IComparable =
member CompareTo : obj:obj -> int
Full name: System.IComparable
override BS.CompareTo : other:obj -> int
Full name: FSharp.Collections.BS.CompareTo
val invalidArg : argumentName:string -> message:string -> 'T
Full name: Microsoft.FSharp.Core.Operators.invalidArg
module ByteString
from FSharp.Collections
val x : BS
val empty : BS
Full name: FSharp.Collections.ByteString.empty
Multiple items
active recognizer BS: BS -> byte [] * int * int
Full name: FSharp.Collections.ByteString.( |BS| )
An active pattern for conveniently retrieving the properties of a BS.
--------------------
type BS =
struct
interface IComparable
new : array:byte [] -> BS
new : array:byte [] * offset:int * count:int -> BS
val Array: byte []
val Offset: int
val Count: int
override Equals : other:obj -> bool
override GetHashCode : unit -> int
static member Compare : a:BS * b:BS -> int
end
Full name: FSharp.Collections.BS
An ArraySegment with structural comparison and equality.
An ArraySegment with structural comparison and equality.
--------------------
BS()
new : array:byte [] -> BS
new : array:byte [] * offset:int * count:int -> BS
val singleton : c:byte -> BS
Full name: FSharp.Collections.ByteString.singleton
val c : byte
val create : count:int -> value:'T -> 'T []
Full name: Microsoft.FSharp.Collections.Array.create
val create : arr:byte [] -> BS
Full name: FSharp.Collections.ByteString.create
val arr : byte []
val ofArraySegment : segment:ArraySegment<byte> -> BS
Full name: FSharp.Collections.ByteString.ofArraySegment
val segment : ArraySegment<byte>
Multiple items
type ArraySegment<'T> =
struct
new : array:'T[] -> ArraySegment<'T> + 1 overload
member Array : 'T[]
member Count : int
member Equals : obj:obj -> bool + 1 overload
member GetHashCode : unit -> int
member Offset : int
end
Full name: System.ArraySegment<_>
--------------------
ArraySegment()
ArraySegment(array: 'T []) : unit
ArraySegment(array: 'T [], offset: int, count: int) : unit
property ArraySegment.Array: byte []
property ArraySegment.Offset: int
property ArraySegment.Count: int
val ofSeq : s:seq<byte> -> BS
Full name: FSharp.Collections.ByteString.ofSeq
val s : seq<byte>
val ofSeq : source:seq<'T> -> 'T []
Full name: Microsoft.FSharp.Collections.Array.ofSeq
val ofList : l:byte list -> BS
Full name: FSharp.Collections.ByteString.ofList
val l : byte list
val ofList : list:'T list -> 'T []
Full name: Microsoft.FSharp.Collections.Array.ofList
property List.Length: int
val ofString : s:string -> BS
Full name: FSharp.Collections.ByteString.ofString
val s : string
Multiple items
val string : value:'T -> string
Full name: Microsoft.FSharp.Core.Operators.string
--------------------
type string = String
Full name: Microsoft.FSharp.Core.string
String.ToCharArray() : char []
String.ToCharArray(startIndex: int, length: int) : char []
val map : mapping:('T -> 'U) -> array:'T [] -> 'U []
Full name: Microsoft.FSharp.Collections.Array.map
val toSeq : bs:BS -> seq<byte>
Full name: FSharp.Collections.ByteString.toSeq
val bs : BS
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 toList : bs:BS -> byte list
Full name: FSharp.Collections.ByteString.toList
val toString : bs:BS -> string
Full name: FSharp.Collections.ByteString.toString
namespace System.Text
type Encoding =
member BodyName : string
member Clone : unit -> obj
member CodePage : int
member DecoderFallback : DecoderFallback with get, set
member EncoderFallback : EncoderFallback with get, set
member EncodingName : string
member Equals : value:obj -> bool
member GetByteCount : chars:char[] -> int + 3 overloads
member GetBytes : chars:char[] -> byte[] + 5 overloads
member GetCharCount : bytes:byte[] -> int + 2 overloads
...
Full name: System.Text.Encoding
property Text.Encoding.ASCII: Text.Encoding
Text.Encoding.GetString(bytes: byte []) : string
Text.Encoding.GetString(bytes: byte [], index: int, count: int) : string
val isEmpty : bs:BS -> bool
Full name: FSharp.Collections.ByteString.isEmpty
type Contract =
static member Assert : condition:bool -> unit + 1 overload
static member Assume : condition:bool -> unit + 1 overload
static member EndContractBlock : unit -> unit
static member Ensures : condition:bool -> unit + 1 overload
static member EnsuresOnThrow<'TException> : condition:bool -> unit + 1 overload
static member Exists<'T> : collection:IEnumerable<'T> * predicate:Predicate<'T> -> bool + 1 overload
static member ForAll<'T> : collection:IEnumerable<'T> * predicate:Predicate<'T> -> bool + 1 overload
static member Invariant : condition:bool -> unit + 1 overload
static member OldValue<'T> : value:'T -> 'T
static member Requires : condition:bool -> unit + 3 overloads
...
Full name: System.Diagnostics.Contracts.Contract
Contract.Requires<'TException (requires 'TException :> exn)>(condition: bool) : unit
Contract.Requires(condition: bool) : unit
Contract.Requires<'TException (requires 'TException :> exn)>(condition: bool, userMessage: string) : unit
Contract.Requires(condition: bool, userMessage: string) : unit
val length : bs:BS -> int
Full name: FSharp.Collections.ByteString.length
val index : bs:BS -> pos:int -> byte
Full name: FSharp.Collections.ByteString.index
val pos : int
val head : bs:BS -> byte
Full name: FSharp.Collections.ByteString.head
val failwith : message:string -> 'T
Full name: Microsoft.FSharp.Core.Operators.failwith
val tail : bs:BS -> BS
Full name: FSharp.Collections.ByteString.tail
val cons : hd:byte -> bs:BS -> BS
Full name: FSharp.Collections.ByteString.cons
cons uses Buffer.SetByte and Buffer.BlockCopy for efficient array operations.
Please note that a new array is created and both the head and tail are copied in,
disregarding any additional bytes in the original tail array.
val hd : byte
val buffer : byte []
val init : count:int -> initializer:(int -> 'T) -> 'T []
Full name: Microsoft.FSharp.Collections.Array.init
type Buffer =
static member BlockCopy : src:Array * srcOffset:int * dst:Array * dstOffset:int * count:int -> unit
static member ByteLength : array:Array -> int
static member GetByte : array:Array * index:int -> byte
static member SetByte : array:Array * index:int * value:byte -> unit
Full name: System.Buffer
Buffer.SetByte(array: Array, index: int, value: byte) : unit
Buffer.BlockCopy(src: Array, srcOffset: int, dst: Array, dstOffset: int, count: int) : unit
val append : a:BS -> b:BS -> BS
Full name: FSharp.Collections.ByteString.append
append uses Buffer.BlockCopy for efficient array operations.
Please note that a new array is created and both arrays are copied in,
disregarding any additional bytes in the original, underlying arrays.
val fold : f:('a -> byte -> 'a) -> seed:'a -> bs:BS -> 'a
Full name: FSharp.Collections.ByteString.fold
val f : ('a -> byte -> 'a)
val seed : 'a
val loop : (BS -> 'a -> 'a)
val acc : 'a
val tl : BS
val span : pred:(byte -> bool) -> bs:BS -> BS * BS
Full name: FSharp.Collections.ByteString.span
val pred : (byte -> bool)
val loop : (int -> BS * BS)
val acc : int
val not : value:bool -> bool
Full name: Microsoft.FSharp.Core.Operators.not
val split : pred:(byte -> bool) -> bs:BS -> BS * BS
Full name: FSharp.Collections.ByteString.split
val splitAt : n:int -> bs:BS -> BS * BS
Full name: FSharp.Collections.ByteString.splitAt
val n : int
val skip : n:int -> bs:BS -> BS
Full name: FSharp.Collections.ByteString.skip
val snd : tuple:('T1 * 'T2) -> 'T2
Full name: Microsoft.FSharp.Core.Operators.snd
val skipWhile : pred:(byte -> bool) -> bs:BS -> BS
Full name: FSharp.Collections.ByteString.skipWhile
val skipUntil : pred:(byte -> bool) -> bs:BS -> BS
Full name: FSharp.Collections.ByteString.skipUntil
val take : n:int -> bs:BS -> BS
Full name: FSharp.Collections.ByteString.take
val fst : tuple:('T1 * 'T2) -> 'T1
Full name: Microsoft.FSharp.Core.Operators.fst
val takeWhile : pred:(byte -> bool) -> bs:BS -> BS
Full name: FSharp.Collections.ByteString.takeWhile
val takeUntil : pred:(byte -> bool) -> bs:BS -> BS
Full name: FSharp.Collections.ByteString.takeUntil
namespace Microsoft.FSharp
namespace Microsoft.FSharp.Collections
val box : value:'T -> obj
Full name: Microsoft.FSharp.Core.Operators.box
Multiple items
val char : value:'T -> char (requires member op_Explicit)
Full name: Microsoft.FSharp.Core.Operators.char
--------------------
type char = Char
Full name: Microsoft.FSharp.Core.char
More information