diff --git a/lib/.gitignore b/lib/.gitignore index 56b1ed2b8404..4125111ebd8c 100644 --- a/lib/.gitignore +++ b/lib/.gitignore @@ -7,6 +7,7 @@ /common_test/doc/src/ct_rpc.xml /common_test/doc/src/ct_snmp.xml /common_test/doc/src/ct_ssh.xml +/common_test/doc/src/ct_netconfc.xml /common_test/doc/src/ct_telnet.xml /common_test/doc/src/unix_telnet.xml diff --git a/lib/common_test/doc/src/Makefile b/lib/common_test/doc/src/Makefile index 2ec6952710d0..99161ce68a5a 100644 --- a/lib/common_test/doc/src/Makefile +++ b/lib/common_test/doc/src/Makefile @@ -1,7 +1,7 @@ # # %CopyrightBegin% # -# Copyright Ericsson AB 2003-2011. All Rights Reserved. +# Copyright Ericsson AB 2003-2012. All Rights Reserved. # # The contents of this file are subject to the Erlang Public License, # Version 1.1, (the "License"); you may not use this file except in @@ -46,7 +46,8 @@ CT_MODULES = \ ct_rpc \ ct_snmp \ unix_telnet \ - ct_slave + ct_slave \ + ct_netconfc CT_XML_FILES = $(CT_MODULES:=.xml) @@ -123,7 +124,7 @@ $(HTMLDIR)/%.gif: %.gif docs: pdf html man -$(CT_XML_FILES): +$(CT_XML_FILES): %.xml: ../../src/%.erl escript $(DOCGEN)/priv/bin/xml_from_edoc.escript -preprocess true -i $(XMERL_DIR)/include \ -i ../../../test_server/include -i ../../include \ -i ../../../../erts/lib/kernel/include -i ../../../../lib/kernel/include \ diff --git a/lib/common_test/doc/src/ref_man.xml b/lib/common_test/doc/src/ref_man.xml index a9fdef7359a3..6fede88434c5 100644 --- a/lib/common_test/doc/src/ref_man.xml +++ b/lib/common_test/doc/src/ref_man.xml @@ -4,7 +4,7 @@
- 20032011 + 20032012 Ericsson AB. All Rights Reserved. @@ -71,6 +71,7 @@ + diff --git a/lib/common_test/src/Makefile b/lib/common_test/src/Makefile index 037a68696357..f7dce195d79d 100644 --- a/lib/common_test/src/Makefile +++ b/lib/common_test/src/Makefile @@ -70,14 +70,18 @@ MODULES= \ ct_hooks\ ct_hooks_lock\ cth_log_redirect\ - cth_surefire + cth_surefire \ + ct_netconfc \ + ct_conn_log_h \ + cth_conn_log TARGET_MODULES= $(MODULES:%=$(EBIN)/%) BEAM_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR)) ERL_FILES= $(MODULES:=.erl) HRL_FILES = \ - ct_util.hrl + ct_util.hrl \ + ct_netconfc.hrl EXTERNAL_HRL_FILES = \ ../include/ct.hrl \ ../include/ct_event.hrl diff --git a/lib/common_test/src/common_test.app.src b/lib/common_test/src/common_test.app.src index ae9a51faeb12..18c1dec7845f 100644 --- a/lib/common_test/src/common_test.app.src +++ b/lib/common_test/src/common_test.app.src @@ -33,6 +33,8 @@ ct_master_event, ct_master_logs, ct_master_status, + ct_netconfc, + ct_conn_log_h, ct_repeat, ct_rpc, ct_run, @@ -49,6 +51,7 @@ ct_config_xml, ct_slave, cth_log_redirect, + cth_conn_log, cth_surefire ]}, {registered, [ct_logs, diff --git a/lib/common_test/src/ct_conn_log_h.erl b/lib/common_test/src/ct_conn_log_h.erl new file mode 100644 index 000000000000..f3b678197163 --- /dev/null +++ b/lib/common_test/src/ct_conn_log_h.erl @@ -0,0 +1,230 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2012. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +-module(ct_conn_log_h). + +%%% +%%% A handler that can be connected to the error_logger event +%%% handler. Writes all ct connection events. See comments in +%%% cth_conn_log for more information. +%%% + +-include("ct_util.hrl"). + +-export([init/1, + handle_event/2, handle_call/2, handle_info/2, + terminate/2]). + +-record(state, {group_leader,logs=[]}). + +-define(WIDTH,80). + +%%%----------------------------------------------------------------- +%%% Callbacks +init({GL,Logs}) -> + open_files(Logs,#state{group_leader=GL}). + +open_files([{ConnMod,{LogType,Logs}}|T],State) -> + case do_open_files(Logs,[]) of + {ok,Fds} -> + open_files(T,State#state{logs=[{ConnMod,{LogType,Fds}} | + State#state.logs]}); + Error -> + Error + end; +open_files([],State) -> + {ok,State}. + + +do_open_files([{Tag,File}|Logs],Acc) -> + case file:open(File, [write]) of + {ok,Fd} -> + do_open_files(Logs,[{Tag,Fd}|Acc]); + {error,Reason} -> + {error,{could_not_open_log,File,Reason}} + end; +do_open_files([],Acc) -> + {ok,lists:reverse(Acc)}. + +handle_event({_Type, GL, _Msg}, State) when node(GL) /= node() -> + {ok, State}; +handle_event({_Type,_GL,{Pid,{ct_connection,Action,ConnName},Report}},State) -> + Info = conn_info(Pid,#conn_log{name=ConnName,action=Action}), + write_report(now(),Info,Report,State), + {ok, State}; +handle_event({_Type,_GL,{Pid,Info=#conn_log{},Report}},State) -> + write_report(now(),conn_info(Pid,Info),Report,State), + {ok, State}; +handle_event({error_report,_,{Pid,_,[{ct_connection,ConnName}|R]}},State) -> + %% Error reports from connection + write_error(now(),conn_info(Pid,#conn_log{name=ConnName}),R,State), + {ok, State}; +handle_event(_, State) -> + {ok, State}. + +handle_info(_, State) -> + {ok, State}. + +handle_call(_Query, State) -> + {ok, {error, bad_query}, State}. + +terminate(_,#state{logs=Logs}) -> + [file:close(Fd) || {_,_,Fds} <- Logs, Fd <- Fds], + ok. + + +%%%----------------------------------------------------------------- +%%% Writing reports +write_report(Time,#conn_log{module=ConnMod}=Info,Data,State) -> + {LogType,Fd} = get_log(Info,State), + io:format(Fd,"~n~s~s~s",[format_head(ConnMod,LogType,Time), + format_title(LogType,Info), + format_data(ConnMod,LogType,Data)]). + +write_error(Time,#conn_log{module=ConnMod}=Info,Report,State) -> + case get_log(Info,State) of + {html,_} -> + %% The error will anyway be written in the html log by the + %% sasl error handler, so don't write it again. + ok; + {LogType,Fd} -> + io:format(Fd,"~n~s~s~s",[format_head(ConnMod,LogType,Time," ERROR"), + format_title(LogType,Info), + format_error(LogType,Report)]) + end. + +get_log(Info,State) -> + case proplists:get_value(Info#conn_log.module,State#state.logs) of + {html,_} -> + {html,State#state.group_leader}; + {LogType,Fds} -> + {LogType,get_fd(Info,Fds)}; + undefined -> + {html,State#state.group_leader} + end. + +get_fd(#conn_log{name=undefined},Fds) -> + proplists:get_value(default,Fds); +get_fd(#conn_log{name=ConnName},Fds) -> + case proplists:get_value(ConnName,Fds) of + undefined -> + proplists:get_value(default,Fds); + Fd -> + Fd + end. + +%%%----------------------------------------------------------------- +%%% Formatting +format_head(ConnMod,LogType,Time) -> + format_head(ConnMod,LogType,Time,""). + +format_head(ConnMod,raw,Time,Text) -> + io_lib:format("~n~p, ~p~s, ",[now_to_time(Time),ConnMod,Text]); +format_head(ConnMod,_,Time,Text) -> + Head = pad_char_end(?WIDTH,pretty_head(now_to_time(Time),ConnMod,Text),$=), + io_lib:format("~n~s",[Head]). + +format_title(raw,#conn_log{client=Client}=Info) -> + io_lib:format("Client ~p ~s ~s",[Client,actionstr(Info),serverstr(Info)]); +format_title(_,Info) -> + Title = pad_char_end(?WIDTH,pretty_title(Info),$=), + io_lib:format("~n~s", [Title]). + +format_data(_,_,NoData) when NoData == ""; NoData == <<>> -> + ""; +format_data(ConnMod,LogType,Data) -> + ConnMod:format_data(LogType,Data). + +format_error(raw,Report) -> + io_lib:format("~n~p~n",[Report]); +format_error(pretty,Report) -> + [io_lib:format("~n ~p: ~p",[K,V]) || {K,V} <- Report]. + + + + +%%%----------------------------------------------------------------- +%%% Helpers +conn_info(LoggingProc, #conn_log{client=undefined} = ConnInfo) -> + conn_info(ConnInfo#conn_log{client=LoggingProc}); +conn_info(_, ConnInfo) -> + conn_info(ConnInfo). + +conn_info(#conn_log{client=Client, module=undefined} = ConnInfo) -> + case ets:lookup(ct_connections,Client) of + [#conn{address=Address,callback=Callback}] -> + ConnInfo#conn_log{address=Address,module=Callback}; + [] -> + ConnInfo + end; +conn_info(ConnInfo) -> + ConnInfo. + + +now_to_time({_,_,MicroS}=Now) -> + {calendar:now_to_local_time(Now),MicroS}. + +pretty_head({{{Y,Mo,D},{H,Mi,S}},MicroS},ConnMod,Text0) -> + Text = string:to_upper(atom_to_list(ConnMod) ++ Text0), + io_lib:format("= ~s ==== ~s-~s-~p::~s:~s:~s,~s ", + [Text,t(D),month(Mo),Y,t(H),t(Mi),t(S), + micro2milli(MicroS)]). + +pretty_title(#conn_log{client=Client}=Info) -> + io_lib:format("= Client ~p ~s Server ~s ", + [Client,actionstr(Info),serverstr(Info)]). + +actionstr(#conn_log{action=send}) -> "----->"; +actionstr(#conn_log{action=recv}) -> "<-----"; +actionstr(#conn_log{action=open}) -> "opened session to"; +actionstr(#conn_log{action=close}) -> "closed session to"; +actionstr(_) -> "<---->". + +serverstr(#conn_log{name=undefined,address=Address}) -> + io_lib:format("~p",[Address]); +serverstr(#conn_log{name=Alias,address=Address}) -> + io_lib:format("~p(~p)",[Alias,Address]). + +month(1) -> "Jan"; +month(2) -> "Feb"; +month(3) -> "Mar"; +month(4) -> "Apr"; +month(5) -> "May"; +month(6) -> "Jun"; +month(7) -> "Jul"; +month(8) -> "Aug"; +month(9) -> "Sep"; +month(10) -> "Oct"; +month(11) -> "Nov"; +month(12) -> "Dec". + +micro2milli(X) -> + pad0(3,integer_to_list(X div 1000)). + +t(X) -> + pad0(2,integer_to_list(X)). + +pad0(N,Str) -> + M = length(Str), + lists:duplicate(N-M,$0) ++ Str. + +pad_char_end(N,Str,Char) -> + case length(lists:flatten(Str)) of + M when M Str ++ lists:duplicate(N-M,Char); + _ -> Str + end. diff --git a/lib/common_test/src/ct_gen_conn.erl b/lib/common_test/src/ct_gen_conn.erl index 5aab4dd2ddcf..6b183110c65e 100644 --- a/lib/common_test/src/ct_gen_conn.erl +++ b/lib/common_test/src/ct_gen_conn.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2003-2010. All Rights Reserved. +%% Copyright Ericsson AB 2003-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -27,7 +27,7 @@ -compile(export_all). -export([start/4, stop/1]). --export([call/2, do_within_time/2]). +-export([call/2, call/3, return/2, do_within_time/2]). -ifdef(debug). -define(dbg,true). @@ -39,17 +39,24 @@ name, address, init_data, + reconnect = true, + forward = false, + use_existing = true, + old = false, conn_pid, cb_state, ct_util_server}). %%%----------------------------------------------------------------- -%%% @spec start(Name,Address,InitData,CallbackMod) -> +%%% @spec start(Address,InitData,CallbackMod,Opts) -> %%% {ok,Handle} | {error,Reason} %%% Name = term() %%% CallbackMod = atom() %%% InitData = term() %%% Address = term() +%%% Opts = [Opt] +%%% Opt = {name,Name} | {use_existing_connection,boolean()} | +%%% {reconnect,boolean()} | {forward_messages,boolean()} %%% %%% @doc Open a connection and start the generic connection owner process. %%% @@ -60,42 +67,59 @@ %%% InitData and returna %%% {ok,ConnectionPid,State} or %%% {error,Reason}.

+%%% +%%% If no name is given, the Name argument in init/3 will +%%% have the value undefined. +%%% +%%% The callback modules must also export +%%% ``` +%%% handle_msg(Msg,From,State) -> {reply,Reply,State} | +%%% {noreply,State} | +%%% {stop,Reply,State} +%%% terminate(ConnectionPid,State) -> term() +%%% close(Handle) -> term() +%%% ''' +%%% +%%% The close/1 callback function is actually a callback +%%% for ct_util, for closing registered connections when +%%% ct_util_server is terminated. Handle is the Pid of +%%% the ct_gen_conn process. +%%% +%%% If option reconnect is true, then the +%%% callback must also export +%%% ``` +%%% reconnect(Address,State) -> {ok,ConnectionPid,State} +%%% ''' +%%% +%%% If option forward_messages is true, then +%%% the callback must also export +%%% ``` +%%% handle_msg(Msg,State) -> {noreply,State} | {stop,State} +%%% ''' +%%% +%%% An old interface still exists. This is used by ct_telnet, ct_ftp +%%% and ct_ssh. The start function then has an explicit +%%% Name argument, and no Opts argument. The +%%% callback must export: +%%% +%%% ``` +%%% init(Name,Address,InitData) -> {ok,ConnectionPid,State} +%%% handle_msg(Msg,State) -> {Reply,State} +%%% reconnect(Address,State) -> {ok,ConnectionPid,State} +%%% terminate(ConnectionPid,State) -> term() +%%% close(Handle) -> term() +%%% ''' +%%% +start(Address,InitData,CallbackMod,Opts) when is_list(Opts) -> + do_start(Address,InitData,CallbackMod,Opts); start(Name,Address,InitData,CallbackMod) -> - case ct_util:does_connection_exist(Name,Address,CallbackMod) of - {ok,Pid} -> - log("ct_gen_conn:start","Using existing connection!\n",[]), - {ok,Pid}; - false -> - Self = self(), - Pid = spawn(fun() -> - init_gen(Self, #gen_opts{callback=CallbackMod, - name=Name, - address=Address, - init_data=InitData}) - end), - MRef = erlang:monitor(process,Pid), - receive - {connected,Pid} -> - erlang:demonitor(MRef, [flush]), - ct_util:register_connection(Name,Address,CallbackMod,Pid), - {ok,Pid}; - {Error,Pid} -> - receive {'DOWN',MRef,process,_,_} -> ok end, - Error; - {'DOWN',MRef,process,_,Reason} -> - log("ct_gen_conn:start", - "Connection process died: ~p\n", - [Reason]), - {error,{connection_process_died,Reason}} - end - end. - + do_start(Address,InitData,CallbackMod,[{name,Name},{old,true}]). %%%----------------------------------------------------------------- %%% @spec stop(Handle) -> ok %%% Handle = handle() %%% -%%% @doc Close the telnet connection and stop the process managing it. +%%% @doc Close the connection and stop the process managing it. stop(Pid) -> call(Pid,stop). @@ -103,7 +127,7 @@ stop(Pid) -> %%% @spec log(Heading,Format,Args) -> ok %%% %%% @doc Log activities on the current connection (tool-internal use only). -%%% @see ct_logs:log/3 +%%% @see ct_logs:log/3 log(Heading,Format,Args) -> log(log,[Heading,Format,Args]). @@ -111,7 +135,7 @@ log(Heading,Format,Args) -> %%% @spec start_log(Heading) -> ok %%% %%% @doc Log activities on the current connection (tool-internal use only). -%%% @see ct_logs:start_log/1 +%%% @see ct_logs:start_log/1 start_log(Heading) -> log(start_log,[Heading]). @@ -119,7 +143,7 @@ start_log(Heading) -> %%% @spec cont_log(Format,Args) -> ok %%% %%% @doc Log activities on the current connection (tool-internal use only). -%%% @see ct_logs:cont_log/2 +%%% @see ct_logs:cont_log/2 cont_log(Format,Args) -> log(cont_log,[Format,Args]). @@ -127,7 +151,7 @@ cont_log(Format,Args) -> %%% @spec end_log() -> ok %%% %%% @doc Log activities on the current connection (tool-internal use only). -%%% @see ct_logs:end_log/0 +%%% @see ct_logs:end_log/0 end_log() -> log(end_log,[]). @@ -148,10 +172,10 @@ do_within_time(Fun,Timeout) -> Silent = get(silent), TmpPid = spawn_link(fun() -> put(silent,Silent), R = Fun(), - Self ! {self(),R} + Self ! {self(),R} end), ConnPid = get(conn_pid), - receive + receive {TmpPid,Result} -> Result; {'EXIT',ConnPid,_Reason}=M -> @@ -159,7 +183,7 @@ do_within_time(Fun,Timeout) -> exit(TmpPid,kill), self() ! M, {error,connection_closed} - after + after Timeout -> exit(TmpPid,kill), receive @@ -176,12 +200,68 @@ do_within_time(Fun,Timeout) -> %%%================================================================= %%% Internal functions +do_start(Address,InitData,CallbackMod,Opts0) -> + Opts = check_opts(Opts0,#gen_opts{callback=CallbackMod, + address=Address, + init_data=InitData}), + case Opts#gen_opts.use_existing of + true -> + case ct_util:does_connection_exist(Opts#gen_opts.name, + Address,CallbackMod) of + {ok,Pid} -> + log("ct_gen_conn:start","Using existing connection!\n",[]), + {ok,Pid}; + false -> + do_start(Opts) + end; + false -> + do_start(Opts) + end. + +do_start(Opts) -> + Self = self(), + Pid = spawn(fun() -> init_gen(Self, Opts) end), + MRef = erlang:monitor(process,Pid), + receive + {connected,Pid} -> + erlang:demonitor(MRef, [flush]), + ct_util:register_connection(Opts#gen_opts.name, Opts#gen_opts.address, + Opts#gen_opts.callback, Pid), + {ok,Pid}; + {Error,Pid} -> + receive {'DOWN',MRef,process,_,_} -> ok end, + Error; + {'DOWN',MRef,process,_,Reason} -> + log("ct_gen_conn:start", + "Connection process died: ~p\n", + [Reason]), + {error,{connection_process_died,Reason}} + end. + +check_opts(Opts0) -> + check_opts(Opts0,#gen_opts{}). + +check_opts([{name,Name}|T],Opts) -> + check_opts(T,Opts#gen_opts{name=Name}); +check_opts([{reconnect,Bool}|T],Opts) -> + check_opts(T,Opts#gen_opts{reconnect=Bool}); +check_opts([{forward_messages,Bool}|T],Opts) -> + check_opts(T,Opts#gen_opts{forward=Bool}); +check_opts([{use_existing_connection,Bool}|T],Opts) -> + check_opts(T,Opts#gen_opts{use_existing=Bool}); +check_opts([{old,Bool}|T],Opts) -> + check_opts(T,Opts#gen_opts{old=Bool}); +check_opts([],Opts) -> + Opts. + call(Pid,Msg) -> + call(Pid,Msg,infinity). +call(Pid,Msg,Timeout) -> MRef = erlang:monitor(process,Pid), Ref = make_ref(), Pid ! {Msg,{self(),Ref}}, receive - {Ref, Result} -> + {Ref, Result} -> erlang:demonitor(MRef, [flush]), case Result of {retry,_Data} -> @@ -189,8 +269,11 @@ call(Pid,Msg) -> Other -> Other end; - {'DOWN',MRef,process,_,Reason} -> + {'DOWN',MRef,process,_,Reason} -> {error,{process_down,Pid,Reason}} + after Timeout -> + erlang:demonitor(MRef, [flush]), + exit(timeout) end. return({To,Ref},Result) -> @@ -201,9 +284,9 @@ init_gen(Parent,Opts) -> CtUtilServer = whereis(ct_util_server), link(CtUtilServer), put(silent,false), - case catch (Opts#gen_opts.callback):init(Opts#gen_opts.name, - Opts#gen_opts.address, - Opts#gen_opts.init_data) of + try (Opts#gen_opts.callback):init(Opts#gen_opts.name, + Opts#gen_opts.address, + Opts#gen_opts.init_data) of {ok,ConnPid,State} when is_pid(ConnPid) -> link(ConnPid), put(conn_pid,ConnPid), @@ -213,21 +296,32 @@ init_gen(Parent,Opts) -> ct_util_server=CtUtilServer}); {error,Reason} -> Parent ! {{error,Reason},self()} + catch + throw:{error,Reason} -> + Parent ! {{error,Reason},self()} end. loop(Opts) -> receive {'EXIT',Pid,Reason} when Pid==Opts#gen_opts.conn_pid -> - log("Connection down!\nOpening new!","Reason: ~p\nAddress: ~p\n", - [Reason,Opts#gen_opts.address]), - case reconnect(Opts) of - {ok, NewPid, NewState} -> - link(NewPid), - put(conn_pid,NewPid), - loop(Opts#gen_opts{conn_pid=NewPid,cb_state=NewState}); - Error -> + case Opts#gen_opts.reconnect of + true -> + log("Connection down!\nOpening new!", + "Reason: ~p\nAddress: ~p\n", + [Reason,Opts#gen_opts.address]), + case reconnect(Opts) of + {ok, NewPid, NewState} -> + link(NewPid), + put(conn_pid,NewPid), + loop(Opts#gen_opts{conn_pid=NewPid,cb_state=NewState}); + Error -> + ct_util:unregister_connection(self()), + log("Reconnect failed. Giving up!","Reason: ~p\n", + [Error]) + end; + false -> ct_util:unregister_connection(self()), - log("Reconnect failed. Giving up!","Reason: ~p\n",[Error]) + log("Connection closed!","Reason: ~p\n",[Reason]) end; {'EXIT',Pid,Reason} -> case Opts#gen_opts.ct_util_server of @@ -252,24 +346,40 @@ loop(Opts) -> loop(Opts); {{retry,{_Error,_Name,_CPid,Msg}}, From} -> log("Rerunning command","Connection reestablished. Rerunning command...",[]), - {Return,NewState} = + {Return,NewState} = (Opts#gen_opts.callback):handle_msg(Msg,Opts#gen_opts.cb_state), return(From, Return), - loop(Opts#gen_opts{cb_state=NewState}); - {Msg,From={Pid,_Ref}} when is_pid(Pid) -> - {Return,NewState} = + loop(Opts#gen_opts{cb_state=NewState}); + {Msg,From={Pid,_Ref}} when is_pid(Pid), Opts#gen_opts.old==true -> + {Return,NewState} = (Opts#gen_opts.callback):handle_msg(Msg,Opts#gen_opts.cb_state), return(From, Return), - loop(Opts#gen_opts{cb_state=NewState}) + loop(Opts#gen_opts{cb_state=NewState}); + {Msg,From={Pid,_Ref}} when is_pid(Pid) -> + case (Opts#gen_opts.callback):handle_msg(Msg,From, + Opts#gen_opts.cb_state) of + {reply,Reply,NewState} -> + return(From,Reply), + loop(Opts#gen_opts{cb_state=NewState}); + {noreply,NewState} -> + loop(Opts#gen_opts{cb_state=NewState}); + {stop,Reply,NewState} -> + ct_util:unregister_connection(self()), + (Opts#gen_opts.callback):terminate(Opts#gen_opts.conn_pid, + NewState), + return(From,Reply) + end; + Msg when Opts#gen_opts.forward==true -> + case (Opts#gen_opts.callback):handle_msg(Msg,Opts#gen_opts.cb_state) of + {noreply,NewState} -> + loop(Opts#gen_opts{cb_state=NewState}); + {stop,NewState} -> + ct_util:unregister_connection(self()), + (Opts#gen_opts.callback):terminate(Opts#gen_opts.conn_pid, + NewState) + end end. -nozero({ok,S}) when is_list(S) -> - {ok,[C || C <- S, - C=/=0, - C=/=13]}; -nozero(M) -> - M. - reconnect(Opts) -> (Opts#gen_opts.callback):reconnect(Opts#gen_opts.address, Opts#gen_opts.cb_state). @@ -277,10 +387,8 @@ reconnect(Opts) -> log(Func,Args) -> case get(silent) of - true when not ?dbg-> + true when not ?dbg-> ok; _ -> apply(ct_logs,Func,Args) end. - - diff --git a/lib/common_test/src/ct_netconfc.erl b/lib/common_test/src/ct_netconfc.erl new file mode 100644 index 000000000000..d9c4a962dc4d --- /dev/null +++ b/lib/common_test/src/ct_netconfc.erl @@ -0,0 +1,1828 @@ +%%---------------------------------------------------------------------- +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2012. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +%%---------------------------------------------------------------------- +%% File: ct_netconfc.erl +%% +%% Description: +%% This file contains the Netconf client interface +%% +%% @author Support +%% +%% @doc Netconf client module. +%% +%%

The Netconf client is compliant with RFC4741 and RFC4742.

+%% +%%

For each server to test against, the following entry can be +%% added to a configuration file:

+%% +%%

`{server_id(),options()}.'

+%% +%%

The `server_id()' or an associated `target_name()' (see +%% {@link ct}) shall then be used in calls to {@link open/2}.

+%% +%%

If no configuration exists for a server, a session can still be +%% opened by calling {@link open/2} with all necessary options given +%% in the call. The first argument to {@link open/2} can then be any +%% atom.

+%% +%% == Logging == +%% +%% The netconf server uses the `error_logger' for logging of netconf +%% traffic. A special purpose error handler is implemented in +%% `ct_conn_log_h'. To use this error handler, add the `cth_conn_log' +%% hook in your test suite, e.g. +%% +%% ``` +%% suite() -> +%% [{ct_hooks, [{cth_conn_log, [{conn_mod(),hook_options()}]}]}]. +%%''' +%% +%% The `conn_mod()' is the name of the common_test module implementing +%% the connection protocol, e.g. `ct_netconfc'. +%% +%% The hook option `log_type' specifies the type of logging: +%% +%%
+%%
`raw'
+%%
The sent and received netconf data is logged to a separate +%% text file as is without any formatting. A link to the file is +%% added to the test case HTML log.
+%% +%%
`pretty'
+%%
The sent and received netconf data is logged to a separate +%% text file with XML data nicely indented. A link to the file is +%% added to the test case HTML log.
+%% +%%
`html (default)'
+%%
The sent and received netconf traffic is pretty printed +%% directly in the test case HTML log.
+%% +%%
`silent'
+%%
Netconf traffic is not logged.
+%%
+%% +%% By default, all netconf traffic is logged in one single log +%% file. However, it is possible to have different connections logged +%% in separate files. To do this, use the hook option `hosts' and +%% list the names of the servers/connections that will be used in the +%% suite. Note that the connections must be named for this to work, +%% i.e. they must be opened with {@link open/2}. +%% +%% The `hosts' option has no effect if `log_type' is set to `html' or +%% `silent'. +%% +%% The hook options can also be specified in a configuration file with +%% the configuration variable `ct_conn_log': +%% +%% ``` +%% {ct_conn_log,[{conn_mod(),hook_options()}]}. +%% ''' +%% +%% For example: +%% +%% ``` +%% {ct_conn_log,[{ct_netconfc,[{log_type,pretty}, +%% {hosts,[key_or_name()]}]}]} +%% ''' +%% +%% Note that hook options specified in a configuration file +%% will overwrite the hardcoded hook options in the test suite. +%% +%% === Logging example 1 === +%% +%% The following `ct_hooks' statement will cause pretty printing of +%% netconf traffic to separate logs for the connections named +%% `nc_server1' and `nc_server2'. Any other connections will be logged +%% to default netconf log. +%% +%% ``` +%% suite() -> +%% [{ct_hooks, [{cth_conn_log, [{ct_netconfc,[{log_type,pretty}}, +%% {hosts,[nc_server1,nc_server2]}]} +%% ]}]}]. +%%''' +%% +%% Connections must be opened like this: +%% +%% ``` +%% open(nc_server1,[...]), +%% open(nc_server2,[...]). +%% ''' +%% +%% === Logging example 2 === +%% +%% The following configuration file will cause raw logging of all +%% netconf traffic into one single text file. +%% +%% ``` +%% {ct_conn_log,[{ct_netconfc,[{log_type,raw}]}]}. +%% ''' +%% +%% The `ct_hooks' statement must look like this: +%% +%% ``` +%% suite() -> +%% [{ct_hooks, [{cth_conn_log, []}]}]. +%% ''' +%% +%% The same `ct_hooks' statement without the configuration file would +%% cause HTML logging of all netconf connections into the test case +%% HTML log. +%% +%% == Notifications == +%% +%% The netconf client is also compliant with RFC5277 NETCONF Event +%% Notifications, which defines a mechanism for an asynchronous +%% message notification delivery service for the netconf protocol. +%% +%% Specific functions to support this are {@link +%% create_subscription/6} and {@link get_event_streams/3}. (The +%% functions also exist with other arities.) +%% +%% @end +%%---------------------------------------------------------------------- +-module(ct_netconfc). + +-include("ct_netconfc.hrl"). +-include("ct_util.hrl"). +-include_lib("xmerl/include/xmerl.hrl"). + +%%---------------------------------------------------------------------- +%% External exports +%%---------------------------------------------------------------------- +-export([open/1, + open/2, + only_open/1, + only_open/2, + hello/1, + hello/2, + close_session/1, + close_session/2, + kill_session/2, + kill_session/3, + send/2, + send/3, + send_rpc/2, + send_rpc/3, + lock/2, + lock/3, + unlock/2, + unlock/3, + get/2, + get/3, + get_config/3, + get_config/4, + edit_config/3, + edit_config/4, + delete_config/2, + delete_config/3, + copy_config/3, + copy_config/4, + action/2, + action/3, + create_subscription/1, + create_subscription/2, + create_subscription/3, + create_subscription/4, + create_subscription/5, + create_subscription/6, + get_event_streams/2, + get_event_streams/3, + get_capabilities/1, + get_capabilities/2, + get_session_id/1, + get_session_id/2]). + +%%---------------------------------------------------------------------- +%% Exported types +%%---------------------------------------------------------------------- +-export_type([hook_options/0, + conn_mod/0, + log_type/0, + key_or_name/0, + notification/0]). + +%%---------------------------------------------------------------------- +%% Internal exports +%%---------------------------------------------------------------------- +%% ct_gen_conn callbacks +-export([init/3, + handle_msg/3, + handle_msg/2, + terminate/2, + close/1]). + +%% ct_conn_log callback +-export([format_data/2]). + +%%---------------------------------------------------------------------- +%% Internal defines +%%---------------------------------------------------------------------- +-define(APPLICATION,?MODULE). +-define(VALID_SSH_OPTS,[user, password, user_dir]). +-define(DEFAULT_STREAM,"NETCONF"). + +-define(error(ConnName,Report), + error_logger:error_report([{ct_connection,ConnName}, + {client,self()}, + {module,?MODULE}, + {line,?LINE} | + Report])). + +-define(is_timeout(T), (is_integer(T) orelse T==infinity)). +-define(is_filter(F), + (is_atom(F) orelse (is_tuple(F) andalso is_atom(element(1,F))))). +-define(is_string(S), (is_list(S) andalso is_integer(hd(S)))). + +%%---------------------------------------------------------------------- +%% Records +%%---------------------------------------------------------------------- +%% Client state +-record(state, {host, + port, + connection, % #connection + capabilities, + session_id, + msg_id = 1, + hello_status, + buff = <<>>, + pending = [], % [#pending] + event_receiver}).% pid + +%% Run-time client options. +-record(options, {ssh = [], % Options for the ssh application + host, + port = ?DEFAULT_PORT, + timeout = ?DEFAULT_TIMEOUT, + name}). + +%% Connection reference +-record(connection, {reference, % {CM,Ch} + host, + port, + name}). + +%% Pending replies from server +-record(pending, {tref, % timer ref (returned from timer:xxx) + ref, % pending ref + msg_id, + op, + caller}).% pid which sent the request + +%%---------------------------------------------------------------------- +%% Type declarations +%%---------------------------------------------------------------------- +-type client() :: handle() | server_id() | target_name(). +-type handle() :: term(). +%% An opaque reference for a connection (netconf session). See {@link +%% ct} for more information. + +-type server_id() :: atom(). +%% A `ServerId' which exists in a configuration file. +-type target_name() :: atom(). +%% A name which is associated to a `server_id()' via a +%% `require' statement or a call to {@link ct:require/2} in the +%% test suite. +-type key_or_name() :: server_id() | target_name(). + +-type options() :: [option()]. +%% Options used for setting up ssh connection to a netconf server. + +-type option() :: {ssh,host()} | {port,inet:port_number()} | {user,string()} | + {password,string()} | {user_dir,string()} | + {timeout,timeout()}. +-type host() :: inet:host_name() | inet:ip_address(). + +-type notification() :: {notification, xml_attributes(), notification_content()}. +-type notification_content() :: [event_time()|simple_xml()]. +-type event_time() :: {eventTime,xml_attributes(),[xs_datetime()]}. + +-type stream_name() :: string(). +-type streams() :: [{stream_name(),[stream_data()]}]. +-type stream_data() :: {description,string()} | + {replaySupport,string()} | + {replayLogCreationTime,string()} | + {replayLogAgedTime,string()}. +%% See XML Schema for Event Notifications found in RFC5277 for further +%% detail about the data format for the string values. + +-type hook_options() :: [hook_option()]. +%% Options that can be given to `cth_conn_log' in the `ct_hook' statement. +-type hook_option() :: {log_type,log_type()} | + {hosts,[key_or_name()]}. +-type log_type() :: raw | pretty | html | silent. +%-type error_handler() :: module(). +-type conn_mod() :: ct_netconfc. + +-type error_reason() :: term(). + +-type simple_xml() :: {xml_tag(), xml_attributes(), xml_content()} | + {xml_tag(), xml_content()} | + xml_tag(). +%%

This type is further described in the documentation for the +%% Xmerl application.

+-type xml_tag() :: atom(). +-type xml_attributes() :: [{xml_attribute_tag(),xml_attribute_value()}]. +-type xml_attribute_tag() :: atom(). +-type xml_attribute_value() :: string(). +-type xml_content() :: [simple_xml() | iolist()]. +-type xpath() :: {xpath,string()}. + +-type netconf_db() :: running | startup | candidate. +-type xs_datetime() :: string(). +%% This date and time identifyer has the same format as the XML type +%% dateTime and compliant to RFC3339. The format is +%% ```[-]CCYY-MM-DDThh:mm:ss[.s][Z|(+|-)hh:mm]''' + +%%---------------------------------------------------------------------- +%% External interface functions +%%---------------------------------------------------------------------- + +%%---------------------------------------------------------------------- +-spec open(Options) -> Result when + Options :: options(), + Result :: {ok,handle()} | {error,error_reason()}. +%% @doc Open a netconf session and exchange `hello' messages. +%% +%% If the server options are specified in a configuration file, or if +%% a named client is needed for logging purposes (see {@section +%% Logging}) use {@link open/2} instead. +%% +%% The opaque `handler()' reference which is returned from this +%% function is required as client identifier when calling any other +%% function in this module. +%% +%% The `timeout' option (milli seconds) is used when setting up +%% the ssh connection and when waiting for the hello message from the +%% server. It is not used for any other purposes during the lifetime +%% of the connection. +%% +%% @end +%%---------------------------------------------------------------------- +open(Options) -> + open(Options,#options{},[],true). + +%%---------------------------------------------------------------------- +-spec open(KeyOrName, ExtraOptions) -> Result when + KeyOrName :: key_or_name(), + ExtraOptions :: options(), + Result :: {ok,handle()} | {error,error_reason()}. +%% @doc Open a named netconf session and exchange `hello' messages. +%% +%% If `KeyOrName' is a configured `server_id()' or a +%% `target_name()' associated with such an ID, then the options +%% for this server will be fetched from the configuration file. +% +%% The `ExtraOptions' argument will be added to the options found in +%% the configuration file. If the same options are given, the values +%% from the configuration file will overwrite `ExtraOptions'. +%% +%% If the server is not specified in a configuration file, use {@link +%% open/1} instead. +%% +%% The opaque `handle()' reference which is returned from this +%% function can be used as client identifier when calling any other +%% function in this module. However, if `KeyOrName' is a +%% `target_name()', i.e. if the server is named via a call to +%% `ct:require/2' or a `require' statement in the test +%% suite, then this name may be used instead of the `handle()'. +%% +%% The `timeout' option (milli seconds) is used when setting up +%% the ssh connection and when waiting for the hello message from the +%% server. It is not used for any other purposes during the lifetime +%% of the connection. +%% +%% @end +%%---------------------------------------------------------------------- +open(KeyOrName, ExtraOpts) -> + open(KeyOrName, ExtraOpts, true). + +open(KeyOrName, ExtraOpts, Hello) -> + SortedExtra = lists:keysort(1,ExtraOpts), + SortedConfig = lists:keysort(1,ct:get_config(KeyOrName,[])), + AllOpts = lists:ukeymerge(1,SortedConfig,SortedExtra), + open(AllOpts,#options{name=KeyOrName},[{name,KeyOrName}],Hello). + +open(OptList,InitOptRec,NameOpt,Hello) -> + case check_options(OptList,undefined,undefined,InitOptRec) of + {Host,Port,Options} -> + case ct_gen_conn:start({Host,Port},Options,?MODULE, + NameOpt ++ [{reconnect,false}, + {use_existing_connection,false}, + {forward_messages,true}]) of + {ok,Client} when Hello==true -> + case hello(Client,Options#options.timeout) of + ok -> + {ok,Client}; + Error -> + Error + end; + Other -> + Other + end; + Error -> + Error + end. + + +%%---------------------------------------------------------------------- +-spec only_open(Options) -> Result when + Options :: options(), + Result :: {ok,handle()} | {error,error_reason()}. +%% @doc Open a netconf session, but don't send `hello'. +%% +%% As {@link open/1} but does not send a `hello' message. +%% +%% @end +%%---------------------------------------------------------------------- +only_open(Options) -> + open(Options,#options{},[],false). + +%%---------------------------------------------------------------------- +-spec only_open(KeyOrName,ExtraOptions) -> Result when + KeyOrName :: key_or_name(), + ExtraOptions :: options(), + Result :: {ok,handle()} | {error,error_reason()}. +%% @doc Open a name netconf session, but don't send `hello'. +%% +%% As {@link open/2} but does not send a `hello' message. +%% +%% @end +%%---------------------------------------------------------------------- +only_open(KeyOrName, ExtraOpts) -> + open(KeyOrName, ExtraOpts, false). + +%%---------------------------------------------------------------------- +%% @spec hello(Client) -> Result +%% @equiv hello(Client, infinity) +hello(Client) -> + hello(Client,?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec hello(Client,Timeout) -> Result when + Client :: handle(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Exchange `hello' messages with the server. +%% +%% Sends a `hello' message to the server and waits for the return. +%% +%% @end +%%---------------------------------------------------------------------- +hello(Client,Timeout) -> + call(Client, {hello, Timeout}). + +%%---------------------------------------------------------------------- +%% @spec get_session_id(Client) -> Result +%% @equiv get_session_id(Client, infinity) +get_session_id(Client) -> + get_session_id(Client, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec get_session_id(Client, Timeout) -> Result when + Client :: client(), + Timeout :: timeout(), + Result :: pos_integer() | {error,error_reason()}. +%% @doc Returns the session id associated with the given client. +%% +%% @end +%%---------------------------------------------------------------------- +get_session_id(Client, Timeout) -> + call(Client, get_session_id, Timeout). + +%%---------------------------------------------------------------------- +%% @spec get_capabilities(Client) -> Result +%% @equiv get_capabilities(Client, infinity) +get_capabilities(Client) -> + get_capabilities(Client, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec get_capabilities(Client, Timeout) -> Result when + Client :: client(), + Timeout :: timeout(), + Result :: [string()] | {error,error_reason()}. +%% @doc Returns the server side capabilities +%% +%% The following capability identifiers, defined in RFC 4741, can be returned: +%% +%%
    +%%
  • `"urn:ietf:params:netconf:base:1.0"'
  • +%%
  • `"urn:ietf:params:netconf:capability:writable-running:1.0"'
  • +%%
  • `"urn:ietf:params:netconf:capability:candidate:1.0"'
  • +%%
  • `"urn:ietf:params:netconf:capability:confirmed-commit:1.0"'
  • +%%
  • `"urn:ietf:params:netconf:capability:rollback-on-error:1.0"'
  • +%%
  • `"urn:ietf:params:netconf:capability:startup:1.0"'
  • +%%
  • `"urn:ietf:params:netconf:capability:url:1.0"'
  • +%%
  • `"urn:ietf:params:netconf:capability:xpath:1.0"'
  • +%%
+%% +%% Note, additional identifiers may exist, e.g. server side namespace. +%% +%% @end +%%---------------------------------------------------------------------- +get_capabilities(Client, Timeout) -> + call(Client, get_capabilities, Timeout). + +%% @private +send(Client, SimpleXml) -> + send(Client, SimpleXml, ?DEFAULT_TIMEOUT). +%% @private +send(Client, SimpleXml, Timeout) -> + call(Client,{send, Timeout, SimpleXml}). + +%% @private +send_rpc(Client, SimpleXml) -> + send_rpc(Client, SimpleXml, ?DEFAULT_TIMEOUT). +%% @private +send_rpc(Client, SimpleXml, Timeout) -> + call(Client,{send_rpc, SimpleXml, Timeout}). + + + +%%---------------------------------------------------------------------- +%% @spec lock(Client, Target) -> Result +%% @equiv lock(Client, Target, infinity) +lock(Client, Target) -> + lock(Client, Target,?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec lock(Client, Target, Timeout) -> Result when + Client :: client(), + Target :: netconf_db(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Unlock configuration target. +%% +%% Which target parameters that can be used depends on if +%% `:candidate' and/or `:startup' are supported by the +%% server. If successfull, the configuration system of the device is +%% not available to other clients (Netconf, CORBA, SNMP etc). Locks +%% are intended to be short-lived. +%% +%% The operations {@link kill_session/2} or {@link kill_session/3} can +%% be used to force the release of a lock owned by another Netconf +%% session. How this is achieved by the server side is implementation +%% specific. +%% +%% @end +%%---------------------------------------------------------------------- +lock(Client, Target, Timeout) -> + call(Client,{send_rpc_op,lock,[Target],Timeout}). + +%%---------------------------------------------------------------------- +%% @spec unlock(Client, Target) -> Result +%% @equiv unlock(Client, Target, infinity) +unlock(Client, Target) -> + unlock(Client, Target,?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec unlock(Client, Target, Timeout) -> Result when + Client :: client(), + Target :: netconf_db(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Unlock configuration target. +%% +%% If the client earlier has aquired a lock, via {@link lock/2} or +%% {@link lock/3}, this operation release the associated lock. To be +%% able to access another target than `running', the server must +%% support `:candidate' and/or `:startup'. +%% +%% @end +%%---------------------------------------------------------------------- +unlock(Client, Target, Timeout) -> + call(Client, {send_rpc_op, unlock, [Target], Timeout}). + +%%---------------------------------------------------------------------- +%% @spec get(Client, Filter) -> Result +%% @equiv get(Client, Filter, infinity) +get(Client, Filter) -> + get(Client, Filter, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec get(Client, Filter, Timeout) -> Result when + Client :: client(), + Filter :: simple_xml() | xpath(), + Timeout :: timeout(), + Result :: {ok,simple_xml()} | {error,error_reason()}. +%% @doc Get data. +%% +%% This operation returns both configuration and state data from the +%% server. +%% +%% Filter type `xpath' can only be used if the server supports +%% `:xpath'. +%% +%% @end +%%---------------------------------------------------------------------- +get(Client, Filter, Timeout) -> + call(Client,{send_rpc_op, get, [Filter], Timeout}). + +%%---------------------------------------------------------------------- +%% @spec get_config(Client, Source, Filter) -> Result +%% @equiv get_config(Client, Source, Filter, infinity) +get_config(Client, Source, Filter) -> + get_config(Client, Source, Filter, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec get_config(Client, Source, Filter, Timeout) -> Result when + Client :: client(), + Source :: netconf_db(), + Filter :: simple_xml() | xpath(), + Timeout :: timeout(), + Result :: {ok,simple_xml()} | {error,error_reason()}. +%% @doc Get configuration data. +%% +%% To be able to access another source than `running', the server +%% must advertise `:candidate' and/or `:startup'. +%% +%% Filter type `xpath' can only be used if the server supports +%% `:xpath'. +%% +%% +%% @end +%%---------------------------------------------------------------------- +get_config(Client, Source, Filter, Timeout) -> + call(Client, {send_rpc_op, get_config, [Source, Filter], Timeout}). + +%%---------------------------------------------------------------------- +%% @spec edit_config(Client, Target, Config) -> Result +%% @equiv edit_config(Client, Target, Config, infinity) +edit_config(Client, Target, Config) -> + edit_config(Client, Target, Config, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec edit_config(Client, Target, Config, Timeout) -> Result when + Client :: client(), + Target :: netconf_db(), + Config :: simple_xml(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Edit configuration data. +%% +%% Per default only the running target is available, unless the server +%% include `:candidate' or `:startup' in its list of +%% capabilities. +%% +%% @end +%%---------------------------------------------------------------------- +edit_config(Client, Target, Config, Timeout) -> + call(Client, {send_rpc_op, edit_config, [Target,Config], Timeout}). + + +%%---------------------------------------------------------------------- +%% @spec delete_config(Client, Target) -> Result +%% @equiv delete_config(Client, Target, infinity) +delete_config(Client, Target) -> + delete_config(Client, Target, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec delete_config(Client, Target, Timeout) -> Result when + Client :: client(), + Target :: startup | candidate, + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Delete configuration data. +%% +%% The running configuration cannot be deleted and `:candidate' +%% or `:startup' must be advertised by the server. +%% +%% @end +%%---------------------------------------------------------------------- +delete_config(Client, Target, Timeout) when Target == startup; + Target == candidate -> + call(Client,{send_rpc_op, delete_config, [Target], Timeout}). + +%%---------------------------------------------------------------------- +%% @spec copy_config(Client, Source, Target) -> Result +%% @equiv copy_config(Client, Source, Target, infinity) +copy_config(Client, Source, Target) -> + copy_config(Client, Source, Target, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec copy_config(Client, Target, Source, Timeout) -> Result when + Client :: client(), + Target :: netconf_db(), + Source :: netconf_db(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Copy configuration data. +%% +%% Which source and target options that can be issued depends on the +%% capabilities supported by the server. I.e. `:candidate' and/or +%% `:startup' are required. +%% +%% @end +%%---------------------------------------------------------------------- +copy_config(Client, Target, Source, Timeout) -> + call(Client,{send_rpc_op, copy_config, [Target, Source], Timeout}). + +%%---------------------------------------------------------------------- +%% @spec action(Client, Action) -> Result +%% @equiv action(Client, Action, infinity) +action(Client,Action) -> + action(Client,Action,?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec action(Client, Action, Timeout) -> Result when + Client :: client(), + Action :: simple_xml(), + Timeout :: timeout(), + Result :: {ok,simple_xml()} | {error,error_reason()}. +%% @doc Execute an action. +%% +%% @end +%%---------------------------------------------------------------------- +action(Client,Action,Timeout) -> + call(Client,{send_rpc_op, action, [Action], Timeout}). + +%%---------------------------------------------------------------------- +create_subscription(Client) -> + create_subscription(Client,?DEFAULT_STREAM,?DEFAULT_TIMEOUT). + +create_subscription(Client,Timeout) + when ?is_timeout(Timeout) -> + create_subscription(Client,?DEFAULT_STREAM,Timeout); +create_subscription(Client,Stream) + when is_list(Stream) -> + create_subscription(Client,Stream,?DEFAULT_TIMEOUT); +create_subscription(Client,Filter) + when ?is_filter(Filter) -> + create_subscription(Client,?DEFAULT_STREAM,Filter, + ?DEFAULT_TIMEOUT). + +create_subscription(Client,Stream,Timeout) + when is_list(Stream) andalso + ?is_timeout(Timeout) -> + call(Client,{send_rpc_op,{create_subscription,self()}, + [Stream,undefined,undefined,undefined], + Timeout}); +create_subscription(Client,StartTime,StopTime) + when is_list(StartTime) andalso + is_list(StopTime) -> + create_subscription(Client,?DEFAULT_STREAM,StartTime,StopTime, + ?DEFAULT_TIMEOUT); +create_subscription(Client,Filter,Timeout) + when ?is_filter(Filter) andalso + ?is_timeout(Timeout) -> + create_subscription(Client,?DEFAULT_STREAM,Filter,Timeout); +create_subscription(Client,Stream,Filter) + when is_list(Stream) andalso + ?is_filter(Filter) -> + create_subscription(Client,Stream,Filter,?DEFAULT_TIMEOUT). + +create_subscription(Client,StartTime,StopTime,Timeout) + when is_list(StartTime) andalso + is_list(StopTime) andalso + ?is_timeout(Timeout) -> + create_subscription(Client,?DEFAULT_STREAM,StartTime,StopTime,Timeout); +create_subscription(Client,Stream,StartTime,StopTime) + when is_list(Stream) andalso + is_list(StartTime) andalso + is_list(StopTime) -> + create_subscription(Client,Stream,StartTime,StopTime,?DEFAULT_TIMEOUT); +create_subscription(Client,Filter,StartTime,StopTime) + when ?is_filter(Filter) andalso + is_list(StartTime) andalso + is_list(StopTime) -> + create_subscription(Client,?DEFAULT_STREAM,Filter, + StartTime,StopTime,?DEFAULT_TIMEOUT); +create_subscription(Client,Stream,Filter,Timeout) + when is_list(Stream) andalso + ?is_filter(Filter) andalso + ?is_timeout(Timeout) -> + call(Client,{send_rpc_op,{create_subscription,self()}, + [Stream,Filter,undefined,undefined], + Timeout}). + +create_subscription(Client,Stream,StartTime,StopTime,Timeout) + when is_list(Stream) andalso + is_list(StartTime) andalso + is_list(StopTime) andalso + ?is_timeout(Timeout) -> + call(Client,{send_rpc_op,{create_subscription,self()}, + [Stream,undefined,StartTime,StopTime], + Timeout}); +create_subscription(Client,Stream,Filter,StartTime,StopTime) + when is_list(Stream) andalso + ?is_filter(Filter) andalso + is_list(StartTime) andalso + is_list(StopTime) -> + create_subscription(Client,Stream,Filter,StartTime,StopTime,?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec create_subscription(Client, Stream, Filter,StartTime, StopTime, Timeout) -> + Result when + Client :: client(), + Stream :: stream_name(), + Filter :: simple_xml(), + StartTime :: xs_datetime(), + StopTime :: xs_datetime(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Create a subscription for event notifications. +%% +%% This function sets up a subscription for netconf event +%% notifications of the given stream type, matching the given +%% filter. The calling process will receive notifications as messages +%% of type `notification()'. +%% +%%
+%%
Stream:
+%%
An optional parameter that indicates which stream of events +%% is of interest. If not present, events in the default NETCONF +%% stream will be sent.
+%% +%%
Filter:
+%%
An optional parameter that indicates which subset of all +%% possible events is of interest. The format of this parameter is +%% the same as that of the filter parameter in the NETCONF protocol +%% operations. If not present, all events not precluded by other +%% parameters will be sent. See section 3.6 for more information on +%% filters.
+%% +%%
StartTime:
+%%
An optional parameter used to trigger the replay feature and +%% indicate that the replay should start at the time specified. If +%% `StartTime' is not present, this is not a replay subscription. +%% It is not valid to specify start times that are later than the +%% current time. If the `StartTime' specified is earlier than the +%% log can support, the replay will begin with the earliest +%% available notification. This parameter is of type dateTime and +%% compliant to [RFC3339]. Implementations must support time +%% zones.
+%% +%%
StopTime:
+%%
An optional parameter used with the optional replay feature +%% to indicate the newest notifications of interest. If `StopTime' +%% is not present, the notifications will continue until the +%% subscription is terminated. Must be used with and be later than +%% `StartTime'. Values of `StopTime' in the future are valid. This +%% parameter is of type dateTime and compliant to [RFC3339]. +%% Implementations must support time zones.
+%%
+%% +%% See RFC5277 for further details about the event notification +%% mechanism. +%% +%% @end +%%---------------------------------------------------------------------- +create_subscription(Client,Stream,Filter,StartTime,StopTime,Timeout) -> + call(Client,{send_rpc_op,{create_subscription, self()}, + [Stream,Filter,StartTime,StopTime], + Timeout}). + +%%---------------------------------------------------------------------- +%% @spec get_event_streams(Client, Timeout) -> Result +%% @equiv get_event_streams(Client, [], Timeout) +get_event_streams(Client,Timeout) when is_integer(Timeout); Timeout==infinity -> + get_event_streams(Client,[],Timeout); + +%%---------------------------------------------------------------------- +%% @spec get_event_streams(Client, Streams) -> Result +%% @equiv get_event_streams(Client, Streams, infinity) +get_event_streams(Client,Streams) when is_list(Streams) -> + get_event_streams(Client,Streams,?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec get_event_streams(Client, Streams, Timeout) + -> Result when + Client :: client(), + Streams :: [stream_name()], + Timeout :: timeout(), + Result :: {ok,streams()} | {error,error_reason()}. +%% @doc Send a request to get the given event streams. +%% +%% `Streams' is a list of stream names. The following filter will +%% be sent to the netconf server in a `get' request: +%% +%% ``` +%% +%% +%% +%% StreamName1 +%% +%% +%% StreamName2 +%% +%% ... +%% +%% +%% ''' +%% +%% If `Streams' is an empty list, ALL streams will be requested +%% by sending the following filter: +%% +%% ``` +%% +%% +%% +%% ''' +%% +%% If more complex filtering is needed, a use {@link get/2} or {@link +%% get/3} and specify the exact filter according to XML Schema for +%% Event Notifications found in RFC5277. +%% +%% @end +%%---------------------------------------------------------------------- +get_event_streams(Client,Streams,Timeout) -> + call(Client,{get_event_streams,Streams,Timeout}). + + +%%---------------------------------------------------------------------- +%% @spec close_session(Client) -> Result +%% @equiv close_session(Client, infinity) +close_session(Client) -> + close_session(Client, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec close_session(Client, Timeout) -> Result when + Client :: client(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Request graceful termination of the session associated with the client. +%% +%% When a netconf server receives a `close-session' request, it +%% will gracefully close the session. The server will release any +%% locks and resources associated with the session and gracefully +%% close any associated connections. Any NETCONF requests received +%% after a `close-session' request will be ignored. +%% +%% @end +%%---------------------------------------------------------------------- +close_session(Client, Timeout) -> + call(Client,{send_rpc_op, close_session, [], Timeout}). + + +%%---------------------------------------------------------------------- +%% @spec kill_session(Client, SessionId) -> Result +%% @equiv kill_session(Client, SessionId, infinity) +kill_session(Client, SessionId) -> + kill_session(Client, SessionId, ?DEFAULT_TIMEOUT). + +%%---------------------------------------------------------------------- +-spec kill_session(Client, SessionId, Timeout) -> Result when + Client :: client(), + SessionId :: pos_integer(), + Timeout :: timeout(), + Result :: ok | {error,error_reason()}. +%% @doc Force termination of the session associated with the supplied +%% session id. +%% +%% The server side shall abort any operations currently in process, +%% release any locks and resources associated with the session, and +%% close any associated connections. +%% +%% Only if the server is in the confirmed commit phase, the +%% configuration will be restored to its state before entering the +%% confirmed commit phase. Otherwise, no configuration roll back will +%% be performed. +%% +%% If the given `SessionId' is equal to the current session id, +%% an error will be returned. +%% +%% @end +%% ---------------------------------------------------------------------- +kill_session(Client, SessionId, Timeout) -> + call(Client,{send_rpc_op, kill_session, [SessionId], Timeout}). + + +%%---------------------------------------------------------------------- +%% Callback functions +%%---------------------------------------------------------------------- + +%% @private +init(_KeyOrName,{_Host,_Port},Options) -> + case ssh_open(Options) of + {ok, Connection} -> + log(Connection,open), + {ConnPid,_} = Connection#connection.reference, + {ok, ConnPid, #state{connection = Connection}}; + {error,Reason}-> + {error,Reason} + end. + +%% @private +terminate(_, #state{connection=Connection}) -> + ssh_close(Connection), + log(Connection,close), + ok. + +%% @private +handle_msg({hello,Timeout}, From, + #state{connection=Connection,hello_status=HelloStatus} = State) -> + case do_send(Connection, client_hello()) of + ok -> + case HelloStatus of + undefined -> + {Ref,TRef} = set_request_timer(Timeout), + {noreply, State#state{hello_status=#pending{tref=TRef, + ref=Ref, + caller=From}}}; + received -> + {reply, ok, State#state{hello_status=done}}; + {error,Reason} -> + {stop, {error,Reason}, State} + end; + Error -> + {stop, Error, State} + end; +handle_msg(_, _From, #state{session_id=undefined} = State) -> + %% Hello is not yet excanged - this shall never happen + {reply,{error,waiting_for_hello},State}; +handle_msg(get_capabilities, _From, #state{capabilities = Caps} = State) -> + {reply, Caps, State}; +handle_msg(get_session_id, _From, #state{session_id = Id} = State) -> + {reply, Id, State}; +handle_msg({send, Timeout, SimpleXml}, From, + #state{connection=Connection,pending=Pending} = State) -> + case do_send(Connection, SimpleXml) of + ok -> + {Ref,TRef} = set_request_timer(Timeout), + {noreply, State#state{pending=[#pending{tref=TRef, + ref=Ref, + caller=From} | Pending]}}; + Error -> + {reply, Error, State} + end; +handle_msg({send_rpc, SimpleXml, Timeout}, From, State) -> + do_send_rpc(undefined, SimpleXml, Timeout, From, State); +handle_msg({send_rpc_op, Op, Data, Timeout}, From, State) -> + SimpleXml = encode_rpc_operation(Op,Data), + do_send_rpc(Op, SimpleXml, Timeout, From, State); +handle_msg({get_event_streams=Op,Streams,Timeout}, From, State) -> + Filter = {netconf,?NETMOD_NOTIF_NAMESPACE_ATTR, + [{streams,[{stream,[{name,[Name]}]} || Name <- Streams]}]}, + SimpleXml = encode_rpc_operation(get,[Filter]), + do_send_rpc(Op, SimpleXml, Timeout, From, State). + +handle_msg({ssh_cm, _CM, {data, _Ch, _Type, Data}}, State) -> + handle_data(Data, State); +handle_msg({ssh_cm, _CM, {closed,_Ch}}, State) -> + %% This will happen if the server terminates the connection, as in + %% kill-session (or if ssh:close is called from somewhere + %% unexpected). + + %%! Log this?? - i.e. as server closing the connection + %%! Currently the log will say that the client closed the + %%! connection - due to terminate/2 + + {stop, State}; +handle_msg({Ref,timeout}, + #state{hello_status=#pending{ref=Ref,caller=Caller}} = State) -> + ct_gen_conn:return(Caller,{error,{hello_session_failed,timeout}}), + {stop,State#state{hello_status={error,timeout}}}; +handle_msg({Ref,timeout},#state{pending=Pending} = State) -> + {value,#pending{caller=Caller},Pending1} = + lists:keytake(Ref,#pending.ref,Pending), + ct_gen_conn:return(Caller,{error,timeout}), + {noreply,State#state{pending=Pending1}}. + +%% @private +%% Called by ct_util_server to close registered connections before terminate. +close(Client) -> + case get_handle(Client) of + {ok,Pid} -> + case ct_gen_conn:stop(Pid) of + {error,{process_down,Pid,noproc}} -> + {error,already_closed}; + Result -> + Result + end; + Error -> + Error + end. + + +%%---------------------------------------------------------------------- +%% Internal functions +%%---------------------------------------------------------------------- +call(Client, Msg) -> + call(Client, Msg, infinity). +call(Client, Msg, Timeout) -> + case get_handle(Client) of + {ok,Pid} -> + case ct_gen_conn:call(Pid,Msg,Timeout) of + {error,{process_down,Client,noproc}} -> + {error,no_such_client}; + {error,{process_down,Client,normal}} -> + {error,closed}; + {error,{process_down,Client,Reason}} -> + {error,{closed,Reason}}; + Other -> + Other + end; + Error -> + Error + end. + +get_handle(Client) when is_pid(Client) -> + {ok,Client}; +get_handle(Client) -> + case ct_util:get_connections(Client, ?MODULE) of + {ok,[{Pid,_}]} -> + {ok,Pid}; + {ok,[]} -> + {error,{no_connection_found,Client}}; + {ok,Conns} -> + {error,{multiple_connections_found,Client,Conns}}; + Error -> + Error + end. + +check_options([], undefined, _Port, _Options) -> + {error, no_host_address}; +check_options([], _Host, undefined, _Options) -> + {error, no_port}; +check_options([], Host, Port, Options) -> + {Host,Port,Options}; +check_options([{ssh, Host}|T], _, Port, #options{} = Options) -> + check_options(T, Host, Port, Options#options{host=Host}); +check_options([{port,Port}|T], Host, _, #options{} = Options) -> + check_options(T, Host, Port, Options#options{port=Port}); +check_options([{timeout, Timeout}|T], Host, Port, Options) + when is_integer(Timeout); Timeout==infinity -> + check_options(T, Host, Port, Options#options{timeout = Timeout}); +check_options([{X,_}=Opt|T], Host, Port, #options{ssh=SshOpts}=Options) -> + case lists:member(X,?VALID_SSH_OPTS) of + true -> + check_options(T, Host, Port, Options#options{ssh=[Opt|SshOpts]}); + false -> + {error, {invalid_option, Opt}} + end. + +%%%----------------------------------------------------------------- +set_request_timer(infinity) -> + {undefined,undefined}; +set_request_timer(T) -> + Ref = make_ref(), + {ok,TRef} = timer:send_after(T,{Ref,timeout}), + {Ref,TRef}. + + +%%%----------------------------------------------------------------- +client_hello() -> + {hello, ?NETCONF_NAMESPACE_ATTR, + [{capabilities, + [{capability,[?NETCONF_BASE_CAP++?NETCONF_BASE_CAP_VSN]}]}]}. + +%%%----------------------------------------------------------------- + +encode_rpc_operation(Lock,[Target]) when Lock==lock; Lock==unlock -> + {Lock,[{target,[Target]}]}; +encode_rpc_operation(get,[Filter]) -> + {get,filter(Filter)}; +encode_rpc_operation(get_config,[Source,Filter]) -> + {'get-config',[{source,[Source]}] ++ filter(Filter)}; +encode_rpc_operation(edit_config,[Target,Config]) -> + {'edit-config',[{target,[Target]},{config,[Config]}]}; +encode_rpc_operation(delete_config,[Target]) -> + {'delete-config',[{target,[Target]}]}; +encode_rpc_operation(copy_config,[Target,Source]) -> + {'copy-config',[{target,[Target]},{source,[Source]}]}; +encode_rpc_operation(action,[Action]) -> + {action,?ACTION_NAMESPACE_ATTR,[{data,[Action]}]}; +encode_rpc_operation(kill_session,[SessionId]) -> + {'kill-session',[{'session-id',[integer_to_list(SessionId)]}]}; +encode_rpc_operation(close_session,[]) -> + 'close-session'; +encode_rpc_operation({create_subscription,_}, + [Stream,Filter,StartTime,StopTime]) -> + {'create-subscription',?NETCONF_NOTIF_NAMESPACE_ATTR, + [{stream,[Stream]}] ++ + filter(Filter) ++ + maybe_element(startTime,StartTime) ++ + maybe_element(stopTime,StopTime)}. + +filter(undefined) -> + []; +filter({xpath,Filter}) when ?is_string(Filter) -> + [{filter,[{type,"xpath"},{select, Filter}],[]}]; +filter(Filter) -> + [{filter,[{type,"subtree"}],[Filter]}]. + +maybe_element(_,undefined) -> + []; +maybe_element(Tag,Value) -> + [{Tag,[Value]}]. + +%%%----------------------------------------------------------------- +%%% Send XML data to server +do_send_rpc(PendingOp,SimpleXml,Timeout,Caller, + #state{connection=Connection,msg_id=MsgId,pending=Pending} = State) -> + case do_send_rpc(Connection, MsgId, SimpleXml) of + ok -> + {Ref,TRef} = set_request_timer(Timeout), + {noreply, State#state{msg_id=MsgId+1, + pending=[#pending{tref=TRef, + ref=Ref, + msg_id=MsgId, + op=PendingOp, + caller=Caller} | Pending]}}; + Error -> + {reply, Error, State#state{msg_id=MsgId+1}} + end. + +do_send_rpc(Connection, MsgId, SimpleXml) -> + do_send(Connection, + {rpc, + [{'message-id',MsgId} | ?NETCONF_NAMESPACE_ATTR], + [SimpleXml]}). + +do_send(Connection, SimpleXml) -> + Xml=to_xml_doc(SimpleXml), + log(Connection,send,Xml), + ssh_send(Connection, Xml). + +to_xml_doc(Simple) -> + Prolog = "", + Xml = list_to_binary(xmerl:export_simple([Simple], + xmerl_xml, + [#xmlAttribute{name=prolog, + value=Prolog}])), + <>. + +%%%----------------------------------------------------------------- +%%% Parse and handle received XML data +handle_data(NewData,#state{connection=Connection,buff=Buff} = State) -> + log(Connection,recv,NewData), + Data = <>, + case xmerl_sax_parser:stream(<<>>, + [{continuation_fun,fun sax_cont/1}, + {continuation_state,{Data,Connection,false}}, + {event_fun,fun sax_event/3}, + {event_state,[]}]) of + {ok, Simple, Rest} -> + decode(Simple,State#state{buff=Rest}); + {fatal_error,_Loc,Reason,_EndTags,_EventState} -> + ?error(Connection#connection.name,[{parse_error,Reason}, + {data,Data}]), + case Reason of + {could_not_fetch_data,Msg} -> + handle_msg(Msg,State#state{buff = <<>>}); + _Other -> + Pending1 = + case State#state.pending of + [] -> + []; + Pending -> + %% Assuming the first request gets the + %% first answer + P=#pending{tref=TRef,caller=Caller} = + lists:last(Pending), + timer:cancel(TRef), + Reason1 = {failed_to_parse_received_data,Reason}, + ct_gen_conn:return(Caller,{error,Reason1}), + lists:delete(P,Pending) + end, + {noreply,State#state{pending=Pending1,buff = <<>>}} + end + end. + +%%%----------------------------------------------------------------- +%%% Parsing of XML data +%% Contiuation function for the sax parser +sax_cont(done) -> + {<<>>,done}; +sax_cont({Data,Connection,false}) -> + case binary:split(Data,[?END_TAG],[]) of + [All] -> + %% No end tag found. Remove what could be a part + %% of an end tag from the data and save for next + %% iteration + SafeSize = size(All)-5, + <> = All, + {New,{Save,Connection,true}}; + [_Msg,_Rest]=Msgs -> + %% We have at least one full message. Any excess data will + %% be returned from xmerl_sax_parser:stream/2 in the Rest + %% parameter. + {list_to_binary(Msgs),done} + end; +sax_cont({Data,Connection,true}) -> + case ssh_receive_data() of + {ok,Bin} -> + log(Connection,recv,Bin), + sax_cont({<>,Connection,false}); + {error,Reason} -> + throw({could_not_fetch_data,Reason}) + end. + + + +%% Event function for the sax parser. It builds a simple XML structure. +%% Care is taken to keep namespace attributes and prefixes as in the original XML. +sax_event(Event,_Loc,State) -> + sax_event(Event,State). + +sax_event({startPrefixMapping, Prefix, Uri},Acc) -> + %% startPrefixMapping will always come immediately before the + %% startElement where the namespace is defined. + [{xmlns,{Prefix,Uri}}|Acc]; +sax_event({startElement,_Uri,_Name,QN,Attrs},Acc) -> + %% Pick out any namespace attributes inserted due to a + %% startPrefixMapping event.The rest of Acc will then be only + %% elements. + {NsAttrs,NewAcc} = split_attrs_and_elements(Acc,[]), + Tag = qn_to_tag(QN), + [{Tag,NsAttrs ++ parse_attrs(Attrs),[]}|NewAcc]; +sax_event({endElement,_Uri,_Name,_QN},[{Name,Attrs,Cont},{Parent,PA,PC}|Acc]) -> + [{Parent,PA,[{Name,Attrs,lists:reverse(Cont)}|PC]}|Acc]; +sax_event(endDocument,[{Tag,Attrs,Cont}]) -> + {Tag,Attrs,lists:reverse(Cont)}; +sax_event({characters,String},[{Name,Attrs,Cont}|Acc]) -> + [{Name,Attrs,[String|Cont]}|Acc]; +sax_event(_Event,State) -> + State. + +split_attrs_and_elements([{xmlns,{Prefix,Uri}}|Rest],Attrs) -> + split_attrs_and_elements(Rest,[{xmlnstag(Prefix),Uri}|Attrs]); +split_attrs_and_elements(Elements,Attrs) -> + {Attrs,Elements}. + +xmlnstag([]) -> + xmlns; +xmlnstag(Prefix) -> + list_to_atom("xmlns:"++Prefix). + +qn_to_tag({[],Name}) -> + list_to_atom(Name); +qn_to_tag({Prefix,Name}) -> + list_to_atom(Prefix ++ ":" ++ Name). + +parse_attrs([{_Uri, [], Name, Value}|Attrs]) -> + [{list_to_atom(Name),Value}|parse_attrs(Attrs)]; +parse_attrs([{_Uri, Prefix, Name, Value}|Attrs]) -> + [{list_to_atom(Prefix ++ ":" ++ Name),Value}|parse_attrs(Attrs)]; +parse_attrs([]) -> + []. + + +%%%----------------------------------------------------------------- +%%% Decoding of parsed XML data +decode({Tag,Attrs,_}=E, #state{connection=Connection,pending=Pending}=State) -> + ConnName = Connection#connection.name, + case get_local_name_atom(Tag) of + 'rpc-reply' -> + case get_msg_id(Attrs) of + undefined -> + case Pending of + [#pending{msg_id=MsgId}] -> + ?error(ConnName,[{warning,rpc_reply_missing_msg_id}, + {assuming,MsgId}]), + decode_rpc_reply(MsgId,E,State); + _ -> + ?error(ConnName,[{error,rpc_reply_missing_msg_id}]), + {noreply,State} + end; + MsgId -> + decode_rpc_reply(MsgId,E,State) + end; + hello -> + case State#state.hello_status of + undefined -> + case decode_hello(E) of + {ok,SessionId,Capabilities} -> + {noreply,State#state{session_id = SessionId, + capabilities = Capabilities, + hello_status = received}}; + {error,Reason} -> + {noreply,State#state{hello_status = {error,Reason}}} + end; + #pending{tref=TRef,caller=Caller} -> + timer:cancel(TRef), + case decode_hello(E) of + {ok,SessionId,Capabilities} -> + ct_gen_conn:return(Caller,ok), + {noreply,State#state{session_id = SessionId, + capabilities = Capabilities, + hello_status = done}}; + {error,Reason} -> + ct_gen_conn:return(Caller,{error,Reason}), + {stop,State#state{hello_status={error,Reason}}} + end; + Other -> + ?error(ConnName,[{got_unexpected_hello,E}, + {hello_status,Other}]), + {noreply,State} + end; + notification -> + EventReceiver = State#state.event_receiver, + EventReceiver ! E, + {noreply,State}; + Other -> + %% Result of send/2, when not sending an rpc request - or + %% if netconf server sends noise. Can handle this only if + %% there is just one pending that matches (i.e. has + %% undefined msg_id and op) + case [P || P = #pending{msg_id=undefined,op=undefined} <- Pending] of + [#pending{tref=TRef, + caller=Caller}] -> + timer:cancel(TRef), + ct_gen_conn:return(Caller,E), + {noreply,State#state{pending=[]}}; + _ -> + ?error(ConnName,[{got_unexpected_msg,Other}, + {expecting,Pending}]), + {noreply,State} + end + + end. + +get_msg_id(Attrs) -> + case lists:keyfind('message-id',1,Attrs) of + {_,Str} -> + list_to_integer(Str); + false -> + undefined + end. + +decode_rpc_reply(MsgId,{_,Attrs,Content0}=E,#state{pending=Pending} = State) -> + case lists:keytake(MsgId,#pending.msg_id,Pending) of + {value, #pending{tref=TRef,op=Op,caller=Caller}, Pending1} -> + timer:cancel(TRef), + Content = forward_xmlns_attr(Attrs,Content0), + {CallerReply,{ServerReply,State2}} = + do_decode_rpc_reply(Op,Content,State#state{pending=Pending1}), + ct_gen_conn:return(Caller,CallerReply), + {ServerReply,State2}; + false -> + %% Result of send/2, when receiving a correct + %% rpc-reply. Can handle this only if there is just one + %% pending that matches (i.e. has undefined msg_id and op) + case [P || P = #pending{msg_id=undefined,op=undefined} <- Pending] of + [#pending{tref=TRef, + msg_id=undefined, + op=undefined, + caller=Caller}] -> + timer:cancel(TRef), + ct_gen_conn:return(Caller,E), + {noreply,State#state{pending=[]}}; + _ -> + ConnName = (State#state.connection)#connection.name, + ?error(ConnName,[{got_unexpected_msg_id,MsgId}, + {expecting,Pending}]), + {noreply,State} + end + end. + +do_decode_rpc_reply(Op,Result,State) + when Op==lock; Op==unlock; Op==edit_config; Op==delete_config; + Op==copy_config; Op==kill_session -> + {decode_ok(Result),{noreply,State}}; +do_decode_rpc_reply(Op,Result,State) + when Op==get; Op==get_config; Op==action -> + {decode_data(Result),{noreply,State}}; +do_decode_rpc_reply(close_session,Result,State) -> + case decode_ok(Result) of + ok -> {ok,{stop,State}}; + Other -> {Other,{noreply,State}} + end; +do_decode_rpc_reply({create_subscription,Caller},Result,State) -> + case decode_ok(Result) of + ok -> + {ok,{noreply,State#state{event_receiver=Caller}}}; + Other -> + {Other,{noreply,State}} + end; +do_decode_rpc_reply(get_event_streams,Result,State) -> + {decode_streams(decode_data(Result)),{noreply,State}}; +do_decode_rpc_reply(undefined,Result,State) -> + {Result,{noreply,State}}. + + + +decode_ok([{Tag,Attrs,Content}]) -> + case get_local_name_atom(Tag) of + ok -> + ok; + 'rpc-error' -> + {error,forward_xmlns_attr(Attrs,Content)}; + _Other -> + {error,{unexpected_rpc_reply,[{Tag,Attrs,Content}]}} + end; +decode_ok(Other) -> + {error,{unexpected_rpc_reply,Other}}. + +decode_data([{Tag,Attrs,Content}]) -> + case get_local_name_atom(Tag) of + data -> + %% Since content of data has nothing from the netconf + %% namespace, we remove the parent's xmlns attribute here + %% - just to make the result cleaner + {ok,forward_xmlns_attr(remove_xmlnsattr_for_tag(Tag,Attrs),Content)}; + 'rpc-error' -> + {error,forward_xmlns_attr(Attrs,Content)}; + _Other -> + {error,{unexpected_rpc_reply,[{Tag,Attrs,Content}]}} + end; +decode_data(Other) -> + {error,{unexpected_rpc_reply,Other}}. + +get_qualified_name(Tag) -> + case string:tokens(atom_to_list(Tag),":") of + [TagStr] -> {[],TagStr}; + [PrefixStr,TagStr] -> {PrefixStr,TagStr} + end. + +get_local_name_atom(Tag) -> + {_,TagStr} = get_qualified_name(Tag), + list_to_atom(TagStr). + + +%% Remove the xmlns attr that points to the tag. I.e. if the tag has a +%% prefix, remove {'xmlns:prefix',_}, else remove default {xmlns,_}. +remove_xmlnsattr_for_tag(Tag,Attrs) -> + {Prefix,_TagStr} = get_qualified_name(Tag), + XmlnsTag = xmlnstag(Prefix), + case lists:keytake(XmlnsTag,1,Attrs) of + {value,_,NoNsAttrs} -> + NoNsAttrs; + false -> + Attrs + end. + +%% Take all xmlns attributes from the parent's attribute list and +%% forward into all childrens' attribute lists. But do not overwrite +%% any. +forward_xmlns_attr(ParentAttrs,Children) -> + do_forward_xmlns_attr(get_all_xmlns_attrs(ParentAttrs,[]),Children). + +do_forward_xmlns_attr(XmlnsAttrs,[{ChT,ChA,ChC}|Children]) -> + ChA1 = add_xmlns_attrs(XmlnsAttrs,ChA), + [{ChT,ChA1,ChC} | do_forward_xmlns_attr(XmlnsAttrs,Children)]; +do_forward_xmlns_attr(_XmlnsAttrs,[]) -> + []. + +add_xmlns_attrs([{Key,_}=A|XmlnsAttrs],ChA) -> + case lists:keymember(Key,1,ChA) of + true -> + add_xmlns_attrs(XmlnsAttrs,ChA); + false -> + add_xmlns_attrs(XmlnsAttrs,[A|ChA]) + end; +add_xmlns_attrs([],ChA) -> + ChA. + +get_all_xmlns_attrs([{xmlns,_}=Default|Attrs],XmlnsAttrs) -> + get_all_xmlns_attrs(Attrs,[Default|XmlnsAttrs]); +get_all_xmlns_attrs([{Key,_}=Attr|Attrs],XmlnsAttrs) -> + case atom_to_list(Key) of + "xmlns:"++_Prefix -> + get_all_xmlns_attrs(Attrs,[Attr|XmlnsAttrs]); + _ -> + get_all_xmlns_attrs(Attrs,XmlnsAttrs) + end; +get_all_xmlns_attrs([],XmlnsAttrs) -> + XmlnsAttrs. + + +%% Decode server hello to pick out session id and capabilities +decode_hello({hello,_Attrs,Hello}) -> + case lists:keyfind('session-id',1,Hello) of + {'session-id',_,[SessionId]} -> + case lists:keyfind(capabilities,1,Hello) of + {capabilities,_,Capabilities} -> + case decode_caps(Capabilities,[],false) of + {ok,Caps} -> + {ok,list_to_integer(SessionId),Caps}; + Error -> + Error + end; + false -> + {error,{incorrect_hello,capabilities_not_found}} + end; + false -> + {error,{incorrect_hello,no_session_id_found}} + end. + +decode_caps([{capability,[],[?NETCONF_BASE_CAP++Vsn=Cap]} |Caps], Acc, _) -> + case Vsn of + ?NETCONF_BASE_CAP_VSN -> + decode_caps(Caps, [Cap|Acc], true); + _ -> + {error,{incompatible_base_capability_vsn,Vsn}} + end; +decode_caps([{capability,[],[Cap]}|Caps],Acc,Base) -> + decode_caps(Caps,[Cap|Acc],Base); +decode_caps([H|_T],_,_) -> + {error,{unexpected_capability_element,H}}; +decode_caps([],_,false) -> + {error,{incorrect_hello,no_base_capability_found}}; +decode_caps([],Acc,true) -> + {ok,lists:reverse(Acc)}. + + +%% Return a list of {Name,Data}, where data is a {Tag,Value} list for each stream +decode_streams({error,Reason}) -> + {error,Reason}; +decode_streams({ok,[{netconf,_,Streams}]}) -> + {ok,decode_streams(Streams)}; +decode_streams([{streams,_,Streams}]) -> + decode_streams(Streams); +decode_streams([{stream,_,Stream} | Streams]) -> + {name,_,[Name]} = lists:keyfind(name,1,Stream), + [{Name,[{Tag,Value} || {Tag,_,[Value]} <- Stream, Tag /= name]} + | decode_streams(Streams)]; +decode_streams([]) -> + []. + + +%%%----------------------------------------------------------------- +%%% Logging + +log(Connection,Action) -> + log(Connection,Action,<<>>). +log(#connection{host=Host,port=Port,name=Name},Action,Data) -> + error_logger:info_report(#conn_log{client=self(), + address={Host,Port}, + name=Name, + action=Action, + module=?MODULE}, + Data). + + +%% Log callback - called from the error handler process +format_data(raw,Data) -> + io_lib:format("~n~s~n",[hide_password(Data)]); +format_data(pretty,Data) -> + io_lib:format("~n~s~n",[indent(Data)]); +format_data(html,Data) -> + io_lib:format("~n~s~n",[html_format(Data)]). + +%%%----------------------------------------------------------------- +%%% Hide password elements from XML data +hide_password(Bin) -> + re:replace(Bin,<<"(]*>)[^<]*()">>,<<"\\1*****\\2">>, + [global,{return,binary}]). + +%%%----------------------------------------------------------------- +%%% HTML formatting +html_format(Bin) -> + binary:replace(indent(Bin),<<"<">>,<<"<">>,[global]). + +%%%----------------------------------------------------------------- +%%% Indentation of XML code +indent(Bin) -> + String = normalize(hide_password(Bin)), + IndentedString = + case erase(part_of_line) of + undefined -> + indent1(String,[]); + Part -> + indent1(lists:reverse(Part)++String,erase(indent)) + end, + list_to_binary(IndentedString). + +%% Normalizes the XML document by removing all space and newline +%% between two XML tags. +%% Returns a list, no matter if the input was a list or a binary. +normalize(Str) -> + re:replace(Str,<<">[ \r\n\t]+<">>,<<"><">>,[global,{return,list}]). + + +indent1(" + %% Prolog + {Line,Rest2,Indent2} = indent_line(Rest1,Indent1,[$?,$<]), + Line++indent1(Rest2,Indent2); +indent1(" + %% Stop tag + {Line,Rest2,Indent2} = indent_line1(Rest1,Indent1,[$/,$<]), + "\n"++Line++indent1(Rest2,Indent2); +indent1("<"++Rest1,Indent1) -> + %% Start- or empty tag + put(tag,get_tag(Rest1)), + {Line,Rest2,Indent2} = indent_line(Rest1,Indent1,[$<]), + "\n"++Line++indent1(Rest2,Indent2); +indent1([H|T],Indent) -> + [H|indent1(T,Indent)]; +indent1([],_Indent) -> + []. + +indent_line("?>"++Rest,Indent,Line) -> + %% Prolog + {lists:reverse(Line)++"?>",Rest,Indent}; +indent_line("/> + %% Empty tag, and stop of parent tag -> one step out in indentation + {Indent++lists:reverse(Line)++"/>",""++Rest,Indent,Line) -> + %% Empty tag, then probably next tag -> keep indentation + {Indent++lists:reverse(Line)++"/>",Rest,Indent}; +indent_line("> + LastTag = erase(tag), + case get_tag(Rest) of + LastTag -> + %% Start and stop tag, but no content + indent_line1(Rest,Indent,[$/,$<,$>|Line]); + _ -> + %% Stop tag completed, and then stop tag of parent -> one step out + {Indent++lists:reverse(Line)++">","<"++Rest,Indent,Line) -> + %% Stop tag completed, and new tag comming -> keep indentation + {Indent++lists:reverse(Line)++">","<"++Rest," "++Indent}; +indent_line(" + %% Stop tag starting -> search for end of this tag + indent_line1(Rest,Indent,[$/,$<|Line]); +indent_line([H|T],Indent,Line) -> + indent_line(T,Indent,[H|Line]); +indent_line([],Indent,Line) -> + %% The line is not complete - will be continued later + put(part_of_line,Line), + put(indent,Indent), + {[],[],Indent}. + +indent_line1("> + %% Stop tag completed, and then stop tag of parent -> one step out + {Indent++lists:reverse(Line)++">",""++Rest,Indent,Line) -> + %% Stop tag completed -> keep indentation + {Indent++lists:reverse(Line)++">",Rest,Indent}; +indent_line1([H|T],Indent,Line) -> + indent_line1(T,Indent,[H|Line]); +indent_line1([],Indent,Line) -> + %% The line is not complete - will be continued later + put(part_of_line,Line), + put(indent,Indent), + {[],[],Indent}. + +get_tag("/>"++_) -> + []; +get_tag(">"++_) -> + []; +get_tag([H|T]) -> + [H|get_tag(T)]; +get_tag([]) -> + %% The line is not complete - will be continued later. + []. + + +%%%----------------------------------------------------------------- +%%% SSH stuff +ssh_receive_data() -> + receive + {ssh_cm, _CM, {data, _Ch, _Type, Data}} -> + {ok, Data}; + {ssh_cm, _CM, {Closed, _Ch}} = X when Closed == closed; Closed == eof -> + {error,X}; + {_Ref,timeout} = X -> + {error,X} + end. + +ssh_open(#options{host=Host,timeout=Timeout,port=Port,ssh=SshOpts,name=Name}) -> + case ssh:connect(Host, Port, + [{user_interaction,false}, + {silently_accept_hosts, true}|SshOpts]) of + {ok,CM} -> + case ssh_connection:session_channel(CM, Timeout) of + {ok,Ch} -> + case ssh_connection:subsystem(CM, Ch, "netconf", Timeout) of + success -> + {ok, #connection{reference = {CM,Ch}, + host = Host, + port = Port, + name = Name}}; + failure -> + ssh:close(CM), + {error,{ssh,could_not_execute_netconf_subsystem}} + end; + {error, Reason} -> + ssh:close(CM), + {error,{ssh,could_not_open_channel,Reason}}; + Other -> + %% Bug in ssh?? got {closed,0} here once... + {error,{ssh,unexpected_from_session_channel,Other}} + end; + {error,Reason} -> + {error,{ssh,could_not_connect_to_server,Reason}} + end. + +ssh_send(#connection{reference = {CM,Ch}}, Data) -> + case ssh_connection:send(CM, Ch, Data) of + ok -> ok; + {error,Reason} -> {error,{ssh,failed_to_send_data,Reason}} + end. + +ssh_close(#connection{reference = {CM,_Ch}}) -> + ssh:close(CM). + + +%%---------------------------------------------------------------------- +%% END OF MODULE +%%---------------------------------------------------------------------- diff --git a/lib/common_test/src/ct_netconfc.hrl b/lib/common_test/src/ct_netconfc.hrl new file mode 100644 index 000000000000..295a61a98be4 --- /dev/null +++ b/lib/common_test/src/ct_netconfc.hrl @@ -0,0 +1,58 @@ +%%-------------------------------------------------------------------- +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2012. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +%%---------------------------------------------------------------------- +%% File: ct_netconfc.hrl +%% +%% Description: +%% This file defines constant values and records used by the +%% netconf client ct_netconfc. +%% +%% @author Support +%% @doc Netconf Client Interface. +%% @end +%%---------------------------------------------------------------------- +%%---------------------------------------------------------------------- + + +%% Default port number (RFC 4742/IANA). +-define(DEFAULT_PORT, 830). + +%% Default timeout to wait for netconf server to reply to a request +-define(DEFAULT_TIMEOUT, infinity). %% msec + +%% Namespaces +-define(NETCONF_NAMESPACE_ATTR,[{xmlns,?NETCONF_NAMESPACE}]). +-define(ACTION_NAMESPACE_ATTR,[{xmlns,?ACTION_NAMESPACE}]). +-define(NETCONF_NOTIF_NAMESPACE_ATTR,[{xmlns,?NETCONF_NOTIF_NAMESPACE}]). +-define(NETMOD_NOTIF_NAMESPACE_ATTR,[{xmlns,?NETMOD_NOTIF_NAMESPACE}]). + +-define(NETCONF_NAMESPACE,"urn:ietf:params:xml:ns:netconf:base:1.0"). +-define(ACTION_NAMESPACE,"urn:com:ericsson:ecim:1.0"). +-define(NETCONF_NOTIF_NAMESPACE, + "urn:ietf:params:xml:ns:netconf:notification:1.0"). +-define(NETMOD_NOTIF_NAMESPACE,"urn:ietf:params:xml:ns:netmod:notification"). + +%% Capabilities +-define(NETCONF_BASE_CAP,"urn:ietf:params:netconf:base:"). +-define(NETCONF_BASE_CAP_VSN,"1.0"). + +%% Misc +-define(END_TAG,<<"]]>]]>">>). + +-define(FORMAT(_F, _A), lists:flatten(io_lib:format(_F, _A))). diff --git a/lib/common_test/src/ct_util.hrl b/lib/common_test/src/ct_util.hrl index 6b016e95df70..474d36574edf 100644 --- a/lib/common_test/src/ct_util.hrl +++ b/lib/common_test/src/ct_util.hrl @@ -64,3 +64,6 @@ -define(ct_config_txt, ct_config_plain). -define(ct_profile_file, ".common_test"). + +%% Logging information for error handler +-record(conn_log, {client, name, address, action, module}). diff --git a/lib/common_test/src/cth_conn_log.erl b/lib/common_test/src/cth_conn_log.erl new file mode 100644 index 000000000000..3af89db3a528 --- /dev/null +++ b/lib/common_test/src/cth_conn_log.erl @@ -0,0 +1,124 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2012. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +%%---------------------------------------------------------------------- +%% CT hook for logging of connections. +%% +%% HookOptions can be hardcoded in the test suite: +%% +%% suite() -> +%% [{ct_hooks, [{cth_conn_log, +%% [{ct_netconfc:conn_mod(),ct_netconfc:hook_options()}]}]}]. +%% +%% or specified in a configuration file: +%% +%% {ct_conn_log,[{ct_netconfc:conn_mod(),ct_netconfc:hook_options()}]}. +%% +%% The conn_mod() is the common test module implementing the protocol, +%% e.g. ct_netconfc, ct_telnet, etc. This module must log by calling +%% +%% error_logger:info_report(ConnLogInfo,Data). +%% ConnLogInfo = #conn_log{} | {ct_connection,Action,ConnName} +%% Action = open | close | send | recv | term() +%% ConnName = atom() - The 'KeyOrName' argument used when opening the connection +%% +%% ct_conn_log_h will print to html log or separate file (depending on +%% log_type() option). conn_mod() must implement and export +%% +%% format_data(log_type(), Data). +%% +%% If logging to separate file, ct_conn_log_h will also log error +%% reports which are witten like this: +%% +%% error_logger:error_report([{ct_connection,ConnName} | Report]). +%% +%%---------------------------------------------------------------------- +-module(cth_conn_log). + +-include_lib("common_test/include/ct.hrl"). + +-export([init/2, + pre_init_per_testcase/3, + post_end_per_testcase/4]). + +-spec init(Id, HookOpts) -> Result when + Id :: term(), + HookOpts :: ct:hook_options(), + Result :: {ok,[{ct_netconfc:conn_mod(), + {ct_netconfc:log_type(),[ct_netconfc:key_or_name()]}}]}. +init(_Id, HookOpts) -> + ConfOpts = ct:get_config(ct_conn_log,[]), + {ok,merge_log_info(ConfOpts,HookOpts)}. + +merge_log_info([{Mod,ConfOpts}|ConfList],HookList) -> + {Opts,HookList1} = + case lists:keytake(Mod,1,HookList) of + false -> + {ConfOpts,HookList}; + {value,{_,HookOpts},HL1} -> + {ConfOpts ++ HookOpts, HL1} % ConfOpts overwrites HookOpts! + end, + [{Mod,get_log_opts(Opts)} | merge_log_info(ConfList,HookList1)]; +merge_log_info([],HookList) -> + [{Mod,get_log_opts(Opts)} || {Mod,Opts} <- HookList]. + +get_log_opts(Opts) -> + LogType = proplists:get_value(log_type,Opts,html), + Hosts = proplists:get_value(hosts,Opts,[]), + {LogType,Hosts}. + + +pre_init_per_testcase(TestCase,Config,CthState) -> + Logs = + lists:map( + fun({ConnMod,{LogType,Hosts}}) -> + case LogType of + LogType when LogType==raw; LogType==pretty -> + Dir = ?config(priv_dir,Config), + TCStr = atom_to_list(TestCase), + ConnModStr = atom_to_list(ConnMod), + DefLogName = TCStr ++ "-" ++ ConnModStr ++ ".txt", + DefLog = filename:join(Dir,DefLogName), + Ls = [{Host, + filename:join(Dir,TCStr ++ "-"++ + atom_to_list(Host) ++ "-" ++ + ConnModStr ++ + ".txt")} + || Host <- Hosts] + ++[{default,DefLog}], + Str = + "" + "" ++ ConnModStr ++ " logs:\n" ++ + [io_lib:format( + "", + [S,L,filename:basename(L)]) + || {S,L} <- Ls] ++ + "
~p~s
", + io:format(Str,[]), + {ConnMod,{LogType,Ls}}; + _ -> + {ConnMod,{LogType,[]}} + end + end, + CthState), + error_logger:add_report_handler(ct_conn_log_h,{group_leader(),Logs}), + {Config,CthState}. + +post_end_per_testcase(_TestCase,_Config,Return,CthState) -> + error_logger:delete_report_handler(ct_conn_log_h), + {Return,CthState}. diff --git a/lib/common_test/test/Makefile b/lib/common_test/test/Makefile index 560a0b0d5ab6..c970593053c2 100644 --- a/lib/common_test/test/Makefile +++ b/lib/common_test/test/Makefile @@ -28,6 +28,7 @@ MODULES= \ ct_test_support \ ct_test_support_eh \ ct_userconfig_callback \ + ct_test_netconf_server \ ct_smoke_test_SUITE \ ct_priv_dir_SUITE \ ct_event_handler_SUITE \ @@ -45,7 +46,8 @@ MODULES= \ ct_config_SUITE \ ct_master_SUITE \ ct_misc_1_SUITE \ - ct_hooks_SUITE + ct_hooks_SUITE \ + ct_netconfc_SUITE ERL_FILES= $(MODULES:%=%.erl) @@ -100,6 +102,7 @@ release_tests_spec: $(INSTALL_DIR) "$(RELSYSDIR)" $(INSTALL_DATA) $(ERL_FILES) $(COVERFILE) "$(RELSYSDIR)" $(INSTALL_DATA) common_test.spec "$(RELSYSDIR)" + $(INSTALL_DATA) ct_netconfc.cfg "$(RELSYSDIR)" chmod -R u+w "$(RELSYSDIR)" @tar cf - *_SUITE_data | (cd "$(RELSYSDIR)"; tar xf -) diff --git a/lib/common_test/test/common_test.spec b/lib/common_test/test/common_test.spec index 8755b08117da..04f3c6444289 100644 --- a/lib/common_test/test/common_test.spec +++ b/lib/common_test/test/common_test.spec @@ -1 +1,2 @@ -{suites,"../common_test_test",all}. \ No newline at end of file +{suites,"../common_test_test",all}. +{config,"../common_test_test/ct_netconfc.cfg"}. \ No newline at end of file diff --git a/lib/common_test/test/ct_netconfc.cfg b/lib/common_test/test/ct_netconfc.cfg new file mode 100644 index 000000000000..646657162337 --- /dev/null +++ b/lib/common_test/test/ct_netconfc.cfg @@ -0,0 +1,6 @@ +%% -*- erlang -*- +{netconf1,[{ssh,"localhost"}, + {port,2060}, + {user,"xxx"}, + {password,"xxx"}]}. +{ct_conn_log,[{ct_netconfc,[{log_type,pretty}]}]}. %overrides args to cth_conn_log diff --git a/lib/common_test/test/ct_netconfc_SUITE.erl b/lib/common_test/test/ct_netconfc_SUITE.erl new file mode 100644 index 000000000000..8880d8b61806 --- /dev/null +++ b/lib/common_test/test/ct_netconfc_SUITE.erl @@ -0,0 +1,1144 @@ +%%-------------------------------------------------------------------- +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2012. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +%%---------------------------------------------------------------------- +%% File: ct_netconfc_SUITE.erl +%% +%% Description: +%% This file contains the test cases for the ct_netconfc API. +%% +%% @author Support +%% @doc Netconf Client Interface. +%% @end +%%---------------------------------------------------------------------- +%%---------------------------------------------------------------------- +-module(ct_netconfc_SUITE). +-include_lib("common_test/include/ct.hrl"). +-include_lib("common_test/src/ct_netconfc.hrl"). +-include_lib("public_key/include/public_key.hrl"). + +-compile(export_all). + +%% Default timetrap timeout (set in init_per_testcase). +-define(default_timeout, ?t:minutes(1)). + +-define(NS,ct_test_netconf_server). +-define(LOCALHOST, "127.0.0.1"). +-define(SSH_PORT, 2060). + +-define(DEFAULT_SSH_OPTS,[{ssh,?LOCALHOST}, + {port,?SSH_PORT}, + {user,"xxx"}, + {password,"xxx"}]). +-define(DEFAULT_SSH_OPTS(Dir), ?DEFAULT_SSH_OPTS++[{user_dir,Dir}]). + +-define(ok,ok). + +suite() -> + [{ct_hooks, [{cth_conn_log, + [{ct_netconfc,[{log_type,html}, %will be overwritten by config + {hosts,[my_named_connection,netconf1]}] + }] + }] + }]. + +all() -> + case os:find_executable("ssh") of + false -> + {skip, "SSH not installed on host"}; + _ -> + [hello, + hello_from_server_first, + hello_named, + hello_configured, + hello_configured_extraopts, + hello_required, + hello_global_pwd, + hello_no_session_id, + hello_incomp_base_vsn, + hello_no_base_cap, + hello_no_caps, + no_server_hello, + no_client_hello, + get_session_id, + get_capabilities, + faulty_user, + faulty_passwd, + faulty_port, + no_host, + no_port, + invalid_opt, + get, + get_xpath, + get_config, + get_config_xpath, + edit_config, + copy_config, + delete_config, + lock, + unlock, + kill_session, + get_required, + get_config_required, + edit_config_required, + get_no_such_client, + action, + send_any_rpc, + send_any, + hide_password, + not_proper_xml, + prefixed_namespace, + receive_chunked_data, + timeout_receive_chunked_data, + close_while_waiting_for_chunked_data, + get_event_streams, + create_subscription, + receive_event] + end. + + +groups() -> + []. + +init_per_group(_GroupName, Config) -> + Config. + +end_per_group(_GroupName, Config) -> + Config. + +init_per_testcase(_Case, Config) -> + ets:delete_all_objects(ns_tab), + Dog = test_server:timetrap(?default_timeout), + [{watchdog, Dog}|Config]. + +end_per_testcase(_Case, Config) -> + Dog=?config(watchdog, Config), + test_server:timetrap_cancel(Dog), + ok. + +init_per_suite(Config) -> + case catch {crypto:start(), ssh:start()} of + {ok, ok} -> + {ok, _} = get_id_keys(Config), + make_dsa_files(Config), + Server = ?NS:start(?config(data_dir,Config)), + [{server,Server}|Config]; + _ -> + {skip, "Crypto and/or SSH could not be started!"} + end. + +end_per_suite(Config) -> + PrivDir = ?config(priv_dir, Config), + ?NS:stop(?config(server,Config)), + ssh:stop(), + crypto:stop(), + remove_id_keys(PrivDir), + Config. + +hello(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +hello_from_server_first(Config) -> + DataDir = ?config(data_dir,Config), + ?NS:hello(1), + {ok,Client} = ct_netconfc:only_open(?DEFAULT_SSH_OPTS(DataDir)), + ct:sleep(500), + ?NS:expect(hello), + ?ok = ct_netconfc:hello(Client), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +hello_named(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(any_name,DataDir), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +hello_configured() -> + [{require, netconf1}]. +hello_configured(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_configured_success(netconf1,DataDir), + ?NS:expect_do_reply('close-session',close,ok), + {error, {no_such_name,netconf1}} = ct_netconfc:close_session(netconf1), + ?ok = ct_netconfc:close_session(Client), + ok. + +hello_configured_extraopts() -> + [{require, netconf1}]. +hello_configured_extraopts(Config) -> + DataDir = ?config(data_dir,Config), + %% Test that the cofiguration overwrites the ExtraOpts parameter + %% to ct_netconfc:open/2. + {ok,Client} = open_configured_success(netconf1,DataDir,[{password,"faulty"}]), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +hello_required() -> + [{require, my_named_connection, netconf1}]. +hello_required(Config) -> + DataDir = ?config(data_dir,Config), + {ok,_Client} = open_configured_success(my_named_connection,DataDir), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(my_named_connection), + ok. + +hello_global_pwd(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir,[{user,"any-user"}, + {password,"global-xxx"}]), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +hello_no_session_id(Config) -> + DataDir = ?config(data_dir,Config), + ?NS:hello(no_session_id), + ?NS:expect(hello), + {error,{incorrect_hello,no_session_id_found}} = open(DataDir), + ok. + +hello_incomp_base_vsn(Config) -> + DataDir = ?config(data_dir,Config), + ?NS:hello(1,{base,"1.1"}), + ?NS:expect(hello), + {error,{incompatible_base_capability_vsn,"1.1"}} = open(DataDir), + ok. + +hello_no_base_cap(Config) -> + DataDir = ?config(data_dir,Config), + ?NS:hello(1,no_base), + ?NS:expect(hello), + {error,{incorrect_hello,no_base_capability_found}} = open(DataDir), + ok. + +hello_no_caps(Config) -> + DataDir = ?config(data_dir,Config), + ?NS:hello(1,no_caps), + ?NS:expect(hello), + {error,{incorrect_hello,capabilities_not_found}} = open(DataDir), + ok. + +no_server_hello(Config) -> + DataDir = ?config(data_dir,Config), + ?NS:expect(hello), + {error,{hello_session_failed,timeout}} = open(DataDir,[{timeout,2000}]), + ok. + +no_client_hello(Config) -> + DataDir = ?config(data_dir,Config), + ?NS:hello(1), + {ok,Client} = ct_netconfc:only_open(?DEFAULT_SSH_OPTS(DataDir)), + + %% Allow server hello to arrive + ct:sleep(500), + + %% Tell server to receive a get request and then die without + %% replying since no hello has been received. (is this correct + %% behavoiur??) + ?NS:expect_do(get,close), + {error,closed} = ct_netconfc:get(Client,whatever), + ok. + +get_session_id(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + 1 = ct_netconfc:get_session_id(Client), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +get_capabilities(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + Caps = ct_netconfc:get_capabilities(Client), + BaseCap = ?NETCONF_BASE_CAP ++ ?NETCONF_BASE_CAP_VSN, + [BaseCap,"urn:ietf:params:netconf:capability:writable-running:1.0" |_] = Caps, + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +faulty_user(Config) -> + DataDir = ?config(data_dir,Config), + {error,{ssh,could_not_connect_to_server, + "Unable to connect using the available authentication methods"}} = + open(DataDir,[{user,"yyy"}]), + ok. + +faulty_passwd(Config) -> + DataDir = ?config(data_dir,Config), + {error,{ssh,could_not_connect_to_server, + "Unable to connect using the available authentication methods"}} = + open(DataDir,[{password,"yyy"}]), + ok. + +faulty_port(Config) -> + DataDir = ?config(data_dir,Config), + {error,{ssh,could_not_connect_to_server,econnrefused}} = + open(DataDir,[{port,2062}]), + ok. + +no_host(Config) -> + DataDir = ?config(data_dir,Config), + Opts = lists:keydelete(ssh,1,?DEFAULT_SSH_OPTS(DataDir)), + {error,no_host_address} = ct_netconfc:open(Opts), + ok. + +no_port(Config) -> + DataDir = ?config(data_dir,Config), + Opts = lists:keydelete(port,1,?DEFAULT_SSH_OPTS(DataDir)), + {error,no_port} = ct_netconfc:open(Opts), + ok. + +invalid_opt(Config) -> + DataDir = ?config(data_dir,Config), + Opts1 = ?DEFAULT_SSH_OPTS(DataDir) ++ [{timeout,invalidvalue}], + {error,{invalid_option,{timeout,invalidvalue}}} = ct_netconfc:open(Opts1), + Opts2 = ?DEFAULT_SSH_OPTS(DataDir) ++ [{some_other_opt,true}], + {error,{invalid_option,{some_other_opt,true}}} = ct_netconfc:open(Opts2), + ok. + +get(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + ?NS:expect_reply('get',{data,Data}), + {ok,Data} = ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +get_xpath(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + ?NS:expect_reply({'get',xpath},{data,Data}), + {ok,Data} = ct_netconfc:get(Client,{xpath,"/server"}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +get_config(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + ?NS:expect_reply('get-config',{data,Data}), + {ok,Data} = ct_netconfc:get_config(Client,running, + {server,[{xmlns,"myns"}],[]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +get_config_xpath(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + ?NS:expect_reply({'get-config',xpath},{data,Data}), + {ok,Data} = ct_netconfc:get_config(Client,running,{xpath,"/server"}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +edit_config(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + ?NS:expect_reply('edit-config',ok), + ?ok = ct_netconfc:edit_config(Client,running, + {server,[{xmlns,"myns"}], + [{name,["myserver"]}]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +copy_config(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + ?NS:expect_reply('copy-config',ok), + ?ok = ct_netconfc:copy_config(Client,startup,running), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +delete_config(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + ?NS:expect_reply('delete-config',ok), + ?ok = ct_netconfc:delete_config(Client,startup), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +lock(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + ?NS:expect_reply('lock',ok), + ?ok = ct_netconfc:lock(Client,running), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +unlock(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + ?NS:expect_reply('unlock',ok), + ?ok = ct_netconfc:unlock(Client,running), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +kill_session(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + ?NS:hello(2), + ?NS:expect(hello), + {ok,_OtherClient} = open(DataDir), + + ?NS:expect_do_reply('kill-session',{kill,2},ok), + ?ok = ct_netconfc:kill_session(Client,2), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + + ok. + +%% get_required, get_config_required and edit_config_required shall +%% test that the same named connection can be used in multiple test +%% cases. Earlier, there was a bug in ct_gen_conn related to this: +%% Connections were not unregistered on close-connection, so +%% ct_netconfc would not find the correct pid for a named connection +%% the second time the name was used. +get_required() -> + [{require, my_named_connection, netconf1}]. +get_required(Config) -> + DataDir = ?config(data_dir,Config), + {ok,_Client} = open_configured_success(my_named_connection,DataDir), + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + ?NS:expect_reply('get',{data,Data}), + {ok,Data} = ct_netconfc:get(my_named_connection,{server,[{xmlns,"myns"}],[]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(my_named_connection), + ok. + +get_config_required() -> + [{require, my_named_connection, netconf1}]. +get_config_required(Config) -> + DataDir = ?config(data_dir,Config), + {ok,_Client} = open_configured_success(my_named_connection,DataDir), + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + ?NS:expect_reply('get-config',{data,Data}), + {ok,Data} = ct_netconfc:get_config(my_named_connection,running, + {server,[{xmlns,"myns"}],[]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(my_named_connection), + ok. + +edit_config_required() -> + [{require, my_named_connection, netconf1}]. +edit_config_required(Config) -> + DataDir = ?config(data_dir,Config), + {ok,_Client} = open_configured_success(my_named_connection,DataDir), + ?NS:expect_reply('edit-config',ok), + ?ok = ct_netconfc:edit_config(my_named_connection,running, + {server,[{xmlns,"myns"}], + [{name,["myserver"]}]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(my_named_connection), + ok. + +get_no_such_client(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + case ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]}) of + {error,no_such_client} -> + ok; + {error,closed} -> + %% Means that the Client process was not terminated before the call. + %% Give it one more go. + {error,no_such_client} = + ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]}) + end, + ok. + +action(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + Data = [{myactionreturn,[{xmlns,"myns"}],["value"]}], + ?NS:expect_reply(action,{data,Data}), + {ok,Data} = ct_netconfc:action(Client,{myaction,[{xmlns,"myns"}],[]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +send_any_rpc(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + GetConf = {'get-config', + [{source,["running"]}, + {filter,[{type,"subtree"}], + [{server,[{xmlns,"myns"}],[]}]}]}, + ?NS:expect_reply('get-config',{data,Data}), + [{data,?NETCONF_NAMESPACE_ATTR,Data}] = ct_netconfc:send_rpc(Client,GetConf), + + EditConf = {'edit-config', + [{target,["running"]}, + {config,[{server,[{xmlns,"myns"}], + [{name,["myserver"]}]}]}]}, + ?NS:expect_reply('edit-config',ok), + [{ok,?NETCONF_NAMESPACE_ATTR,[]}] = ct_netconfc:send_rpc(Client,EditConf), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +send_any(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + %% Correct get-config rpc + Data = [{server,[{xmlns,"myns"}],[{name,[],["myserver"]}]}], + RpcAttr1 = ?NETCONF_NAMESPACE_ATTR ++ [{'message-id',"1"}], + RpcGetConf = {rpc,RpcAttr1, + [{'get-config', + [{source,["running"]}, + {filter,[{type,"subtree"}], + [{server,[{xmlns,"myns"}],[]}]}]}]}, + ?NS:expect_reply('get-config',{data,Data}), + {'rpc-reply',RpcAttr1,[{data,_,Data}]} = ct_netconfc:send(Client,RpcGetConf), + + %% Correct edit-config rpc + RpcAttr2 = ?NETCONF_NAMESPACE_ATTR ++ [{'message-id',"2"}], + RpcEditConf = {rpc,RpcAttr2, + [{'edit-config', + [{target,["running"]}, + {config,[{server,[{xmlns,"myns"}], + [{name,["myserver"]}]}]}]}]}, + ?NS:expect_reply('edit-config',ok), + {'rpc-reply',RpcAttr2,[{ok,_,[]}]} = ct_netconfc:send(Client,RpcEditConf), + + %% Send any data + ?NS:expect_reply(any,{ok,[],[]}), + {ok,_,[]} = ct_netconfc:send(Client,{any,[],[]}), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +hide_password(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + Password = "my_very_secret_password", + Data = [{passwords,[{xmlns,"myns"}], + [{password,[{xmlns,"pwdns"}],[Password]}, + {password,[],[Password]}]}], + ?NS:expect_reply('get',{data,Data}), + ct:capture_start(), % in case of html logging + {ok,Data} = ct_netconfc:get(Client,{passwords,[{xmlns,"myns"}],[]}), + ct:capture_stop(), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + + Log = filename:join(?config(priv_dir,Config),"hide_password-netconf.txt"), + + Text = + case file:read_file(Log) of + {ok,Bin} -> + Bin; + _NoLog -> + %% Assume html logging + list_to_binary(ct:capture_get()) + end, + + nomatch = binary:match(Text,list_to_binary(Password)), + + ok. + +not_proper_xml(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + NS = list_to_binary(?NETCONF_NAMESPACE), + NotProper = <<"">>, + ?NS:expect_reply('get',NotProper), + {error,{failed_to_parse_received_data,_}} = + ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]}), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +prefixed_namespace(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + NS = list_to_binary(?NETCONF_NAMESPACE), + + %% Test that data element can be properly decoded and that + %% prefixed namespace attributes (exepct the netconf namespace) + %% are forwarded to the content of the data element - i.e. that + %% the xmlns:my is forwarded from the rpc-reply element to the + %% server element below. + Data = <<"", + "myserver" + "">>, + ?NS:expect_reply('get',Data), + {ok,[{'my:server',[{'xmlns:my',"myns"}], + [{'my:name',[{'my:lang',"en"}],["myserver"]}]}]} = + ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]}), + + Ok = <<"">>, + ?NS:expect_reply('edit-config',Ok), + ?ok = ct_netconfc:edit_config(Client,running, + {server,[{xmlns,"myns"}], + [{name,["myserver"]}]}), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +%% Test that the client can parse data which is received in chunks, +%% i.e. when the complete rpc-reply is not contained in one single ssh +%% data message. +receive_chunked_data(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + %% Construct the data to return from netconf server + Data = [{servers,[{xmlns,"myns"}], + [{server,[],[{name,[],["server0"]}]}, + {server,[],[{name,[],["server1"]}]}, + {server,[],[{name,[],["server2"]}]}, + {server,[],[{name,[],["server3"]}]}, + {server,[],[{name,[],["server4"]}]}, + {server,[],[{name,[],["server5"]}]}, + {server,[],[{name,[],["server6"]}]}, + {server,[],[{name,[],["server7"]}]}, + {server,[],[{name,[],["server8"]}]}, + {server,[],[{name,[],["server9"]}]}] + }], + Rpc = {'rpc-reply',?NETCONF_NAMESPACE_ATTR ++ [{'message-id',"1"}], + [{data,Data}]}, + Xml = list_to_binary(xmerl:export_simple_element(Rpc,xmerl_xml)), + Netconf = + <<"\n", + Xml/binary,"\n",?END_TAG/binary>>, + + %% Split the data in some chunks + PartLength = size(Netconf) div 3, + <> = Netconf, + + %% Spawn a process which will wait a bit for the client to send + %% the request (below), then order the server to the chunks of the + %% rpc-reply one by one. + spawn(fun() -> timer:sleep(500),?NS:hupp(send,Part1), + timer:sleep(100),?NS:hupp(send,Part2), + timer:sleep(100),?NS:hupp(send,Part3), + timer:sleep(100),?NS:hupp(send,Part4) + end), + + %% Order server to expect a get - then the process above will make + %% sure the rpc-reply is sent. + ?NS:expect('get'), + {ok,Data} = ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]}), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +%% Same as receive_chunked_data, but timeout waiting for last part. +timeout_receive_chunked_data(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + %% Construct the data to return from netconf server + Data = [{servers,[{xmlns,"myns"}], + [{server,[],[{name,[],["server0"]}]}, + {server,[],[{name,[],["server1"]}]}, + {server,[],[{name,[],["server2"]}]}, + {server,[],[{name,[],["server3"]}]}, + {server,[],[{name,[],["server4"]}]}, + {server,[],[{name,[],["server5"]}]}, + {server,[],[{name,[],["server6"]}]}, + {server,[],[{name,[],["server7"]}]}, + {server,[],[{name,[],["server8"]}]}, + {server,[],[{name,[],["server9"]}]}] + }], + Rpc = {'rpc-reply',?NETCONF_NAMESPACE_ATTR ++ [{'message-id',"1"}], + [{data,Data}]}, + Xml = list_to_binary(xmerl:export_simple_element(Rpc,xmerl_xml)), + Netconf = + <<"\n", + Xml/binary,"\n",?END_TAG/binary>>, + + %% Split the data in some chunks + PartLength = size(Netconf) div 3, + <> = Netconf, + + %% Spawn a process which will wait a bit for the client to send + %% the request (below), then order the server to the chunks of the + %% rpc-reply one by one. + spawn(fun() -> timer:sleep(500),?NS:hupp(send,Part1), + timer:sleep(100),?NS:hupp(send,Part2) + end), + + %% Order server to expect a get - then the process above will make + %% sure the rpc-reply is sent - but only a part of it - then timeout. + ?NS:expect('get'), + {error,timeout} = ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]},2000), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +%% Same as receive_chunked_data, but timeout waiting for last part. +close_while_waiting_for_chunked_data(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + + %% Construct the data to return from netconf server + Data = [{servers,[{xmlns,"myns"}], + [{server,[],[{name,[],["server0"]}]}, + {server,[],[{name,[],["server1"]}]}, + {server,[],[{name,[],["server2"]}]}, + {server,[],[{name,[],["server3"]}]}, + {server,[],[{name,[],["server4"]}]}, + {server,[],[{name,[],["server5"]}]}, + {server,[],[{name,[],["server6"]}]}, + {server,[],[{name,[],["server7"]}]}, + {server,[],[{name,[],["server8"]}]}, + {server,[],[{name,[],["server9"]}]}] + }], + Rpc = {'rpc-reply',?NETCONF_NAMESPACE_ATTR ++ [{'message-id',"1"}], + [{data,Data}]}, + Xml = list_to_binary(xmerl:export_simple_element(Rpc,xmerl_xml)), + Netconf = + <<"\n", + Xml/binary,"\n",?END_TAG/binary>>, + + %% Split the data in some chunks + PartLength = size(Netconf) div 3, + <> = Netconf, + + %% Spawn a process which will wait a bit for the client to send + %% the request (below), then order the server to the chunks of the + %% rpc-reply one by one. + spawn(fun() -> timer:sleep(500),?NS:hupp(send,Part1), + timer:sleep(100),?NS:hupp(send,Part2), + timer:sleep(100),?NS:hupp(kill) + end), + + %% Order server to expect a get - then the process above will make + %% sure the rpc-reply is sent - but only a part of it - then close. + ?NS:expect('get'), + {error,closed} = ct_netconfc:get(Client,{server,[{xmlns,"myns"}],[]},2000), + ok. + +get_event_streams(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + StreamNames = ["NETCONF","stream1","stream2"], + Streams = [{N,[{description,"descr of " ++ N}]} || N <- StreamNames], + StreamsXml = [{stream,[{name,[N]}|[{Tag,[Value]} || {Tag,Value} <- Data]]} + || {N,Data} <- Streams], + ReplyData = [{netconf,?NETMOD_NOTIF_NAMESPACE_ATTR,[{streams,StreamsXml}]}], + ?NS:expect_reply('get',{data,ReplyData}), + {ok,Streams} = ct_netconfc:get_event_streams(Client,StreamNames), + + ?NS:expect_reply('get',{data,ReplyData}), + {ok,Streams} = ct_netconfc:get_event_streams(Client,StreamNames,5000), + + ?NS:expect('get'), + {error,timeout} = ct_netconfc:get_event_streams(Client,100), + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + ok. + +create_subscription(Config) -> + DataDir = ?config(data_dir,Config), + + %% All defaults + {ok,Client1} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream]},ok), + ?ok = ct_netconfc:create_subscription(Client1), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client1), + + %% All defaults with timeout + {ok,Client1a} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream]},ok), + ?ok = ct_netconfc:create_subscription(Client1a,5000), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client1a), + + %% All defaults timing out + {ok,Client1b} = open_success(DataDir), + ?NS:expect({'create-subscription',[stream]}), + {error,timeout} = ct_netconfc:create_subscription(Client1b,100), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client1b), + + %% Stream + {ok,Client2} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream]},ok), + Stream = "some_stream", + ?ok = ct_netconfc:create_subscription(Client2,Stream), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client2), + + %% Filter + {ok,Client3} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,filter]},ok), + Filter = {notification,?NETMOD_NOTIF_NAMESPACE_ATTR, + [eventTime]}, + ?ok = ct_netconfc:create_subscription(Client3,Filter), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client3), + + %% Filter with timeout + {ok,Client3a} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,filter]},ok), + ?ok = ct_netconfc:create_subscription(Client3a,Filter,5000), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client3a), + + %% Filter timing out + {ok,Client3b} = open_success(DataDir), + ?NS:expect({'create-subscription',[stream,filter]}), + {error,timeout}=ct_netconfc:create_subscription(Client3b,Filter,100), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client3b), + + %% Stream and filter + {ok,Client4} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,filter]},ok), + ?ok = ct_netconfc:create_subscription(Client4,Stream,Filter), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client4), + + %% Start/stop time + {ok,Client5} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,startTime,stopTime]},ok), + StartTime = xs_datetime({D,{H,M,S}}= calendar:local_time()), + StopTime = xs_datetime({D,{H+2,M,S}}), + ?ok = ct_netconfc:create_subscription(Client5,StartTime,StopTime), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client5), + + %% Start/stop time with timeout + {ok,Client5a} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,startTime,stopTime]},ok), + ?ok = ct_netconfc:create_subscription(Client5a,StartTime,StopTime,5000), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client5a), + + %% Start/stop time timing out + {ok,Client5b} = open_success(DataDir), + ?NS:expect({'create-subscription',[stream,startTime,stopTime]}), + {error,timeout} = + ct_netconfc:create_subscription(Client5b,StartTime,StopTime,100), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client5b), + + %% Stream and start/stop time + {ok,Client6} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,startTime,stopTime]},ok), + ?ok = ct_netconfc:create_subscription(Client6,Stream,StartTime,StopTime), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client6), + + %% Filter and start/stop time + {ok,Client7} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,filter,startTime,stopTime]}, + ok), + ?ok = ct_netconfc:create_subscription(Client7,Filter, + StartTime,StopTime), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client7), + + %% Stream, filter and start/stop time + {ok,Client8} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream,filter,startTime,stopTime]}, + ok), + ?ok = ct_netconfc:create_subscription(Client8,Stream,Filter, + StartTime,StopTime), + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client8), + + ok. + +receive_event(Config) -> + DataDir = ?config(data_dir,Config), + {ok,Client} = open_success(DataDir), + ?NS:expect_reply({'create-subscription',[stream]},ok), + ?ok = ct_netconfc:create_subscription(Client), + + ?NS:hupp(send_event), + + receive + %% Matching ?NS:make_msg(event) + {notification,?NETCONF_NOTIF_NAMESPACE_ATTR, + [{eventTime,[],[_Time]}, + {event,[{xmlns,"http://my.namespaces.com/event"}], + [{severity,_,_}, + {description,_,_}]}]} -> + ok; + Other -> + ct:fail({got_unexpected_while_waiting_for_event, Other}) + after 3000 -> + ct:fail(timeout_waiting_for_event) + end, + + ?NS:expect_do_reply('close-session',close,ok), + ?ok = ct_netconfc:close_session(Client), + + ok. + +%%%----------------------------------------------------------------- + +break(_Config) -> + test_server:break("break test case"). + +br() -> + test_server:break(""). + +%%%----------------------------------------------------------------- +%% Open a netconf session which is not specified in a config file +open_success(Dir) -> + open_success(Dir,[]). + +%% Open a netconf session which is not specified in a config file, and +%% give som extra options in addition to the test defaults. +open_success(Dir,ExtraOpts) when is_list(Dir), is_list(ExtraOpts) -> + ?NS:hello(1), % tell server to send hello with session id 1 + ?NS:expect(hello), % tell server to expect a hello message from client + open(Dir,ExtraOpts); + +%% Open a named netconf session which is not specified in a config file +open_success(KeyOrName,Dir) when is_atom(KeyOrName), is_list(Dir) -> + ?NS:hello(1), + ?NS:expect(hello), + ct_netconfc:open(KeyOrName,?DEFAULT_SSH_OPTS(Dir)). + +open(Dir) -> + open(Dir,[]). +open(Dir,ExtraOpts) -> + Opts = lists:ukeymerge(1,lists:keysort(1,ExtraOpts), + lists:keysort(1,?DEFAULT_SSH_OPTS(Dir))), + ct_netconfc:open(Opts). + +%%%----------------------------------------------------------------- +%%% Open a netconf session which is specified in a config file +%%% KeyOrName is the config key (server_id()) or name given in a +%%% require statement (target_name()). +open_configured_success(KeyOrName,Dir) when is_atom(KeyOrName) -> + open_configured_success(KeyOrName,Dir,[]). +open_configured_success(KeyOrName,Dir,ExtraOpts) when is_atom(KeyOrName) -> + ?NS:hello(1), + ?NS:expect(hello), + ct_netconfc:open(KeyOrName,[{user_dir,Dir}|ExtraOpts]). + +%%%----------------------------------------------------------------- +%%% Convert erlang datetime to the simplest variant of XML dateTime +xs_datetime({{Y,M,D},{H,Mi,S}}) -> + lists:flatten( + io_lib:format("~p-~s-~sT~s:~s:~s",[Y,pad(M),pad(D),pad(H),pad(Mi),pad(S)])). + +pad(I) when I<10 -> + "0"++integer_to_list(I); +pad(I) -> + integer_to_list(I). + + +%%%----------------------------------------------------------------- +%%% BEGIN SSH key management +%% copy private keys to given dir from ~/.ssh +get_id_keys(Config) -> + DstDir = ?config(priv_dir, Config), + SrcDir = filename:join(os:getenv("HOME"), ".ssh"), + RsaOk = copyfile(SrcDir, DstDir, "id_rsa"), + DsaOk = copyfile(SrcDir, DstDir, "id_dsa"), + case {RsaOk, DsaOk} of + {{ok, _}, {ok, _}} -> {ok, both}; + {{ok, _}, _} -> {ok, rsa}; + {_, {ok, _}} -> {ok, dsa}; + {Error, _} -> Error + end. + +%% Remove later on. Use make_dsa_files instead. +remove_id_keys(Config) -> + Dir = ?config(priv_dir, Config), + file:delete(filename:join(Dir, "id_rsa")), + file:delete(filename:join(Dir, "id_dsa")). + + +make_dsa_files(Config) -> + make_dsa_files(Config, rfc4716_public_key). +make_dsa_files(Config, Type) -> + {DSA, EncodedKey} = gen_dsa(128, 20), + PKey = DSA#'DSAPrivateKey'.y, + P = DSA#'DSAPrivateKey'.p, + Q = DSA#'DSAPrivateKey'.q, + G = DSA#'DSAPrivateKey'.g, + Dss = #'Dss-Parms'{p=P, q=Q, g=G}, + {ok, Hostname} = inet:gethostname(), + {ok, {A, B, C, D}} = inet:getaddr(Hostname, inet), + IP = lists:concat([A, ".", B, ".", C, ".", D]), + Attributes = [], % Could be [{comment,"user@" ++ Hostname}], + HostNames = [{hostnames,[IP, IP]}], + PublicKey = [{{PKey, Dss}, Attributes}], + KnownHosts = [{{PKey, Dss}, HostNames}], + + KnownHostsEnc = public_key:ssh_encode(KnownHosts, known_hosts), + KnownHosts = public_key:ssh_decode(KnownHostsEnc, known_hosts), + + PublicKeyEnc = public_key:ssh_encode(PublicKey, Type), + + SystemTmpDir = ?config(data_dir, Config), + filelib:ensure_dir(SystemTmpDir), + file:make_dir(SystemTmpDir), + + DSAFile = filename:join(SystemTmpDir, "ssh_host_dsa_key.pub"), + file:delete(DSAFile), + + DSAPrivateFile = filename:join(SystemTmpDir, "ssh_host_dsa_key"), + file:delete(DSAPrivateFile), + + KHFile = filename:join(SystemTmpDir, "known_hosts"), + file:delete(KHFile), + + PemBin = public_key:pem_encode([EncodedKey]), + + file:write_file(DSAFile, PublicKeyEnc), + file:write_file(KHFile, KnownHostsEnc), + file:write_file(DSAPrivateFile, PemBin), + ok. + +%%-------------------------------------------------------------------- +%% Creates a dsa key (OBS: for testing only) +%% the sizes are in bytes +%% gen_dsa(::integer()) -> {::atom(), ::binary(), ::opaque()} +%%-------------------------------------------------------------------- +gen_dsa(LSize,NSize) when is_integer(LSize), is_integer(NSize) -> + Key = gen_dsa2(LSize, NSize), + {Key, encode_key(Key)}. + +encode_key(Key = #'RSAPrivateKey'{}) -> + {ok, Der} = 'OTP-PUB-KEY':encode('RSAPrivateKey', Key), + {'RSAPrivateKey', list_to_binary(Der), not_encrypted}; +encode_key(Key = #'DSAPrivateKey'{}) -> + {ok, Der} = 'OTP-PUB-KEY':encode('DSAPrivateKey', Key), + {'DSAPrivateKey', list_to_binary(Der), not_encrypted}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%% DSA key generation (OBS: for testing only) +%% See http://en.wikipedia.org/wiki/Digital_Signature_Algorithm +%% and the fips_186-3.pdf +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +gen_dsa2(LSize, NSize) -> + Q = prime(NSize), %% Choose N-bit prime Q + X0 = prime(LSize), + P0 = prime((LSize div 2) +1), + + %% Choose L-bit prime modulus P such that p-1 is a multiple of q. + case dsa_search(X0 div (2*Q*P0), P0, Q, 1000) of + error -> + gen_dsa2(LSize, NSize); + P -> + G = crypto:mod_exp(2, (P-1) div Q, P), % Choose G a number whose multiplicative order modulo p is q. + %% such that This may be done by setting g = h^(p-1)/q mod p, commonly h=2 is used. + + X = prime(20), %% Choose x by some random method, where 0 < x < q. + Y = crypto:mod_exp(G, X, P), %% Calculate y = g^x mod p. + + #'DSAPrivateKey'{version=0, p=P, q=Q, g=G, y=Y, x=X} + end. + +%% See fips_186-3.pdf +dsa_search(T, P0, Q, Iter) when Iter > 0 -> + P = 2*T*Q*P0 + 1, + case is_prime(crypto:mpint(P), 50) of + true -> P; + false -> dsa_search(T+1, P0, Q, Iter-1) + end; +dsa_search(_,_,_,_) -> + error. + + +%%%%%%% Crypto Math %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +prime(ByteSize) -> + Rand = odd_rand(ByteSize), + crypto:erlint(prime_odd(Rand, 0)). + +prime_odd(Rand, N) -> + case is_prime(Rand, 50) of + true -> + Rand; + false -> + NotPrime = crypto:erlint(Rand), + prime_odd(crypto:mpint(NotPrime+2), N+1) + end. + +%% see http://en.wikipedia.org/wiki/Fermat_primality_test +is_prime(_, 0) -> true; +is_prime(Candidate, Test) -> + CoPrime = odd_rand(<<0,0,0,4, 10000:32>>, Candidate), + case crypto:mod_exp(CoPrime, Candidate, Candidate) of + CoPrime -> is_prime(Candidate, Test-1); + _ -> false + end. + +odd_rand(Size) -> + Min = 1 bsl (Size*8-1), + Max = (1 bsl (Size*8))-1, + odd_rand(crypto:mpint(Min), crypto:mpint(Max)). + +odd_rand(Min,Max) -> + Rand = <> = crypto:rand_uniform(Min,Max), + BitSkip = (Sz+4)*8-1, + case Rand of + Odd = <<_:BitSkip, 1:1>> -> Odd; + Even = <<_:BitSkip, 0:1>> -> + crypto:mpint(crypto:erlint(Even)+1) + end. + +copyfile(SrcDir, DstDir, Fn) -> + file:copy(filename:join(SrcDir, Fn), + filename:join(DstDir, Fn)). + +%%% END SSH key management +%%%----------------------------------------------------------------- diff --git a/lib/common_test/test/ct_test_netconf_server.erl b/lib/common_test/test/ct_test_netconf_server.erl new file mode 100644 index 000000000000..11855ce959c8 --- /dev/null +++ b/lib/common_test/test/ct_test_netconf_server.erl @@ -0,0 +1,506 @@ +%%-------------------------------------------------------------------- +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2012. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +%%---------------------------------------------------------------------- +%% A netconf server used for testing of netconfc +-module(ct_test_netconf_server). + +%-compile(export_all). +-include_lib("common_test/src/ct_netconfc.hrl"). + + +%%%----------------------------------------------------------------- +%%% API +-export([start/1, + stop/1, + hello/1, + hello/2, + expect/1, + expect_reply/2, + expect_do/2, + expect_do_reply/3, + hupp/1, + hupp/2]). + +%%%----------------------------------------------------------------- +%%% ssh_channel callbacks +-export([init/1, + terminate/2, + handle_ssh_msg/2, + handle_msg/2]). + +%%%----------------------------------------------------------------- +%% Server specifications +-define(SERVER_DATA_NAMESPACE, "ClientTest"). +-define(CAPABILITIES,?CAPABILITIES_VSN("1.0")). +-define(CAPABILITIES_VSN(Vsn), + [ + ?NETCONF_BASE_CAP ++ Vsn, + "urn:ietf:params:netconf:capability:writable-running:1.0", + "urn:ietf:params:netconf:capability:candidate:1.0", + "urn:ietf:params:netconf:capability:confirmed-commit:1.0", + "urn:ietf:params:netconf:capability:rollback-on-error:1.0", + "urn:ietf:params:netconf:capability:startup:1.0", + "urn:ietf:params:netconf:capability:url:1.0", + "urn:ietf:params:netconf:capability:xpath:1.0", + "urn:ietf:params:netconf:capability:notification:1.0", + "urn:ietf:params:netconf:capability:interleave:1.0", + ?ACTION_NAMESPACE, + ?SERVER_DATA_NAMESPACE + ]). +-define(SSH_PORT, 2060). +-define(ssh_config(Dir),[{port, ?SSH_PORT}, + {interface, {127,0,0,1}}, + {system_dir, Dir}, + {user_dir, Dir}, + {user_passwords, [{"xxx","xxx"}]}, + {password, "global-xxx"}]). + +%% Some help for debugging +%-define(dbg(F,A),io:format(F,A)). +-define(dbg(F,A),ok). +-define(dbg_event(Event,Expect), + ?dbg("Event: ~p~nExpected: ~p~n",[Event,Expect])). + +%% State +-record(session, {cb, + connection, + buffer = <<>>, + session_id}). + + +%%%----------------------------------------------------------------- +%%% API + +%% Start the netconf server and use the given directory as system_dir +%% and user_dir +start(Dir) -> + spawn(fun() -> init_server(Dir) end). + +%% Stop the netconf server +stop(Pid) -> + Pid ! {stop,self()}, + receive stopped -> ok end. + +%% Set the session id for the hello message. +%% If this is not called prior to starting the session, no hello +%% message will be sent. +%% 'Stuff' indicates some special handling to e.g. provoke error cases +hello(SessionId) -> + hello(SessionId,undefined). +hello(SessionId,Stuff) -> + insert(hello,{SessionId,Stuff}). + +%% Tell server to expect the given message without doing any further +%% actions. To be called directly before sending a request. +expect(Expect) -> + expect_do_reply(Expect,undefined,undefined). + +%% Tell server to expect the given message and reply with the give +%% reply. To be called directly before sending a request. +expect_reply(Expect,Reply) -> + expect_do_reply(Expect,undefined,Reply). + +%% Tell server to expect the given message and perform an action. To +%% be called directly before sending a request. +expect_do(Expect,Do) -> + expect_do_reply(Expect,Do,undefined). + +%% Tell server to expect the given message, perform an action and +%% reply with the given reply. To be called directly before sending a +%% request. +expect_do_reply(Expect,Do,Reply) -> + add_expect({Expect,Do,Reply}). + +%% Hupp the server - i.e. tell it to do something - +%% e.g. hupp(send_event) will cause send_event(State) to be called on +%% the session channel process. +hupp(send_event) -> + hupp(send,[make_msg(event)]); +hupp(kill) -> + hupp(fun hupp_kill/1,[]). + +hupp(send,Data) -> + hupp(fun hupp_send/2,[Data]); +hupp(Fun,Args) when is_function(Fun) -> + [{_,Pid}] = lookup(channel_process), + Pid ! {hupp,Fun,Args}. + +%%%----------------------------------------------------------------- +%%% Main loop of the netconf server +init_server(Dir) -> + ets:new(ns_tab,[set,named_table,public]), + Config = ?ssh_config(Dir), + {_,Host} = lists:keyfind(interface, 1, Config), + {_,Port} = lists:keyfind(port, 1, Config), + Opts = lists:filter(fun({Key,_}) -> + lists:member(Key,[system_dir, + password, + user_passwords, + pwdfun]) + end, + Config), + {ok, Daemon} = + ssh:daemon(Host, Port, + [{subsystems,[{"netconf",{?MODULE,[]}}]} + |Opts]), + loop(Daemon). + +loop(Daemon) -> + receive + {stop,From} -> + ssh:stop_daemon(Daemon), + From ! stopped + end. + +%%---------------------------------------------------------------------- +%% Behaviour callback functions (ssh_channel) +%%---------------------------------------------------------------------- +init([]) -> + {ok, undefined}. + +terminate(_Reason, _State) -> + ok. + +handle_ssh_msg({ssh_cm,CM,{data, Ch, _Type = 0, Data}}, State) -> + %% erlang:display({self(),data,CM,Ch,State}), + data_for_channel(CM, Ch, Data, State); +handle_ssh_msg({ssh_cm,CM,{closed, Ch}}, State) -> + %% erlang:display({self(),closed,CM,Ch,State}), + stop_channel(CM, Ch, State); +handle_ssh_msg({ssh_cm,CM,{eof, Ch}}, State) -> + %% erlang:display({self(),eof,CM,Ch,State}), + data_for_channel(CM,Ch, <<>>, State). + + +handle_msg({'EXIT', _Pid, _Reason}, State) -> + {ok, State}; +handle_msg({ssh_channel_up,Ch,CM},undefined) -> + %% erlang:display({self(),up,CM,Ch}), + ConnRef = {CM,Ch}, + SessionId = maybe_hello(ConnRef), + insert(channel_process,self()), % used to hupp the server + {ok, #session{connection = ConnRef, + session_id = SessionId}}; +handle_msg({hupp,Fun,Args},State) -> + {ok,apply(Fun,Args ++ [State])}. + +data_for_channel(CM, Ch, Data, State) -> + try data(Data, State) of + {ok, NewState} -> + case erase(stop) of + true -> + stop_channel(CM, Ch, NewState); + _ -> + {ok, NewState} + end + catch + Class:Reason -> + Stacktrace = erlang:get_stacktrace(), + error_logger:error_report([{?MODULE, data_for_channel}, + {request, Data}, + {reason, {Class, Reason}}, + {stacktrace, Stacktrace}]), + stop_channel(CM, Ch, State) + end. + +data(Data, State = #session{connection = ConnRef, + buffer = Buffer}) -> + AllData = <>, + case find_endtag(AllData) of + {ok,Msgs,Rest} -> + [check_expected(ConnRef,Msg) || Msg <- Msgs], + {ok,State#session{buffer=Rest}}; + need_more -> + {ok,State#session{buffer=AllData}} + end. + +stop_channel(CM, Ch, State) -> + ssh:close(CM), + {stop, Ch, State}. + + +%%%----------------------------------------------------------------- +%%% Functions to trigg via hupp/1: + +%% Send data spontaneously - e.g. an event +hupp_send(Data,State = #session{connection = ConnRef}) -> + send(ConnRef,Data), + State. +hupp_kill(State = #session{connection = ConnRef}) -> + kill(ConnRef), + State. + +%%%----------------------------------------------------------------- +%%% Internal functions + + +%%% Send ssh data to the client +send({CM,Ch},Data) -> + ssh_connection:send(CM, Ch, Data). + +%%% Kill ssh connection +kill({CM,_Ch}) -> + ssh:close(CM). + +add_expect(Add) -> + case lookup(expect) of + [] -> + insert(expect,[Add]); + [{expect,First}] -> + insert(expect,First ++ [Add]) + end, + ok. + +insert(Key,Value) -> + ets:insert(ns_tab,{Key,Value}). +lookup(Key) -> + ets:lookup(ns_tab,Key). + +maybe_hello(ConnRef) -> + case lookup(hello) of + [{hello,{SessionId,Stuff}}] -> + %% erlang:display({SessionId,Stuff}), + ets:delete(ns_tab,hello), + insert({session,SessionId},ConnRef), + reply(ConnRef,{hello,SessionId,Stuff}), + SessionId; + [] -> + undefined + end. + +find_endtag(Data) -> + case binary:split(Data,[?END_TAG],[global]) of + [Data] -> + need_more; + Msgs -> + {ok,lists:sublist(Msgs,length(Msgs)-1),lists:last(Msgs)} + end. + +check_expected(ConnRef,Msg) -> + case lookup(expect) of + [{expect,[{Expect,Do,Reply}|Rest]}] -> + insert(expect,Rest), + %% erlang:display({got,io_lib:format("~s",[Msg])}), + %% erlang:display({expected,Expect}), + match(Msg,Expect), + do(ConnRef, Do), + reply(ConnRef,Reply); + Expected -> + exit({error,{got_unexpected,Msg,Expected}}) + end. + +match(Msg,Expect) -> + ?dbg("Match: ~p~n",[Msg]), + {ok,ok,<<>>} = xmerl_sax_parser:stream(Msg,[{event_fun,fun event/3}, + {event_state,Expect}]). + +event(Event,_Loc,Expect) -> + ?dbg_event(Event,Expect), + event(Event,Expect). + +event(startDocument,Expect) -> match(Expect); +event({startElement,_,Name,_,Attrs},[{se,Name}|Match]) -> + msg_id(Name,Attrs), + Match; +event({startElement,_,Name,_,Attrs},[ignore,{se,Name}|Match]) -> + msg_id(Name,Attrs), + Match; +event({startElement,_,Name,_,Attrs},[{se,Name,As}|Match]) -> + msg_id(Name,Attrs), + match_attrs(Name,As,Attrs), + Match; +event({startElement,_,Name,_,Attrs},[ignore,{se,Name,As}|Match]) -> + msg_id(Name,Attrs), + match_attrs(Name,As,Attrs), + Match; +event({startPrefixMapping,_,Ns},[{ns,Ns}|Match]) -> Match; +event({startPrefixMapping,_,Ns},[ignore,{ns,Ns}|Match]) -> Match; +event({endPrefixMapping,_},Match) -> Match; +event({endElement,_,Name,_},[{ee,Name}|Match]) -> Match; +event({endElement,_,Name,_},[ignore,{ee,Name}|Match]) -> Match; +event(endDocument,Match) when Match==[]; Match==[ignore] -> ok; +event(_,[ignore|_]=Match) -> Match; +event(Event,Match) -> throw({nomatch,{Event,Match}}). + +msg_id("rpc",Attrs) -> + case lists:keyfind("message-id",3,Attrs) of + {_,_,_,Str} -> put(msg_id,Str); + false -> erase(msg_id) + end; +msg_id(_,_) -> + ok. + +match_attrs(Name,[{Key,Value}|As],Attrs) -> + case lists:keyfind(atom_to_list(Key),3,Attrs) of + {_,_,_,Value} -> match_attrs(Name,As,Attrs); + false -> throw({missing_attr,Key,Name,Attrs}); + _ -> throw({faulty_attr_value,Key,Name,Attrs}) + end; +match_attrs(_,[],_) -> + ok. + +do(ConnRef, close) -> + ets:match_delete(ns_tab,{{session,'_'},ConnRef}), + put(stop,true); +do(_ConnRef, {kill,SessionId}) -> + case lookup({session,SessionId}) of + [{_,Owner}] -> + ets:delete(ns_tab,{session,SessionId}), + kill(Owner); + _ -> + exit({no_session_to_kill,SessionId}) + end; +do(_, undefined) -> + ok. + +reply(_,undefined) -> + ?dbg("no reply~n",[]), + ok; +reply(ConnRef,Reply) -> + ?dbg("Reply: ~p~n",[Reply]), + send(ConnRef, make_msg(Reply)). + +from_simple(Simple) -> + list_to_binary(xmerl:export_simple_element(Simple,xmerl_xml)). + +xml(Content) -> + <<"\n", + Content/binary,"\n",?END_TAG/binary>>. + +rpc_reply(Content) when is_binary(Content) -> + MsgId = case erase(msg_id) of + undefined -> <<>>; + Id -> list_to_binary([" message-id=\"",Id,"\""]) + end, + <<"\n", + Content/binary,"\n">>; +rpc_reply(Content) -> + rpc_reply(list_to_binary(Content)). + +session_id(no_session_id) -> + <<>>; +session_id(SessionId0) -> + SessionId = list_to_binary(integer_to_list(SessionId0)), + <<"",SessionId/binary,"\n">>. + +capabilities(undefined) -> + CapsXml = list_to_binary([["",C,"\n"] + || C <- ?CAPABILITIES]), + <<"\n",CapsXml/binary,"\n">>; +capabilities({base,Vsn}) -> + CapsXml = list_to_binary([["",C,"\n"] + || C <- ?CAPABILITIES_VSN(Vsn)]), + <<"\n",CapsXml/binary,"\n">>; +capabilities(no_base) -> + [_|Caps] = ?CAPABILITIES, + CapsXml = list_to_binary([["",C,"\n"] || C <- Caps]), + <<"\n",CapsXml/binary,"\n">>; +capabilities(no_caps) -> + <<>>. + +%%%----------------------------------------------------------------- +%%% Match received netconf message from the client. Add a new clause +%%% for each new message to recognize. The clause argument shall match +%%% the Expect argument in expect/1, expect_reply/2 or +%%% expect_do_reply/3. +%%% +%%% match(term()) -> [Match]. +%%% Match = ignore | {se,Name} | {se,Name,Attrs} | {ee,Name} | {ns,Namespace} +%%% Name = string() +%%% Attrs = [{atom(),string()}] +%%% Namespace = string() +%%% +%%% 'se' means start element, 'ee' means end element - i.e. to match +%%% an XML element you need one 'se' entry and one 'ee' entry with the +%%% same name in the match list. +match(hello) -> + [ignore,{se,"hello"},ignore,{ee,"hello"},ignore]; +match('close-session') -> + [ignore,{se,"rpc"},{se,"close-session"}, + {ee,"close-session"},{ee,"rpc"},ignore]; +match('edit-config') -> + [ignore,{se,"rpc"},{se,"edit-config"},{se,"target"},ignore,{ee,"target"}, + {se,"config"},ignore,{ee,"config"},{ee,"edit-config"},{ee,"rpc"},ignore]; +match('get') -> + match({get,subtree}); +match({'get',FilterType}) -> + [ignore,{se,"rpc"},{se,"get"},{se,"filter",[{type,atom_to_list(FilterType)}]}, + ignore,{ee,"filter"},{ee,"get"},{ee,"rpc"},ignore]; +match('get-config') -> + match({'get-config',subtree}); +match({'get-config',FilterType}) -> + [ignore,{se,"rpc"},{se,"get-config"},{se,"source"},ignore,{ee,"source"}, + {se,"filter",[{type,atom_to_list(FilterType)}]},ignore,{ee,"filter"}, + {ee,"get-config"},{ee,"rpc"},ignore]; +match('copy-config') -> + [ignore,{se,"rpc"},{se,"copy-config"},{se,"target"},ignore,{ee,"target"}, + {se,"source"},ignore,{ee,"source"},{ee,"copy-config"},{ee,"rpc"},ignore]; +match('delete-config') -> + [ignore,{se,"rpc"},{se,"delete-config"},{se,"target"},ignore,{ee,"target"}, + {ee,"delete-config"},{ee,"rpc"},ignore]; +match('lock') -> + [ignore,{se,"rpc"},{se,"lock"},{se,"target"},ignore,{ee,"target"}, + {ee,"lock"},{ee,"rpc"},ignore]; +match('unlock') -> + [ignore,{se,"rpc"},{se,"unlock"},{se,"target"},ignore,{ee,"target"}, + {ee,"unlock"},{ee,"rpc"},ignore]; +match('kill-session') -> + [ignore,{se,"rpc"},{se,"kill-session"},{se,"session-id"},ignore, + {ee,"session-id"},{ee,"kill-session"},{ee,"rpc"},ignore]; +match(action) -> + [ignore,{se,"rpc"},{ns,?ACTION_NAMESPACE},{se,"action"},{se,"data"},ignore, + {ee,"data"},{ee,"action"},{ee,"rpc"},ignore]; +match({'create-subscription',Content}) -> + [ignore,{se,"rpc"},{ns,?NETCONF_NOTIF_NAMESPACE}, + {se,"create-subscription"}] ++ + lists:flatmap(fun(X) -> + [{se,atom_to_list(X)},ignore,{ee,atom_to_list(X)}] + end, Content) ++ + [{ee,"create-subscription"},{ee,"rpc"},ignore]; +match(any) -> + [ignore]. + + + +%%%----------------------------------------------------------------- +%%% Make message to send to the client. +%%% Add a new clause for each new message that shall be sent. The +%%% clause shall match the Reply argument in expect_reply/2 or +%%% expect_do_reply/3. +make_msg({hello,SessionId,Stuff}) -> + SessionIdXml = session_id(SessionId), + CapsXml = capabilities(Stuff), + xml(<<"\n",CapsXml/binary, + SessionIdXml/binary,"">>); +make_msg(ok) -> + xml(rpc_reply("")); +make_msg({data,Data}) -> + xml(rpc_reply(from_simple({data,Data}))); +make_msg(event) -> + xml(<<"" + "2012-06-14T14:50:54+02:00" + "" + "major" + "Something terrible happened" + "" + "">>); +make_msg(Xml) when is_binary(Xml) -> + xml(Xml); +make_msg(Simple) when is_tuple(Simple) -> + xml(from_simple(Simple)).