Просмотр исходного кода

Add Transport:sendfile/4,/5

Adds offset based sendfile to transports. Same behaviour as
file:sendfile/4,/5 except socket and file arguments are reversed and
either a raw file or a filename can be used.

sendfile/2,/4,/5 now compulsory callbacks in ranch_transport.

ranch_tcp:sendfile/2 now defaults to a chunk_size of 8191 - the default
for ranch_ssl:sendfile/2. The same default is used for both
ranch_tcp:sendfile/4,5 and ranch_ssl:sendfile/4,5.
James Fish 12 лет назад
Родитель
Сommit
ca6817880e
6 измененных файлов с 558 добавлено и 33 удалено
  1. 1 1
      Makefile
  2. 32 0
      guide/transports.md
  3. 24 23
      src/ranch_ssl.erl
  4. 42 9
      src/ranch_tcp.erl
  5. 108 0
      src/ranch_transport.erl
  6. 351 0
      test/sendfile_SUITE.erl

+ 1 - 1
Makefile

@@ -10,7 +10,7 @@ dep_ct_helper = https://github.com/extend/ct_helper.git master
 # Options.
 
 COMPILE_FIRST = ranch_transport
-CT_SUITES = acceptor
+CT_SUITES = acceptor sendfile
 PLT_APPS = crypto public_key ssl
 
 # Standard targets.

+ 32 - 0
guide/transports.md

@@ -119,6 +119,34 @@ end.
 You can easily integrate active sockets with existing Erlang code as all
 you really need is just a few more clauses when receiving messages.
 
+Sending files
+-------------
+
+As in the previous section it is assumed `Transport` is a valid transport
+handler and `Socket` is a connected socket obtained through the listener.
+
+To send a whole file, with name `Filename`, over a socket:
+
+```erlang
+{ok, SentBytes} = Transport:sendfile(Socket, Filename).
+```
+
+Or part of a file, with `Offset` greater than or equal to 0, `Bytes` number of
+bytes and chunks of size `ChunkSize`:
+
+```erlang
+Opts = [{chunk_size, ChunkSize}],
+{ok, SentBytes} = Transport:sendfile(Socket, Filename, Offset, Bytes, Opts).
+```
+
+To improve efficiency when sending multiple parts of the same file it is also
+possible to use a file descriptor opened in raw mode:
+
+```erlang
+{ok, RawFile} = file:open(Filename, [raw, read, binary]),
+{ok, SentBytes} = Transport:sendfile(Socket, RawFile, Offset, Bytes, Opts).
+```
+
 Writing a transport handler
 ---------------------------
 
@@ -131,3 +159,7 @@ socket. These do not need to be common to all transports as it's easy enough
 to write different initialization functions for the different transports that
 will be used. With one exception though. The `setopts/2` function *must*
 implement the `{active, once}` and the `{active, true}` options.
+
+If the transport handler doesn't have a native implementation of `sendfile/5` a
+fallback is available, `ranch_transport:sendfile/6`. The extra first argument
+is the transport's module. See `ranch_ssl` for an example.

+ 24 - 23
src/ranch_ssl.erl

@@ -34,6 +34,8 @@
 -export([recv/3]).
 -export([send/2]).
 -export([sendfile/2]).
+-export([sendfile/4]).
+-export([sendfile/5]).
 -export([setopts/2]).
 -export([controlling_process/2]).
 -export([peername/1]).
@@ -188,33 +190,32 @@ recv(Socket, Length, Timeout) ->
 send(Socket, Packet) ->
 	ssl:send(Socket, Packet).
 
-%% @doc Send a file on a socket.
+%% @equiv sendfile(Socket, Filename, 0, 0, [])
+-spec sendfile(ssl:sslsocket(), file:name_all())
+	-> {ok, non_neg_integer()} | {error, atom()}.
+sendfile(Socket, Filename) ->
+	sendfile(Socket, Filename, 0, 0, []).
+
+%% @equiv sendfile(Socket, File, Offset, Bytes, [])
+-spec sendfile(ssl:sslsocket(), file:name_all() | file:fd(),
+		non_neg_integer(), non_neg_integer())
+	-> {ok, non_neg_integer()} | {error, atom()}.
+sendfile(Socket, File, Offset, Bytes) ->
+	sendfile(Socket, File, Offset, Bytes, []).
+
+%% @doc Send part of a file on a socket.
 %%
 %% Unlike with TCP, no syscall can be used here, so sending files
