Can be used to communicate with a client
websocket :: WebsocketConnection :: connected
Checks if a connection to a client is availablewebsocket :: WebsocketConnection :: frame_type=
Type of the current framewebsocket :: WebsocketConnection :: read_http_frame
Read an HTTP framewebsocket $ WebsocketConnection :: SELF
Type of this instance, automatically specialized in every classwebsocket $ WebsocketConnection :: is_writable
Can the stream be used to writewebsocket $ WebsocketConnection :: poll_in
Is there something to read? (without blocking)websocket $ WebsocketConnection :: raw_read_byte
Read a byte directly from the underlying stream, withoutwebsocket $ WebsocketConnection :: raw_read_bytes
Read at mostmax bytes from the underlying stream into buf,
			websocket $ WebsocketConnection :: write_bytes_from_cstring
Writelen bytes from ns
			core :: Reader :: append_line_to
Read a string until the end of the line and append it tos.
			binary :: BinaryStream :: big_endian
Use the big-endian convention? otherwise use little-endian.binary :: BinaryStream :: big_endian=
Use the big-endian convention? otherwise use little-endian.core :: Object :: class_factory
Implementation used byget_class to create the specific class.
			websocket :: WebsocketConnection :: connected
Checks if a connection to a client is availablecore :: Object :: defaultinit
core :: DuplexProtocol :: defaultinit
core :: Duplex :: defaultinit
core :: ReaderProtocol :: defaultinit
core :: WriterProtocol :: defaultinit
core :: Stream :: defaultinit
core :: Protocol :: defaultinit
core :: Writer :: defaultinit
binary :: BinaryStream :: defaultinit
core :: PollableReader :: defaultinit
core :: Reader :: defaultinit
core :: Reader :: deserialize_msgpack
Deserialize full Nitnullable Object from MessagePack formated data
			websocket :: WebsocketConnection :: frame_type=
Type of the current framecore :: Object :: is_same_instance
Return true ifself and other are the same instance (i.e. same identity).
			core :: Object :: is_same_serialized
Isself the same as other in a serialization context?
			core :: Object :: is_same_type
Return true ifself and other have the same dynamic type.
			core :: Stream :: last_error=
Error produced by the file streamcore :: Stream :: lookahead=
Lookahead buffer for codecscore :: Stream :: lookahead_capacity
Capacity of the lookaheadcore :: Stream :: lookahead_capacity=
Capacity of the lookaheadcore :: Stream :: lookahead_length
Current occupation of the lookaheadcore :: Stream :: lookahead_length=
Current occupation of the lookaheadcore :: Object :: output_class_name
Display class name on stdout (debug only).core :: PollableReader :: poll_in
Is there something to read? (without blocking)core :: Reader :: raw_read_byte
Read a byte directly from the underlying stream, withoutcore :: Reader :: raw_read_bytes
Read at mostmax bytes from the underlying stream into buf,
			core :: Reader :: read_block
Read the length as a 64 bits integer, then the content of the blockcore :: Reader :: read_bytes_to_cstring
Reads up tomax bytes from source and stores them in bytes
			core :: Reader :: read_double
Read a floating point on 64 bits and return it as aFloat
			core :: Reader :: read_float
Read a floating point on 32 bits and return it as aFloat
			websocket :: WebsocketConnection :: read_http_frame
Read an HTTP framecore :: Reader :: read_int64
Read a signed integer on 64 bits and return is anInt
			core :: Reader :: read_msgpack
Read the next MessagePack object and return it as a simple Nit objectcore :: Reader :: read_nonwhitespace
Skip whitespace characters (if any) then return the following non-whitespace character.core :: Writer :: serialize_msgpack
Serializevalue in MessagePack format
			core :: Writer :: write_block
Write the length as a 64 bits integer, then the content oftext
			core :: Writer :: write_bool
Write a booleanvalue on a byte, using 0 for false and 1 for true
			core :: Stream :: write_buffer
Buffer for writing data to a streamcore :: Stream :: write_buffer=
Buffer for writing data to a streamcore :: Writer :: write_bytes_from_cstring
Writelen bytes from ns
			core :: Writer :: write_double
Write a floating pointvalue on 64 bits
			core :: Writer :: write_int64
Writevalue as a signed integer on 64 bits
			core :: Writer :: write_msgpack_array
Write an array header forlen items in the shortest possible MessagePack array format
			core :: Writer :: write_msgpack_array16
Write an array header forlen items, max of 0xFFFF items
			core :: Writer :: write_msgpack_array32
Write an array header forlen items, max of 0xFFFF_FFFF items
			core :: Writer :: write_msgpack_bin
Writedata in the shortest possible MessagePack bin format
			core :: Writer :: write_msgpack_bin16
Writedata in bin16 format, max of 0xFFFF bytes
			core :: Writer :: write_msgpack_bin32
Writedata in bin32 format, max of 0xFFFF_FFFF bytes
			core :: Writer :: write_msgpack_bin8
Writedata in bin8 format, max of 0xFF bytes
			core :: Writer :: write_msgpack_bool
Writebool in MessagePack format
			core :: Writer :: write_msgpack_double
