ct_telnet
Common Test specific layer on top of telnet client ct_telnet_client.erl.
Common Test specific layer on top of telnet client ct_telnet_client.erl
Use this module to set up telnet connections, send commands and
perform string matching on the result.
See the unix_telnet
manual page for information about how to use
ct_telnet, and configure connections, specifically for unix hosts.
The following default values are defined in ct_telnet:
Connection timeout = 10 sec (time to wait for connection) Command timeout = 10 sec (time to wait for a command to return) Max no of reconnection attempts = 3 Reconnection interval = 5 sek (time to wait in between reconnection attempts) Keep alive = true (will send NOP to the server every 10 sec if connection is idle)
These parameters can be altered by the user with the following configuration term:
{telnet_settings, [{connect_timeout,Millisec}, {command_timeout,Millisec}, {reconnection_attempts,N}, {reconnection_interval,Millisec}, {keep_alive,Bool}]}.
Millisec = integer(), N = integer()
Enter the telnet_settings
term in a configuration
file included in the test and ct_telnet will retrieve the information
automatically. Note that keep_alive
may be specified per connection if
required. See unix_telnet
for details.
DATA TYPES
connection() = handle() | {target_name() (see module ct), connection_type()} | target_name() (see module ct)
connection_type() = telnet | ts1 | ts2
handle() = handle() (see module ct_gen_conn)
Handle for a specific telnet connection.
prompt_regexp() = string()
A regular expression which matches all possible prompts for a specific type of target. The regexp must not have any groups i.e. when matching, re:run/3 shall return a list with one single element.
Functions
open(Name) -> {ok, Handle} | {error, Reason}
Equivalent to open(Name, telnet).
open(Name, ConnType) -> {ok, Handle} | {error, Reason}
Name = target_name()
ConnType = connection_type() (see module ct_telnet)
Handle = handle() (see module ct_telnet)
Open a telnet connection to the specified target host.
open(KeyOrName, ConnType, TargetMod) -> {ok, Handle} | {error, Reason}
Equivalent to open(KeyOrName, ConnType, TargetMod, []).
open(KeyOrName, ConnType, TargetMod, Extra) -> {ok, Handle} | {error, Reason}
KeyOrName = Key | Name
Key = atom()
Name = target_name() (see module ct)
ConnType = connection_type()
TargetMod = atom()
Extra = term()
Handle = handle()
Open a telnet connection to the specified target host.
The target data must exist in a configuration file. The connection
may be associated with either Name
and/or the returned
Handle
. To allocate a name for the target,
use ct:require/2
in a test case, or use a
require
statement in the suite info function
(suite/0
), or in a test case info function.
If you want the connection to be associated with Handle
only
(in case you need to open multiple connections to a host for example),
simply use Key
, the configuration variable name, to
specify the target. Note that a connection that has no associated target
name can only be closed with the handle value.
TargetMod
is a module which exports the functions
connect(Ip,Port,KeepAlive,Extra)
and get_prompt_regexp()
for the given TargetType
(e.g. unix_telnet
).
See also: ct:require/2.
close(Connection) -> ok | {error, Reason}
Connection = connection() (see module ct_telnet)
Close the telnet connection and stop the process managing it.
A connection may be associated with a target name and/or a handle.
If Connection
has no associated target name, it may only
be closed with the handle value (see the open/4
function).
cmd(Connection, Cmd) -> {ok, Data} | {error, Reason}
Equivalent to cmd(Connection, Cmd, DefaultTimeout).
cmd(Connection, Cmd, Timeout) -> {ok, Data} | {error, Reason}
Connection = connection() (see module ct_telnet)
Cmd = string()
Timeout = integer()
Data = [string()]
Send a command via telnet and wait for prompt.
cmdf(Connection, CmdFormat, Args) -> {ok, Data} | {error, Reason}
Equivalent to cmdf(Connection, CmdFormat, Args, DefaultTimeout).
cmdf(Connection, CmdFormat, Args, Timeout) -> {ok, Data} | {error, Reason}
Connection = connection() (see module ct_telnet)
CmdFormat = string()
Args = list()
Timeout = integer()
Data = [string()]
Send a telnet command and wait for prompt (uses a format string and list of arguments to build the command).
get_data(Connection) -> {ok, Data} | {error, Reason}
Connection = connection() (see module ct_telnet)
Data = [string()]
Get all data which has been received by the telnet client since last command was sent.
send(Connection, Cmd) -> ok | {error, Reason}
Connection = connection() (see module ct_telnet)
Cmd = string()
Send a telnet command and return immediately.
The resulting output from the command can be read with
get_data/1
or expect/2/3
.
sendf(Connection, CmdFormat, Args) -> ok | {error, Reason}
Connection = connection() (see module ct_telnet)
CmdFormat = string()
Args = list()
Send a telnet command and return immediately (uses a format string and a list of arguments to build the command).
expect(Connection, Patterns) -> term()
Equivalent to expect(Connections, Patterns, []).
expect(Connection, Patterns, Opts) -> {ok, Match} | {ok, MatchList, HaltReason} | {error, Reason}
Connection = connection() (see module ct_telnet)
Patterns = Pattern | [Pattern]
Pattern = string() | {Tag, string()} | prompt | {prompt, Prompt}
Prompt = string()
Tag = term()
Opts = [Opt]
Opt = {timeout, Timeout} | repeat | {repeat, N} | sequence | {halt, HaltPatterns} | ignore_prompt | no_prompt_check
Timeout = integer()
N = integer()
HaltPatterns = Patterns
MatchList = [Match]
Match = RxMatch | {Tag, RxMatch} | {prompt, Prompt}
RxMatch = [string()]
HaltReason = done | Match
Reason = timeout | {prompt, Prompt}
Get data from telnet and wait for the expected pattern.
Pattern
can be a POSIX regular expression. If more
than one pattern is given, the function returns when the first
match is found.
RxMatch
is a list of matched strings. It looks
like this: [FullMatch, SubMatch1, SubMatch2, ...]
where FullMatch
is the string matched by the whole
regular expression and SubMatchN
is the string that
matched subexpression no N
. Subexpressions are
denoted with '(' ')' in the regular expression
If a Tag
is given, the returned Match
will also include the matched Tag
. Else, only
RxMatch
is returned.
The timeout
option indicates that the function
shall return if the telnet client is idle (i.e. if no data is
received) for more than Timeout
milliseconds. Default
timeout is 10 seconds.
The function will always return when a prompt is found, unless
any of the ignore_prompt
or
no_prompt_check
options are used, in which case it
will return when a match is found or after a timeout.
If the ignore_prompt
option is used,
ct_telnet
will ignore any prompt found. This option
is useful if data sent by the server could include a pattern that
would match the prompt regexp (as returned by
TargedMod:get_prompt_regexp/0
), but which should not
cause the function to return.
If the no_prompt_check
option is used,
ct_telnet
will not search for a prompt at all. This
is useful if, for instance, the Pattern
itself
matches the prompt.
The repeat
option indicates that the pattern(s)
shall be matched multiple times. If N
is given, the
pattern(s) will be matched N
times, and the function
will return with HaltReason = done
.
The sequence
option indicates that all patterns
shall be matched in a sequence. A match will not be concluded
untill all patterns are matched.
Both repeat
and sequence
can be
interrupted by one or more HaltPatterns
. When
sequence
or repeat
is used, there will
always be a MatchList
returned, i.e. a list of
Match
instead of only one Match
. There
will also be a HaltReason
returned.
Examples:
expect(Connection,[{abc,"ABC"},{xyz,"XYZ"}],
[sequence,{halt,[{nnn,"NNN"}]}]).
will try to match
"ABC" first and then "XYZ", but if "NNN" appears the function will
return {error,{nnn,["NNN"]}}
. If both "ABC" and "XYZ"
are matched, the function will return
{ok,[AbcMatch,XyzMatch]}
.
expect(Connection,[{abc,"ABC"},{xyz,"XYZ"}],
[{repeat,2},{halt,[{nnn,"NNN"}]}]).
will try to match
"ABC" or "XYZ" twice. If "NNN" appears the function will return
with HaltReason = {nnn,["NNN"]}
.
The repeat
and sequence
options can be
combined in order to match a sequence multiple times.