-%% through SSL will be much slower in comparison.
+%% through SSL will be much slower in comparison. Note that unlike
+%% file:sendfile/5 this function accepts either a file or a file name.
 %%
-%% @see file:sendfile/2
--spec sendfile(ssl:sslsocket(), file:name())
+%% @see ranch_transport:sendfile/6
+%% @see file:sendfile/5
+-spec sendfile(ssl:sslsocket(), file:name_all() | file:fd(),
+		non_neg_integer(), non_neg_integer(), ranch_transport:sendfile_opts())
 	-> {ok, non_neg_integer()} | {error, atom()}.
-sendfile(Socket, Filepath) ->
-	{ok, IoDevice} = file:open(Filepath, [read, binary, raw]),
-	sendfile(Socket, IoDevice, 0).
-
--spec sendfile(ssl:sslsocket(), file:io_device(), non_neg_integer())
-	-> {ok, non_neg_integer()} | {error, atom()}.
-sendfile(Socket, IoDevice, Sent) ->
-	case file:read(IoDevice, 16#1FFF) of
-		eof ->
-			ok = file:close(IoDevice),
-			{ok, Sent};
-		{ok, Bin} ->
-			case send(Socket, Bin) of
-				ok ->
-					sendfile(Socket, IoDevice, Sent + byte_size(Bin));
-				{error, Reason} ->
-					{error, Reason}
-			end
-	end.
+sendfile(Socket, File, Offset, Bytes, Opts) ->
+	ranch_transport:sendfile(?MODULE, Socket, File, Offset, Bytes, Opts).
 
 %% @doc Set options on the given socket.
 %% @see ssl:setopts/2

+ 42 - 9
src/ranch_tcp.erl

@@ -28,6 +28,8 @@
 -export([recv/3]).
 -export([send/2]).
 -export([sendfile/2]).
+-export([sendfile/4]).
+-export([sendfile/5]).
 -export([setopts/2]).
 -export([controlling_process/2]).
 -export([peername/1]).
@@ -110,21 +112,52 @@ recv(Socket, Length, Timeout) ->
 send(Socket, Packet) ->
 	gen_tcp:send(Socket, Packet).
 
-%% @doc Send a file on a socket.
+%% @equiv sendfile(Socket, File, Offset, Bytes, [])
+-spec sendfile(inet:socket(), file:name_all())
+	-> {ok, non_neg_integer()} | {error, atom()}.
+sendfile(Socket, Filename) ->
+	sendfile(Socket, Filename, 0, 0, []).
+
+%% @equiv sendfile(Socket, File, Offset, Bytes, [])
+-spec sendfile(inet:socket(), file:name_all() | file:fd(), non_neg_integer(),
+		non_neg_integer())
+	-> {ok, non_neg_integer()} | {error, atom()}.
+sendfile(Socket, File, Offset, Bytes) ->
+	sendfile(Socket, File, Offset, Bytes, []).
+
+%% @doc Send part of a file on a socket.
 %%
-%% This is the optimal way to send files using TCP. It uses a syscall
-%% which means there is no context switch between opening the file
-%% and writing its contents on the socket.
+%% As with sendfile/2 this is the optimal way to send (parts) of files using
+%% TCP. Note that unlike file:sendfile/5 this function accepts either a raw file
+%% or a file name and the ordering of arguments is different.
 %%
-%% @see file:sendfile/2
--spec sendfile(inet:socket(), file:name())
+%% @see file:sendfile/5
+-spec sendfile(inet:socket(), file:name_all() | file:fd(), non_neg_integer(),
+		non_neg_integer(), [{chunk_size, non_neg_integer()}])
 	-> {ok, non_neg_integer()} | {error, atom()}.
-sendfile(Socket, Filename) ->
-	try file:sendfile(Filename, Socket) of
+sendfile(Socket, Filename, Offset, Bytes, Opts)
+		when is_list(Filename) orelse is_atom(Filename)
+		orelse is_binary(Filename) ->
+	case file:open(Filename, [read, raw, binary]) of
+		{ok, RawFile} ->
+			try sendfile(Socket, RawFile, Offset, Bytes, Opts) of
+				Result -> Result
+			after
+				ok = file:close(RawFile)
+			end;
+		{error, _} = Error ->
+			Error
+	end;
+sendfile(Socket, RawFile, Offset, Bytes, Opts) ->
+	Opts2 = case Opts of
+		[] -> [{chunk_size, 16#1FFF}];
+		_ -> Opts
+	end,
+	try file:sendfile(RawFile, Socket, Offset, Bytes, Opts2) of
 		Result -> Result
 	catch
 		error:{badmatch, {error, enotconn}} ->
-			%% file:sendfile/2 might fail by throwing a {badmatch, {error, enotconn}}
+			%% file:sendfile/5 might fail by throwing a {badmatch, {error, enotconn}}
 			%% this is because its internal implementation fails with a badmatch in
 			%% prim_file:sendfile/10 if the socket is not connected.
 			{error, closed}

+ 108 - 0
src/ranch_transport.erl

@@ -15,8 +15,12 @@
 %% @private
 -module(ranch_transport).
 
+-export([sendfile/6]).
+
 -type socket() :: any().
 -type opts() :: any().
+-type sendfile_opts() :: [{chunk_size, non_neg_integer()}].
+-export_type([sendfile_opts/0]).
 
 %% Name of the transport.
 -callback name() -> atom().
@@ -55,6 +59,19 @@
 %% Send data on a socket.
 -callback send(socket(), iodata()) -> ok | {error, atom()}.
 
+%% Send a file on a socket.
+-callback sendfile(socket(), file:name())
+	-> {ok, non_neg_integer()} | {error, atom()}.
+
+%% Send part of a file on a socket.
+-callback sendfile(socket(), file:name() | file:fd(), non_neg_integer(),
+		non_neg_integer()) -> {ok, non_neg_integer()} | {error, atom()}.
+
+%% Send part of a file on a socket.
+-callback sendfile(socket(), file:name() | file:fd(), non_neg_integer(),
+		non_neg_integer(), sendfile_opts())
+	-> {ok, non_neg_integer()} | {error, atom()}.
+
 %% Set options on the given socket.
 -callback setopts(socket(), opts()) -> ok | {error, atom()}.
 
@@ -75,3 +92,94 @@
 
 %% Close the given socket.
 -callback close(socket()) -> ok.
+
+%% @doc Send part of a file on a socket.
+%%
+%% A fallback for transports that don't have a native sendfile implementation.
+%% Note that the ordering of arguments is different from file:sendfile/5 and
+%% that this function accepts either a raw file or a file name.
+%%
+%% @see file:sendfile/5
+-spec sendfile(module(), socket(), file:filename_all() | file:fd(),
+		non_neg_integer(), non_neg_integer(), sendfile_opts())
+	-> {ok, non_neg_integer()} | {error, atom()}.
+sendfile(Transport, Socket, Filename, Offset, Bytes, Opts)
+		when is_list(Filename) orelse is_atom(Filename)
+		orelse is_binary(Filename) ->
+	ChunkSize = chunk_size(Opts),
+	case file:open(Filename, [read, raw, binary]) of
+		{ok, RawFile} ->
+			_ = case Offset of
+				0 ->
+					ok;
+				_ ->
+					{ok, _} = file:position(RawFile, {bof, Offset})
+			end,
+			try
+				sendfile_loop(Transport, Socket, RawFile, Bytes, 0, ChunkSize)
+			after
+				ok = file:close(RawFile)
+			end;
+		{error, _Reason} = Error ->
+			Error
+	end;
+sendfile(Transport, Socket, RawFile, Offset, Bytes, Opts) ->
+	ChunkSize = chunk_size(Opts),
+	Initial2 = case file:position(RawFile, {cur, 0}) of
+		{ok, Offset} ->
+			Offset;
+		{ok, Initial} ->
+			{ok, _} = file:position(RawFile, {bof, Offset}),
+			Initial
+		end,
+	case sendfile_loop(Transport, Socket, RawFile, Bytes, 0, ChunkSize) of
+		{ok, _Sent} = Result ->
+			{ok, _} = file:position(RawFile, {bof, Initial2}),
+			Result;
+		{error, _Reason} = Error ->
+			Error
+	end.
+
+-spec chunk_size(sendfile_opts()) -> pos_integer().
+chunk_size(Opts) ->
+	case lists:keyfind(chunk_size, 1, Opts) of
+		{chunk_size, ChunkSize}
+				when is_integer(ChunkSize) andalso ChunkSize > 0 ->
+			ChunkSize;
+		{chunk_size, 0} ->
+			16#1FFF;
+		false ->
+			16#1FFF
+	end.
+
+-spec sendfile_loop(module(), socket(), file:fd(), non_neg_integer(),
+		non_neg_integer(), pos_integer())
+	-> {ok, non_neg_integer()} | {error, term()}.
+sendfile_loop(_Transport, _Socket, _RawFile, Sent, Sent, _ChunkSize)
+		when Sent =/= 0 ->
+	%% All requested data has been read and sent, return number of bytes sent.
+	{ok, Sent};
+sendfile_loop(Transport, Socket, RawFile, Bytes, Sent, ChunkSize) ->
+	ReadSize = read_size(Bytes, Sent, ChunkSize),
+	case file:read(RawFile, ReadSize) of
+		{ok, IoData} ->
+			case Transport:send(Socket, IoData) of
+				ok ->
+					Sent2 = iolist_size(IoData) + Sent,
+					sendfile_loop(Transport, Socket, RawFile, Bytes, Sent2,
+						ChunkSize);
+				{error, _Reason} = Error ->
+					Error
+			end;
+		eof ->
+			{ok, Sent};
+		{error, _Reason} = Error ->
+			Error
+	end.
+
+-spec read_size(non_neg_integer(), non_neg_integer(), non_neg_integer()) ->
+	non_neg_integer().
+read_size(0, _Sent, ChunkSize) ->
+	ChunkSize;
+read_size(Bytes, Sent, ChunkSize) ->
+	min(Bytes - Sent, ChunkSize).

+ 351 - 0
test/sendfile_SUITE.erl

@@ -0,0 +1,351 @@
+%% Copyright (c) 2013, James Fish <james@fishcakez.com>
+%%
+%% Permission to use, copy, modify, and/or distribute this software for any
+%% purpose with or without fee is hereby granted, provided that the above
+%% copyright notice and this permission notice appear in all copies.
+%%
+%% THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
+%% WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
+%% MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
+%% ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
+%% WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
+%% ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
+%% OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
+
+-module(sendfile_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+
+%% ct.
+-export([all/0]).
+-export([suite/0]).
+-export([groups/0]).
+-export([init_per_suite/1]).
+-export([end_per_suite/1]).
+-export([init_per_group/2]).
+-export([end_per_group/2]).
+
+%% Tests.
+-export([filename/1]).
+-export([rawfile/1]).
+-export([rawfile_bytes_large/1]).
+-export([rawfile_bytes_zero/1]).
+-export([rawfile_chunk_size_large/1]).
+-export([rawfile_offset_large/1]).
+-export([rawfile_range_large/1]).
+-export([rawfile_range_medium/1]).
+-export([rawfile_range_small/1]).
+-export([ssl_chunk_size/1]).
+
+all() ->
+	[{group, tcp}, {group, ssl}].
+
+suite() ->
+	[{timetrap, {seconds, 60}}].
+
+groups() ->
+	Tests = [
+		filename,
+		rawfile,
+		rawfile_bytes_large,
+		rawfile_bytes_zero,
+		rawfile_chunk_size_large,
+		rawfile_offset_large,
+		rawfile_range_large,
+		rawfile_range_medium,
+		rawfile_range_small
+	],
+	[{tcp, [parallel], Tests}, {ssl, [parallel], Tests ++ [ssl_chunk_size]}].
+
+init_per_suite(Config) ->
+	ok = application:start(ranch),
+	ok = application:start(crypto),
+	Filename = filename:join(?config(priv_dir, Config), "sendfile"),
+	Binary = crypto:rand_bytes(20 * 1024 * 1024),
+	ok = file:write_file(Filename, Binary),
+	[{filename, Filename} | Config].
+
+end_per_suite(Config) ->
+	application:stop(ranch),
+	application:stop(crypto),
+	Filename = ?config(filename, Config),
+	ok = file:delete(Filename),
+	ok.
+
+init_per_group(ssl, Config) ->
+	application:start(asn1),
+	application:start(public_key),
+	application:start(ssl),
+	{_, Cert, Key} = ct_helper:make_certs(),
+	SslOpts = [{cert, Cert}, {key, Key}],
+	[{transport, ranch_ssl}, {transport_opts, SslOpts} | Config];
+init_per_group(tcp, Config) ->
+	[{transport, ranch_tcp}, {transport_opts, []} | Config].
+
+end_per_group(ssl, _) ->
+	application:stop(ssl),
+	application:stop(public_key),
+	application:stop(asn1),
+	ok;
+end_per_group(_, _) ->
+	ok.
+
+%% Check can send a whole file given with filename.
+filename(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	Ref = recv(Transport, Server, Size),
+	{ok, Size} = Transport:sendfile(Client, Filename),
+	{ok, Binary} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check can send a whole file with rawfile.
+rawfile(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	Ref = recv(Transport, Server, Size),
+	{ok, Size} = Transport:sendfile(Client, RawFile, 0, Size),
+	{ok, Binary} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	{ok, 0} = file:position(RawFile, {cur, 0}),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check can send a file where Bytes is larger than file size.
+rawfile_bytes_large(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	Ref = recv(Transport, Server, Size),
+	%% Only send Size not Size * 2
+	{ok, Size} = Transport:sendfile(Client, RawFile, 0, Size * 2),
+	{ok, Binary} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	{ok, 0} = file:position(RawFile, {cur, 0}),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check can send whole file when Bytes =:= 0.
+rawfile_bytes_zero(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	Ref = recv(Transport, Server, Size),
+	{ok, Size} = Transport:sendfile(Client, RawFile, 0, 0),
+	{ok, Binary} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	{ok, 0} = file:position(RawFile, {cur, 0}),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check can send file where chunk_size is greater than file size.
+rawfile_chunk_size_large(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	Ref = recv(Transport, Server, Size),
+	{ok, Size} = Transport:sendfile(Client, RawFile, 0, Size,
+			[{chunk_size, Size * 2}]),
+	{ok, Binary} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	{ok, 0} = file:position(RawFile, {cur, 0}),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check send file where offset is larger than file size sends no bytes and
+%% returns {ok, 0}.
+rawfile_offset_large(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	{ok, 0} = Transport:sendfile(Client, RawFile, Size, 1),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check can send file with positive Offset and Offset + Bytes larger than file
+%% size.
+rawfile_range_large(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	Initial = 499,
+	{ok, _} = file:position(RawFile, {bof, Initial}),
+	Offset = 75,
+	Bytes = Size * 2,
+	Sent = Size - Offset,
+	Ref = recv(Transport, Server, Sent),
+	{ok, Sent} = Transport:sendfile(Client, RawFile, Offset, Bytes),
+	Binary2 = binary:part(Binary, Offset, Sent),
+	{ok, Binary2} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	{ok, Initial} = file:position(RawFile, {cur, 0}),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check can send file with positive Offset and Offset + Bytes less than file
+%% size.
+rawfile_range_medium(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	Initial = 50,
+	{ok, _} = file:position(RawFile, {bof, Initial}),
+	Offset = 50,
+	Bytes = Size - Offset - 50,
+	Ref = recv(Transport, Server, Bytes),
+	{ok, Bytes} = Transport:sendfile(Client, RawFile, Offset, Bytes),
+	Binary2 = binary:part(Binary, Offset, Bytes),
+	{ok, Binary2} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	{ok, Initial} = file:position(RawFile, {cur, 0}),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check can send file with positive Offset, Offset + Bytes less than file
+%% size and Bytes less than chunk_size.
+rawfile_range_small(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	{ok, {Server, Client}} = sockets(Config),
+	{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+	Initial = 3,
+	{ok, _} = file:position(RawFile, {bof, Initial}),
+	Offset = 7,
+	Bytes = 19,
+	Ref = recv(Transport, Server, Bytes),
+	{ok, Bytes} = Transport:sendfile(Client, RawFile, Offset, Bytes,
+			[{chunk_size, 16#FFFF}]),
+	Binary2 = binary:part(Binary, Offset, Bytes),
+	{ok, Binary2} = result(Ref),
+	{error, timeout} = Transport:recv(Server, 1, 100),
+	{ok, Initial} = file:position(RawFile, {cur, 0}),
+	ok = file:close(RawFile),
+	ok = Transport:close(Client),
+	ok = Transport:close(Server).
+
+%% Check ssl obeys chunk_size.
+ssl_chunk_size(Config) ->
+	Transport = ?config(transport, Config),
+	Filename = ?config(filename, Config),
+	{ok, Binary} = file:read_file(Filename),
+	Size = byte_size(Binary),
+	Self = self(),
+	ChunkSize = 8 * 1024,
+	Fun = fun() ->
+		receive go -> ok after 1000 -> error(timeout) end,
+		{ok, {Server, Client}} = sockets(Config),
+		{ok, RawFile} = file:open(Filename, [read, raw, binary]),
+		Ref = recv(Transport, Server, Size),
+		{ok, Size} = Transport:sendfile(Client, RawFile, 0, Size,
+				[{chunk_size, ChunkSize}]),
+		{ok, Binary} = result(Ref),
+		{error, timeout} = Transport:recv(Server, 1, 100),
+		Self ! done,
+		ok = file:close(RawFile),
+		ok = Transport:close(Client),
+		ok = Transport:close(Server)
+	end,
+	Pid = spawn_link(Fun),
+	1 = erlang:trace(Pid, true, [call]),
+	_ = erlang:trace_pattern({Transport, send, 2}, true, [global]),
+	Pid ! go,
+	receive done -> ok after 30000 -> error(timeout) end,
+	Sizes = lists:duplicate(Size div ChunkSize, ChunkSize) ++
+		[Size rem ChunkSize || (Size rem ChunkSize) =/= 0],
+	ok = recv_send_trace(Sizes, Pid),
+	_ = erlang:trace(all, false, [all]),
+	ok = clean_traces().
+
+sockets(Config) ->
+	Transport = ?config(transport, Config),
+	TransportOpts = ?config(transport_opts, Config),
+	{ok, LSocket} = Transport:listen(TransportOpts),
+	{ok, {_, Port}} = Transport:sockname(LSocket),
+	Self = self(),
+	Fun = fun() ->
+		{ok, Client} = Transport:connect("localhost", Port, TransportOpts),
+		ok = Transport:controlling_process(Client, Self),
+		Self ! {ok, Client}
+	end,
+	_ = spawn_link(Fun),
+	{ok, Server} = Transport:accept(LSocket, 500),
+	receive
+		{ok, Client} ->
+			ok = Transport:close(LSocket),
+			{ok, {Server, Client}}
+	after 1000 ->
+		{error, timeout}
+	end.
+
+recv(Transport, Server, Size) ->
+	Self = self(),
+	Ref = make_ref(),
+	spawn_link(fun() -> Self ! {Ref, Transport:recv(Server, Size, 20000)} end),
+	Ref.
+
+result(Ref) ->
+	receive
+		{Ref, Result} ->
+			Result
+	after
+		30000 ->
+			{error, result_timedout}
+	end.
+
+recv_send_trace([], _Pid) ->
+	ok;
+recv_send_trace([Size | Rest], Pid) ->
+	receive
+		{trace, Pid, call, {_, _, [_, Chunk]}} when byte_size(Chunk) == Size ->
+			recv_send_trace(Rest, Pid);
+		{trace, Pid, call, {_, _, [_, Chunk]}} ->
+			{error, {invalid_chunk, Size, byte_size(Chunk)}}
+	after 1000 ->
+		{error, timeout}
+	end.
+
+clean_traces() ->
+	receive
+		{trace, _, _, _} ->
+			clean_traces();
+		{trace, _, _, _, _} ->
+			clean_traces()
+	after 0 ->
+		ok
+	end.