Writevalue as a MessagePack double
			core :: Writer :: write_msgpack_ext
Write an application-specific extension fortyp and bytes in the shortest possible MessagePack ext format
			core :: Writer :: write_msgpack_ext16
Write the header for an application-specific extension oflen data bytes
			core :: Writer :: write_msgpack_ext32
Write the header for an application-specific extension oflen data bytes
			core :: Writer :: write_msgpack_ext8
Write the header for an application-specific extension oflen data bytes
			core :: Writer :: write_msgpack_fixarray
Write an array header forlen items, max of 0x0F items
			core :: Writer :: write_msgpack_fixext1
Write the header for an application-specific extension of one data bytecore :: Writer :: write_msgpack_fixext16
Write the header for an application-specific extension of 16 data bytescore :: Writer :: write_msgpack_fixext2
Write the header for an application-specific extension of two data bytescore :: Writer :: write_msgpack_fixext4
Write the header for an application-specific extension of 4 data bytescore :: Writer :: write_msgpack_fixext8
Write the header for an application-specific extension of 8 data bytescore :: Writer :: write_msgpack_fixint
Writevalue as a single byte with metadata
			core :: Writer :: write_msgpack_fixmap
Write a map header forlen key/value pairs, max of 0x0F pairs
			core :: Writer :: write_msgpack_fixstr
Writetext in fixstr format, max of 0x1F bytes
			core :: Writer :: write_msgpack_float
Writevalue as a MessagePack float (losing precision)
			core :: Writer :: write_msgpack_int
Write the integervalue either as the shortest possible MessagePack int
			core :: Writer :: write_msgpack_int16
Writevalue over two signed bytes, following 1 metadata byte
			core :: Writer :: write_msgpack_int32
Writevalue over 4 signed bytes, following 1 metadata byte
			core :: Writer :: write_msgpack_int64
Writevalue over 8 signed bytes, following 1 metadata byte
			core :: Writer :: write_msgpack_int8
Writevalue over one signed byte, following 1 metadata byte
			core :: Writer :: write_msgpack_map
Write a map header forlen keys/value pairs in the shortest possible MessagePack map format
			core :: Writer :: write_msgpack_map16
Write a map header forlen key/value pairs, max of 0xFFFF pairs
			core :: Writer :: write_msgpack_map32
Write a map header forlen key/value pairs, max of 0xFFFF_FFFF pairs
			core :: Writer :: write_msgpack_null
Writenull, or nil, in MessagePack format
			core :: Writer :: write_msgpack_str
Writetext in the shortest possible MessagePack format
			core :: Writer :: write_msgpack_str16
Writetext in str16 format, max of 0xFFFF bytes
			core :: Writer :: write_msgpack_str32
Writetext in str32 format, max of 0xFFFF_FFFF bytes
			core :: Writer :: write_msgpack_str8
Writetext in str8 format, max of 0xFF bytes
			core :: Writer :: write_msgpack_uint16
Writevalue over two unsigned bytes, following 1 metadata byte
			core :: Writer :: write_msgpack_uint32
Writevalue over 4 unsigned bytes, following 1 metadata byte
			core :: Writer :: write_msgpack_uint64
Writevalue over 8 unsigned bytes, following 1 metadata byte
			core :: Writer :: write_msgpack_uint8
Writevalue over one unsigned byte, following 1 metadata byte
			Reader capable of declaring if readable without blocking
			
