[wip] websockets should have their own supervision tree

I also hate this bullshit of

- fd_client having such a stupid name
- websocket lib needs some love

basically I think this should be the approach:

renames:

- fd_clients    -> fd_http
- fd_client_man -> fd_http_client_man
- fd_client_sup -> fd_http_client_sup
- fd_client     -> fd_http_client
- fd_cache      -> fd_wfc_cache

new trees:

- tetris        -> new tree
- websockets    -> probably should fall into http supervision tree

Notes:
- fd_client_man is necessary because someone needs to own the listen socket
- rewrite fd_client as gen_server
This commit is contained in:
Peter Harpending 2025-10-27 10:35:05 -07:00
parent 1aed42598a
commit 4e48d6b40b
7 changed files with 458 additions and 140 deletions

105
src/et_piece.erl Normal file
View File

@ -0,0 +1,105 @@
-module(et_piece).
-vsn("1.0.4").
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("MIT").
-export([rand/0, new/1, flip/2, points/2, points/1, type/1, sides/1]).
-export_type([data/0]).
-record(p,
{flip = 1 :: 1..4,
type = i :: erltris:type()}).
-opaque data() :: #p{}.
rand() ->
case rand:uniform(7) of
1 -> new(i);
2 -> new(o);
3 -> new(t);
4 -> new(s);
5 -> new(z);
6 -> new(j);
7 -> new(l)
end.
new(T) -> #p{type = T}.
flip(r, Piece = #p{flip = 4}) -> Piece#p{flip = 1};
flip(r, Piece = #p{flip = F}) -> Piece#p{flip = F + 1};
flip(l, Piece = #p{flip = 1}) -> Piece#p{flip = 4};
flip(l, Piece = #p{flip = F}) -> Piece#p{flip = F - 1}.
points(Piece, {LX, LY}) ->
Offsets = points(Piece),
Translate = fun({OX, OY}) -> {LX + OX, LY + OY} end,
lists:map(Translate, Offsets).
points(#p{flip = F, type = T}) ->
offset(T, F).
offset(i, 1) -> [{0, 2}, {1, 2}, {2, 2}, {3, 2}];
offset(i, 2) -> [{2, 3}, {2, 2}, {2, 1}, {2, 0}];
offset(i, 3) -> [{0, 1}, {1, 1}, {2, 1}, {3, 1}];
offset(i, 4) -> [{1, 3}, {1, 2}, {1, 1}, {1, 0}];
offset(o, _) -> [{1, 1}, {1, 2}, {2, 1}, {2, 2}];
offset(t, 1) -> [{0, 1}, {1, 1}, {2, 1}, {1, 2}];
offset(t, 2) -> [{1, 2}, {1, 1}, {1, 0}, {2, 1}];
offset(t, 3) -> [{0, 1}, {1, 1}, {2, 1}, {1, 0}];
offset(t, 4) -> [{1, 2}, {1, 1}, {1, 0}, {0, 1}];
offset(s, 1) -> [{0, 1}, {1, 1}, {1, 2}, {2, 2}];
offset(s, 2) -> [{1, 2}, {1, 1}, {2, 1}, {2, 0}];
offset(s, 3) -> [{0, 0}, {1, 0}, {1, 1}, {2, 1}];
offset(s, 4) -> [{0, 2}, {0, 1}, {1, 1}, {1, 0}];
offset(z, 1) -> [{0, 2}, {1, 2}, {1, 1}, {2, 1}];
offset(z, 2) -> [{1, 0}, {1, 1}, {2, 1}, {2, 2}];
offset(z, 3) -> [{0, 1}, {1, 1}, {1, 0}, {2, 0}];
offset(z, 4) -> [{0, 0}, {0, 1}, {1, 1}, {1, 2}];
offset(j, 1) -> [{0, 2}, {0, 1}, {1, 1}, {2, 1}];
offset(j, 2) -> [{1, 0}, {1, 1}, {1, 2}, {2, 2}];
offset(j, 3) -> [{0, 1}, {1, 1}, {2, 1}, {2, 0}];
offset(j, 4) -> [{0, 0}, {1, 0}, {1, 1}, {1, 2}];
offset(l, 1) -> [{0, 1}, {1, 1}, {2, 1}, {2, 2}];
offset(l, 2) -> [{1, 2}, {1, 1}, {1, 0}, {2, 0}];
offset(l, 3) -> [{0, 0}, {0, 1}, {1, 1}, {2, 1}];
offset(l, 4) -> [{0, 2}, {1, 2}, {1, 1}, {1, 0}].
type(#p{type = T}) -> T.
sides(#p{type = T, flip = F}) ->
sides(T, F).
sides(i, 1) -> {0, 3, 2};
sides(i, 2) -> {2, 2, 3};
sides(i, 3) -> {0, 3, 1};
sides(i, 4) -> {1, 1, 3};
sides(o, _) -> {1, 2, 2};
sides(t, 1) -> {0, 2, 2};
sides(t, 2) -> {1, 2, 2};
sides(t, 3) -> {0, 2, 1};
sides(t, 4) -> {0, 1, 2};
sides(s, 1) -> {0, 2, 2};
sides(s, 2) -> {1, 2, 2};
sides(s, 3) -> {0, 2, 1};
sides(s, 4) -> {0, 1, 2};
sides(z, 1) -> {0 ,2, 2};
sides(z, 2) -> {1, 2, 2};
sides(z, 3) -> {0 ,2, 1};
sides(z, 4) -> {0, 1, 2};
sides(j, 1) -> {0, 2, 2};
sides(j, 2) -> {1, 2, 2};
sides(j, 3) -> {0, 2, 1};
sides(j, 4) -> {0, 1, 2};
sides(l, 1) -> {0, 2, 2};
sides(l, 2) -> {1, 2, 2};
sides(l, 3) -> {0, 2, 1};
sides(l, 4) -> {0, 1, 2}.

79
src/et_well.erl Normal file
View File

@ -0,0 +1,79 @@
-module(et_well).
-vsn("1.0.4").
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("MIT").
-export([new/0, new/2,
dimensions/1, height/1, width/1,
fetch/3, store/4, complete/1, collapse/2]).
-export_type([playfield/0]).
-opaque playfield() :: tuple().
new() ->
new(10, 20).
new(W, H) ->
erlang:make_tuple(H, row(W)).
row(W) ->
erlang:make_tuple(W, x).
dimensions(Well) ->
H = size(Well),
W = size(element(1, Well)),
{W, H}.
height(Well) ->
size(Well).
width(Well) ->
size(element(1, Well)).
fetch(Well, X, Y) ->
element(X, element(Y, Well)).
store(Well, Value, X, Y) ->
setelement(Y, Well, setelement(X, element(Y, Well), Value)).
complete(Well) ->
{W, H} = dimensions(Well),
complete(H, W, Well, []).
complete(Y, W, Well, Lines) when Y >= 1 ->
case line_complete(W, element(Y, Well)) of
true -> complete(Y - 1, W, Well, [Y | Lines]);
false -> complete(Y - 1, W, Well, Lines)
end;
complete(_, _, _, Lines) ->
Lines.
line_complete(X, Line) when X >= 1 ->
case element(X, Line) of
x -> false;
_ -> line_complete(X - 1, Line)
end;
line_complete(_, _) ->
true.
collapse(Well, Lines) ->
Blank = row(width(Well)),
Crunch =
fun(L, {W, Count}) ->
Crunched = erlang:insert_element(1, erlang:delete_element(L, W), Blank),
{Crunched, Count + 1}
end,
lists:foldl(Crunch, {Well, 0}, Lines).

View File

@ -142,7 +142,7 @@ loop(Parent, Debug, State = #s{socket = Socket, next = Next0}) ->
%% should trigger bad request
tell(error, "~p QHL parse error: ~tp", [?LINE, Error]),
tell(error, "~p bad request:~n~ts", [?LINE, Received]),
http_err(Socket, 400),
fd_http_utils:http_err(Socket, 400),
gen_tcp:shutdown(Socket, read_write),
exit(normal)
end;
@ -240,10 +240,10 @@ route(Sock, get, Route, Request, Received) ->
route(Sock, post, Route, Request, Received) ->
case Route of
<<"/wfcin">> -> wfcin(Sock, Request) , Received;
_ -> http_err(Sock, 404) , Received
_ -> fd_http_utils:http_err(Sock, 404) , Received
end;
route(Sock, _, _, _, Received) ->
http_err(Sock, 404),
fd_http_utils:http_err(Sock, 404),
Received.
@ -275,9 +275,9 @@ respond_static(Sock, {found, Entry}) ->
Headers1 = [{"content-type", fd_sfc_entry:mime_type(Entry)} | Headers0],
Response = #response{headers = Headers1,
body = fd_sfc_entry:contents(Entry)},
respond(Sock, Response);
fd_http_utils:respond(Sock, Response);
respond_static(Sock, not_found) ->
http_err(Sock, 404).
fd_http_utils:http_err(Sock, 404).
%% ------------------------------
@ -291,13 +291,7 @@ respond_static(Sock, not_found) ->
NewReceived :: binary().
ws_tetris(Sock, Request, Received) ->
try
ws_tetris2(Sock, Request, Received)
catch
X:Y:Z ->
tell(error, "CRASH ws_tetris: ~tp:~tp:~tp", [X, Y, Z]),
http_err(Sock, 500)
end.
.
@ -311,35 +305,41 @@ ws_tetris2(Sock, Request, Received) ->
%tell("~p: ws_tetris request: ~tp", [?LINE, Request]),
case fd_ws:handshake(Request) of
{ok, Response} ->
respond(Sock, Response),
{ok, _} = fd_tetris:start_link(),
ws_tetris_loop(Sock, [], Received);
fd_http_utils:respond(Sock, Response),
{ok, TetrisPid} = fd_tetris:start_link(),
ws_tetris_loop(Sock, TetrisPid, [], Received);
Error ->
tell("ws_tetris: error: ~tp", [Error]),
http_err(Sock, 400)
fd_http_utils:http_err(Sock, 400)
end.
-spec ws_tetris_loop(Sock, Frames, Received) -> NewReceived
-spec ws_tetris_loop(Sock, Tetris, Frames, Received) -> NewReceived
when Sock :: gen_tcp:socket(),
Tetris :: pid(),
Frames :: [fd_ws:frame()],
Received :: binary(),
NewReceived :: binary().
ws_tetris_loop(Sock, Frames, Received) ->
tell("~p:ws_tetris_loop(Sock, ~p, ~p)", [?MODULE, Frames, Received]),
ws_tetris_loop(Sock, Tetris, Frames, Received) ->
tell("~p:ws_tetris_loop(Sock, ~p, ~p, ~p)", [?MODULE, Tetris, Frames, Received]),
%% create tetris state
case inet:setopts(Sock, [{active, once}]) of
ok ->
receive
{tcp, Sock, Bin} ->
Rcv1 = <<Received/binary, Bin/binary>>,
ok = tell("~p:~p rcv1: ~tp", [?MODULE, ?LINE, Rcv1]),
ws_tetris_loop(Sock, Frames, <<>>);
case fd_ws:recv(Sock, Rcv1, 3_000, Frames) of
{ok, WsMsg, NewFrames, Rcv2} ->
ok = fd_tetris:ws_msg(Tetris, WsMsg),
ws_tetris_loop(Sock, Tetris, NewFrames, Rcv2);
Error ->
error(Error)
end;
{tetris, Message} ->
ok = tell("tetris: ~p", [Message]),
ok = log(info, "~p tetris: ~p", [self(), Message]),
ok = fd_ws:send(Sock, {text, Message}),
ws_tetris_loop(Sock, Frames, Received);
ws_tetris_loop(Sock, Tetris, Frames, Received);
{tcp_closed, Sock} -> {error, tcp_closed};
{tcp_error, Sock, Reason} -> {error, {tcp_error, Reason}}
after 30_000 ->
@ -359,17 +359,17 @@ ws_echo(Sock, Request) ->
catch
X:Y:Z ->
tell(error, "CRASH ws_echo: ~tp:~tp:~tp", [X, Y, Z]),
http_err(Sock, 500)
fd_http_utils:http_err(Sock, 500)
end.
ws_echo2(Sock, Request) ->
case fd_ws:handshake(Request) of
{ok, Response} ->
respond(Sock, Response),
fd_http_utils:respond(Sock, Response),
ws_echo_loop(Sock);
Error ->
tell("ws_echo: error: ~tp", [Error]),
http_err(Sock, 400)
fd_http_utils:http_err(Sock, 400)
end.
ws_echo_loop(Sock) ->
@ -389,6 +389,11 @@ ws_echo_loop(Sock, Frames, Received) ->
error(Error)
end.
%% ------------------------------
%% wfc
%% ------------------------------
wfcin(Sock, #request{enctype = json,
cookies = Cookies,
body = #{"wfcin" := Input}}) ->
@ -400,17 +405,17 @@ wfcin(Sock, #request{enctype = json,
case wfc_read:expr(Input) of
{ok, Expr, _Rest} ->
case wfc_eval:eval(Expr, Ctx0) of
{ok, noop, Ctx1} -> {jsgud("<noop>"), Ctx1};
{ok, Sentence, Ctx1} -> {jsgud(wfc_pp:sentence(Sentence)), Ctx1};
{error, Message} -> {jsbad(Message), Ctx0}
{ok, noop, Ctx1} -> {fd_http_utils:jsgud("<noop>"), Ctx1};
{ok, Sentence, Ctx1} -> {fd_http_utils:jsgud(wfc_pp:sentence(Sentence)), Ctx1};
{error, Message} -> {fd_http_utils:jsbad(Message), Ctx0}
end;
{error, Message} ->
{jsbad(Message), Ctx0}
{fd_http_utils:jsbad(Message), Ctx0}
end
catch
error:E:S ->
ErrorMessage = unicode:characters_to_list(io_lib:format("parser crashed: ~p:~p", [E, S])),
{jsbad(ErrorMessage), Ctx0}
{fd_http_utils:jsbad(ErrorMessage), Ctx0}
end,
% update cache with new context
ok = fd_cache:set(Cookie, NewCtx),
@ -418,10 +423,10 @@ wfcin(Sock, #request{enctype = json,
Response = #response{headers = [{"content-type", "application/json"},
{"set-cookie", ["wfc=", Cookie]}],
body = Body},
respond(Sock, Response);
fd_http_utils:respond(Sock, Response);
wfcin(Sock, Request) ->
tell("wfcin: bad request: ~tp", [Request]),
http_err(Sock, 400).
fd_http_utils:http_err(Sock, 400).
@ -436,110 +441,12 @@ ctx(#{<<"wfc">> := Cookie}) ->
error -> {Cookie, wfc_eval_context:default()}
end;
ctx(_) ->
{new_cookie(), wfc_eval_context:default()}.
{fd_http_utils:new_cookie(), wfc_eval_context:default()}.
-spec new_cookie() -> Cookie
when Cookie :: binary().
new_cookie() ->
binary:encode_hex(crypto:strong_rand_bytes(8)).
-spec jsgud(JSON) -> Encodable
when JSON :: zj:value(),
Encodable :: JSON.
jsgud(X) ->
#{"ok" => true,
"result" => X}.
-spec jsbad(JSON) -> JSBad
when JSON :: zj:value(),
JSBad :: zj:value().
jsbad(X) ->
#{"ok" => false,
"error" => X}.
-spec http_err(Socket, ErrorCode) -> ok
when Socket :: gen_tcp:socket(),
ErrorCode :: integer().
http_err(Sock, N) ->
Slogan = qhl:slogan(N),
Body = ["<!doctype html>"
"<html lang=\"en\">"
"<head>"
"<meta charset=\"utf-8\">"
"<title>QHL: ", integer_to_list(N), " ", Slogan, "</title>"
"</head>"
"<body>"
"<h1>"
"QHL: ", integer_to_list(N), " ", Slogan,
"</h1>"
"</body>"
"</html>"],
Resp = #response{code = N,
headers = [{"content/type", "text/html"}],
body = Body},
respond(Sock, Resp).
-spec respond(Sock, Response) -> ok
when Sock :: gen_tcp:socket(),
Response :: response().
respond(Sock, Response = #response{code = Code}) ->
tell("~tp ~tp ~ts", [self(), Code, qhl:slogan(Code)]),
gen_tcp:send(Sock, fmtresp(Response)).
-spec fmtresp(Response) -> Formatted
when Response :: response(),
Formatted :: iolist().
fmtresp(#response{type = page, %% no idea what {data, String} is
version = http11,
code = Code,
headers = Hs,
body = Body}) ->
%% need byte size for binary
Headers = add_headers(Hs, Body),
[io_lib:format("HTTP/1.1 ~tp ~ts", [Code, qhl:slogan(Code)]), "\r\n",
[io_lib:format("~ts: ~ts\r\n", [K, V]) || {K, V} <- Headers],
"\r\n",
Body].
-spec add_headers(Existing, Body) -> Hdrs
when Existing :: [{iolist(), iolist()}],
Body :: iolist(),
Hdrs :: [{iolist(), iolist()}].
%% body needed just for size
add_headers(Hs, Body) ->
Defaults = default_headers(Body),
Hs2 = proplists:to_map(Hs),
proplists:from_map(maps:merge(Defaults, Hs2)).
-spec default_headers(Body) -> HdrsMap
when Body :: iolist(),
HdrsMap :: #{iolist() := iolist()}.
default_headers(Body) ->
BodySize = byte_size(iolist_to_binary(Body)),
#{"Server" => "fewd 0.1.0",
"Date" => qhl:ridiculous_web_date(),
"Content-Length" => io_lib:format("~p", [BodySize])}.

115
src/fd_http_utils.erl Normal file
View File

@ -0,0 +1,115 @@
% @doc http utility functions
-module(fd_http_utils).
-export([
new_cookie/0,
jsgud/1, jsbad/1,
http_err/2,
respond/2,
fmtresp/1
])
-spec new_cookie() -> Cookie
when Cookie :: binary().
new_cookie() ->
binary:encode_hex(crypto:strong_rand_bytes(8)).
-spec jsgud(JSON) -> Encodable
when JSON :: zj:value(),
Encodable :: JSON.
jsgud(X) ->
#{"ok" => true,
"result" => X}.
-spec jsbad(JSON) -> JSBad
when JSON :: zj:value(),
JSBad :: zj:value().
jsbad(X) ->
#{"ok" => false,
"error" => X}.
-spec http_err(Socket, ErrorCode) -> ok
when Socket :: gen_tcp:socket(),
ErrorCode :: integer().
http_err(Sock, N) ->
Slogan = qhl:slogan(N),
Body = ["<!doctype html>"
"<html lang=\"en\">"
"<head>"
"<meta charset=\"utf-8\">"
"<title>QHL: ", integer_to_list(N), " ", Slogan, "</title>"
"</head>"
"<body>"
"<h1>"
"QHL: ", integer_to_list(N), " ", Slogan,
"</h1>"
"</body>"
"</html>"],
Resp = #response{code = N,
headers = [{"content/type", "text/html"}],
body = Body},
respond(Sock, Resp).
-spec respond(Sock, Response) -> ok
when Sock :: gen_tcp:socket(),
Response :: response().
respond(Sock, Response = #response{code = Code}) ->
tell("~tp ~tp ~ts", [self(), Code, qhl:slogan(Code)]),
gen_tcp:send(Sock, fmtresp(Response)).
-spec fmtresp(Response) -> Formatted
when Response :: response(),
Formatted :: iolist().
fmtresp(#response{type = page, %% no idea what {data, String} is
version = http11,
code = Code,
headers = Hs,
body = Body}) ->
%% need byte size for binary
Headers = add_headers(Hs, Body),
[io_lib:format("HTTP/1.1 ~tp ~ts", [Code, qhl:slogan(Code)]), "\r\n",
[io_lib:format("~ts: ~ts\r\n", [K, V]) || {K, V} <- Headers],
"\r\n",
Body].
-spec add_headers(Existing, Body) -> Hdrs
when Existing :: [{iolist(), iolist()}],
Body :: iolist(),
Hdrs :: [{iolist(), iolist()}].
%% body needed just for size
add_headers(Hs, Body) ->
Defaults = default_headers(Body),
Hs2 = proplists:to_map(Hs),
proplists:from_map(maps:merge(Defaults, Hs2)).
-spec default_headers(Body) -> HdrsMap
when Body :: iolist(),
HdrsMap :: #{iolist() := iolist()}.
default_headers(Body) ->
BodySize = byte_size(iolist_to_binary(Body)),
#{"Server" => "fewd 0.1.0",
"Date" => qhl:ridiculous_web_date(),
"Content-Length" => io_lib:format("~p", [BodySize])}.

View File

@ -2,7 +2,11 @@
%
% manages state for a single game of tetris
%
% https://www.erlang.org/docs/24/man/gen_server
% sends parent process messages `{tetris, String}` where String is an encoded
% JSON blob meant to be sent to the page script in /priv/static/js/ts/tetris.ts
%
% Refs:
% 1. https://www.erlang.org/docs/24/man/gen_server
-module(fd_tetris).
-behavior(gen_server).
@ -27,6 +31,14 @@
%% caller context below this line
%%-----------------------------------------------------------------------------
-spec ws_msg(Tetris, Message) -> ok
when Tetris :: pid(),
Message :: fd_ws:ws_msg().
ws_msg(Tetris, Msg) ->
gen_server:cast(Tetris, {ws_msg, Msg}).
-spec start_link() -> {ok, pid()} | {error, term()}.
start_link() ->
gen_server:start_link(?MODULE, [self()], []).

View File

@ -65,10 +65,8 @@ day() -> 24*hr().
-spec handshake(Req) -> Result
when Req :: request(),
Result :: {ok, ClientProtocols, ClientExtensions, DraftResponse}
Result :: {ok, DraftResponse}
| {error, Reason},
ClientProtocols :: [binary()],
ClientExtensions :: binary(),
DraftResponse :: response(),
Reason :: any().
% @doc
@ -634,11 +632,11 @@ recv_frame_await(Frame, Sock, Received, Timeout) ->
% @end
send(Socket, {Type, Payload}) ->
tell("fd_ws: send(~tp, {~tp, ~tp})", [Socket, Type, Payload]),
log(info, "fd_ws: send(~tp, {~tp, ~tp})", [Socket, Type, Payload]),
BPayload = payload_to_binary(Payload),
tell("fd_ws: BPayload = ~tp", [BPayload]),
log(info, "fd_ws: BPayload = ~tp", [BPayload]),
Frame = message_to_frame(Type, BPayload),
tell("fd_ws: Frame = ~tp", [Frame]),
log(info, "fd_ws: Frame = ~tp", [Frame]),
send_frame(Socket, Frame).
payload_to_binary(Bin) when is_binary(Bin) -> Bin;
@ -677,7 +675,7 @@ message_to_frame(Control, Payload)
send_frame(Sock, Frame) ->
Binary = render_frame(Frame),
tell("send_frame: rendered frame: ~tp", [Binary]),
log(info, "send_frame: rendered frame: ~tp", [Binary]),
gen_tcp:send(Sock, Binary).

102
src/fd_wsp.erl Normal file
View File

@ -0,0 +1,102 @@
% @doc Abstracts a web socket into a process
%
% hands the TCP socket over to this process, also this process does the
% handshake.
%
% this process sends back `{ws, self(), Message: fd_ws:ws_msg()}'
%
% for each websocket message it gets
-module(fd_wsp).
-behavior(gen_server).
-export_type([
]).
-export([
%% caller context
handshake/0,
start_link/0,
%% process context
init/1, handle_call/3, handle_cast/2, handle_info/2,
code_change/3, terminate/2
]).
-include("http.hrl").
-include("$zx_include/zx_logger.hrl").
-record(s, {socket :: gen_tcp:socket()})
-type state() :: #s{}.
%%-----------------------------------------------------------------------------
%% caller context
%%-----------------------------------------------------------------------------
-spec start_link(Socket, HandshakeReq, Received) -> Result
when Socket :: gen_tcp:socket(),
HandshakeReq :: request(),
Received :: binary(),
Result :: {ok, pid()}
| {error, term()}.
% @doc
% starts a websocket and hands control of socket over to child process
start_link(Socket, HandshakeReq, Received) ->
case gen_server:start_link(?MODULE, [Socket, HandshakeReq, Received], []) of
{ok, PID} ->
gen_tcp:controlling_process(Socket, PID),
{ok, PID};
Error ->
Error
end.
%%-----------------------------------------------------------------------------
%% process context below this line
%%-----------------------------------------------------------------------------
%% gen_server callbacks
init([Socket, HandshakeReq, Received]) ->
log("~p:~p init", [?MODULE, self()]),
case fd_ws:handshake(HandshakeReq) of
{ok, Response} ->
ok = fd_http_utils:respond(Sock, Response),
InitState = #s{socket = Socket},
Error ->
tell("~p:~p websocket handshake err: ~p", [?MODULE, self(), Error]),
fd_http_utils:http_err(Socket, 400)
Error
end.
handle_call(Unexpected, From, State) ->
tell("~tp: unexpected call from ~tp: ~tp", [?MODULE, Unexpected, From]),
{noreply, State}.
handle_cast(Unexpected, State) ->
tell("~tp: unexpected cast: ~tp", [?MODULE, Unexpected]),
{noreply, State}.
handle_info({tcp, Sock, Bytes}, State = #s{socket = Sock}) ->
handle_info(Unexpected, State) ->
tell("~tp: unexpected info: ~tp", [?MODULE, Unexpected]),
{noreply, State}.
code_change(_, State, _) ->
{ok, State}.
terminate(_, _) ->
ok.
%%-----------------------------------------------------------------------------
%% internals
%%-----------------------------------------------------------------------------