# Connection to a websocket client
#
# Can be used to communicate with a client
class WebsocketConnection
	super DuplexProtocol
	super PollableReader
	redef type STREAM: TCPStream
	# Does the current frame have a mask?
	private var has_mask = false
	# Mask with which to XOR input data
	private var mask = new CString(4)
	# Offset of the mask to use when decoding input data
	private var mask_offset = -1
	# Length of the current frame
	private var frame_length = -1
	# Position in current frame
	private var frame_cursor = -1
	# Type of the current frame
	var frame_type = -1
	# Is `self` closed?
	var closed = false
	init do
		var headers = parse_handshake
		var resp = handshake_response(headers)
		origin.write(resp)
	end
	# Disconnect from a client
	redef fun close do
		origin.close
		closed = true
	end
	# Ping response message
	private fun pong_msg: Bytes do return once b"\x8a\x00"
	# Parse the input handshake sent by the client
	# See RFC 6455 for information
	private fun parse_handshake: Map[String,String]
	do
		var recved = read_http_frame(new FlatBuffer)
		var headers = recved.split("\r\n")
		var headmap = new HashMap[String,String]
		for i in headers do
			var temp_head = i.split(" ")
			var head = temp_head.shift
			if head.is_empty or head.length == 1 then continue
			if head.chars.last == ':' then
				head = head.substring(0, head.length - 1)
			end
			var body = temp_head.join(" ")
			headmap[head] = body
		end
		return headmap
	end
	# Generate a handshake response
	private fun handshake_response(heads: Map[String,String]): String
	do
		var resp_map = new HashMap[String,String]
		resp_map["HTTP/1.1"] = "101 Switching Protocols"
		resp_map["Upgrade:"] = "websocket"
		resp_map["Connection:"] = "Upgrade"
		var key = heads["Sec-WebSocket-Key"]
		key += "258EAFA5-E914-47DA-95CA-C5AB0DC85B11"
		key = key.sha1.encode_base64.to_s
		resp_map["Sec-WebSocket-Accept:"] = key
		var resp = resp_map.join("\r\n", " ")
		resp += "\r\n\r\n"
		return resp
	end
	# Frame a text message to be sent to a client
	private fun frame_message(msg: Text): Bytes
	do
		var ans_buffer = new Bytes.with_capacity(msg.byte_length + 2)
		# Flag for final frame set to 1
		# opcode set to 1 (for text)
		ans_buffer.add(129)
		if msg.length < 126 then
			ans_buffer.add(msg.length)
		end
		if msg.length >= 126 and msg.length <= 65535 then
			ans_buffer.add(126)
			ans_buffer.add(msg.length >> 8)
			ans_buffer.add(msg.length)
		end
		msg.append_to_bytes(ans_buffer)
		return ans_buffer
	end
	# Read an HTTP frame
	protected fun read_http_frame(buf: Buffer): String
	do
		var ln = origin.read_line
		buf.append ln
		buf.append "\r\n"
		if buf.has_suffix("\r\n\r\n") then return buf.to_s
		return read_http_frame(buf)
	end
	# Get a frame's information
	private fun read_frame_info do
		var fst_byte = origin.read_byte
		var snd_byte = origin.read_byte
		if fst_byte < 0 or snd_byte < 0 then
			last_error = new IOError("Error: bad frame")
			close
			return
		end
		# First byte in msg is formatted this way :
		# |(fin - 1bit)|(RSV1 - 1bit)|(RSV2 - 1bit)|(RSV3 - 1bit)|(opcode - 4bits)
		# fin = Flag indicating if current frame is the last one for the current message
		# RSV1/2/3 = Extension flags, unsupported
		# Opcode values :
		#	%x0 denotes a continuation frame
		#	%x1 denotes a text frame
		#	%x2 denotes a binary frame
		#	%x3-7 are reserved for further non-control frames
		#	%x8 denotes a connection close
		#	%x9 denotes a ping
		#	%xA denotes a pong
		#	%xB-F are reserved for further control frames
		var opcode = fst_byte & 0b0000_1111
		if opcode == 9 then
			origin.write_bytes(pong_msg)
			return
		end
		if opcode == 8 then
			close
			return
		end
		frame_type = opcode
		# Second byte is formatted this way :
		# |(mask - 1bit)|(payload length - 7 bits)
		# As specified, if the payload length is 126 or 127
		# The next 16 or 64 bits contain an extended payload length
		var mask_flag = snd_byte & 0b1000_0000
		var len = snd_byte & 0b0111_1111
		var payload_ext_len = 0
		if len == 126 then
			var tmp = origin.read_bytes(2)
			if tmp.length != 2 then
				last_error = new IOError("Error: received interrupted frame")
				origin.close
				return
			end
			payload_ext_len += tmp[0].to_i << 8
			payload_ext_len += tmp[1].to_i
		else if len == 127 then
			var tmp = origin.read_bytes(8)
			if tmp.length != 8 then
				last_error = new IOError("Error: received interrupted frame")
				origin.close
				return
			end
			for i in [0 .. 8[ do
				payload_ext_len += tmp[i].to_i << (8 * (7 - i))
			end
		end
		if mask_flag != 0 then
			origin.read_bytes_to_cstring(mask, 4)
			has_mask = true
		else
			mask.memset(0, 4)
			has_mask = false
		end
		if payload_ext_len != 0 then
			len = payload_ext_len
		end
		frame_length = len
		frame_cursor = 0
	end
	redef fun raw_read_byte do
		while not closed and frame_cursor >= frame_length do
			read_frame_info
		end
		if closed then return -1
		var b = origin.read_byte
		if b >= 0 then
			frame_cursor += 1
		end
		return b
	end
	redef fun raw_read_bytes(ns, len) do
		while not closed and frame_cursor >= frame_length do
			read_frame_info
		end
		if closed then return -1
		var available = frame_length - frame_cursor
		var to_rd = len.min(available)
		var rd = origin.read_bytes_to_cstring(ns, to_rd)
		if rd < 0 then
			close
			return 0
		end
		if has_mask then
			ns.xor(mask, rd, 4, mask_offset)
			mask_offset = rd % 4
		end
		frame_cursor += rd
		return rd
	end
	# Checks if a connection to a client is available
	fun connected: Bool do return not closed and origin.connected
	redef fun write_bytes_from_cstring(ns, len) do
		origin.write_bytes(frame_message(ns.to_s_unsafe(len)))
	end
	redef fun write(msg) do origin.write_bytes(frame_message(msg))
	redef fun is_writable do return origin.connected
	# Is there some data available to be read ?
	fun can_read(timeout: Int): Bool do return  not closed and origin.ready_to_read(timeout)
	redef fun poll_in do return origin.poll_in
end
					lib/websocket/websocket.nit:63,1--294,3