1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2019-2023, VU University Amsterdam 7 SWI-Prolog Solutions b.v. 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(ssh_server, 37 [ ssh_server/0, 38 ssh_server/1, % +Options 39 capture_messages/1 % +Level 40 ]). 41:- use_module(library(debug)). 42:- use_module(library(option)). 43:- use_module(library(settings)). 44 45:- use_foreign_library(foreign(sshd4pl)). 46 47/** <module> Embedded SSH server 48 49This module defines an embedded SSH server for SWI-Prolog on top of 50[libssh](https://libssh.org). This module allows for a safe secondary 51access point to a running Prolog process. A typical use case is to 52provide a safe channal or inspection and maintenance of servers or 53embedded Prolog instances. 54 55If possible, a _login_ to the Prolog process uses a _pseudo terminal_ to 56realise normal terminal interaction, including processing of ^C to 57interrupt running queries. If `libedit` (editline) is used as the 58command line editor this is installed (see el_wrap/0), providing 59advanced command line editing and history. 60 61The library currently support _login_ to the Prolog process. Future 62versions may also use the client access and exploit the SSH subsystem 63interface to achieve safe interaction between Prolog peers. 64 65## The client session 66 67A new connection creates a Prolog thread that handles the connection. 68The new thread's standard streams (`user_input`, `user_output`, 69`user_error`, `current_input` and `current_output`) are attached to the 70new connection. Some of the environment is shared as Prolog flags. The 71following flags are defined: 72 73 - ssh_tty 74 Provides the name of the _pseudo terminal_ if such a terminal us 75 allocated for this connection. 76 - ssh_term 77 Provides the ``TERM`` environment variable passed from the client. 78 - ssh_user 79 Provides the name of the user logged on. 80 81If a _pseudo terminal_ is used and the `ssh_term` flag is not `dump`, 82library(ansi_term) is connected to provide colorized output. 83 84If a _pseudo terminal_ is used and library(editline) is available, this 85library is used to enable command line editing. 86 87## Executing commands 88 89Using ``ssh <options> <server> <command>``, ``<command>`` is executed 90without a terminal (unless the ``-t`` option is given to `ssh` to force 91a terminal) and otherwise as a single Prolog toplevel command. For 92example: 93 94``` 95ssh -p 2020 localhost "writeln('Hello world')" 96Hello world 97true. 98``` 99 100If the query is nondeterministic alternative answers can be requested in 101the same way as using the interactive toplevel. The exit code is defined 102as follows: 103 104 - 0 105 The query succeeded 106 - 1 107 The query failed 108 - 2 109 The query produced an exception (the system prints a backtrace) 110 - 3 111 The query itself was not syntactically correct. 112 113### Aborting the server 114 115If a Prolor process with an embedded ssh server misbehaves it can be 116forcefully aborted using the `abort` command. This calls C `abort()` as 117soon as possible and thus should function even if Prolog is, for 118example, stuck in a deadlock. 119 120 ssh -p 2020 localhost abort 121 122@tbd Currently only supports Unix. A Windows port is probably doable. It 123mostly requires finding a sensible replacement for the Unix pseudo 124terminal. 125 126@tbd Implement running other commands than the Prolog toplevel. 127*/ 128 129:- multifile 130 verify_password/3. % +ServerName, +User, +Password 131 132:- predicate_options( 133 ssh_server/1, 1, 134 [ name(atom), 135 port(integer), 136 bind_address(atom), 137 host_key_file(atom), 138 authorized_keys_file(atom), 139 auth_methods(list(oneof([password,public_key]))) 140 ]). 141 142:- setting(port, positive_integer, 2020, 143 "Default port for SWI-Prolog SSH server"). 144:- setting(color_term, boolean, true, 145 "Enable ANSI color output on SSH terminal"). 146 147%! ssh_server is det. 148%! ssh_server(+PortOrOptions) is det. 149% 150% Create an embedded SSH server in the current Prolog process. If the 151% argument is an integer it is interpreted as 152% ssh_server([port(Integer)]). Options: 153% 154% - name(+Atom) 155% Name the server. Passed as first argument to verify_password/3 156% to identify multiple servers. 157% - port(+Integer) 158% Port to listen on. Default is 2020. 159% - bind_address(+Name) 160% Interface to listen to. Default is `localhost`. Use `*` 161% to grant acccess from all network interfaces. 162% - host_key_file(+File) 163% 164% File name for the host private key. If omitted it searches for 165% `etc/ssh` below the current directory and user_app_config('etc/ssh') 166% (normally ``~/.config/swi-prolog/etc/ssh``). On failure it 167% creates, a directory `etc/ssh` with default host keys and uses 168% these. 169% - auth_methods(+ListOfMethod) 170% Set allowed authentication methods. ListOfMethod is a list of 171% - password 172% Allow password login (see verify_password/3) 173% - public_key 174% Allow key based login (see `authorized_keys_file` below) 175% The default is derived from the `authorized_keys_file` option 176% and whether or not verify_password/3 is defined. 177% - authorized_keys_file(+File) 178% File name for a file holding the public keys for users that 179% are allows to login. Activates auth_methods([public_key]). 180% This file is in OpenSSH format and contains a certificate 181% per line in the format 182% 183% <type> <base64-key> <comment> 184% 185% The the file `~/.ssh/authorized_keys` is present, this will 186% be used as default, granting anyone with access to this account 187% to access the server with the same keys. If the option is 188% present with value `[]` (empty list), no key file is used. 189 190 191ssh_server :- 192 ssh_server([]). 193 194ssh_server(Port) :- 195 integer(Port), 196 !, 197 ssh_server([port(Port)]). 198ssh_server(Options) :- 199 setting(port, DefPort), 200 merge_options(Options, 201 [ port(DefPort), 202 bind_address(localhost) 203 ], Options1), 204 ( option(name(Name), Options) 205 -> Alias = Name 206 ; option(port(Port), Options1), 207 format(atom(Alias), 'sshd@~w', [Port]) 208 ), 209 ensure_host_keys(Options1, Options2), 210 add_authorized_keys(Options2, Options3), 211 add_auth_methods(Options3, Options4), 212 setup_signals(Options4), 213 thread_create(ssh_server_nt(Options4), _, 214 [ alias(Alias), 215 detached(true) 216 ]). 217 218%! ensure_host_keys(+Options0, -Options) is det. 219% 220% Provide a host key: 221% 222% 1. If the key file is given, use it. 223% 2. If there is a key in `etc/ssh`, use it. 224% 3. If there is a key in user_app_config('etc/ssh'), use it. 225% 4. Try to create a key in user_app_config('etc/ssh') 226% 5. Try to create a key in `etc/ssh` 227 228ensure_host_keys(Options, Options) :- 229 option(host_key_file(KeyFile), Options), 230 !, 231 ( access_file(KeyFile, read) 232 -> true 233 ; permission_error(read, ssh_host_key_file, KeyFile) 234 ). 235ensure_host_keys(Options0, Options) :- 236 exists_file('etc/ssh/ssh_host_ecdsa_key'), 237 !, 238 Options = [host_key_file('etc/ssh/ssh_host_ecdsa_key')|Options0]. 239ensure_host_keys(Options0, Options) :- 240 absolute_file_name(user_app_config('etc/ssh'), Dir, 241 [ file_type(directory), 242 access(exist), 243 file_errors(fail) 244 ]), 245 !, 246 directory_file_path(Dir, ssh_host_ecdsa_key, KeyFile), 247 Options = [host_key_file(KeyFile)|Options0]. 248ensure_host_keys(Options0, Options) :- 249 absolute_file_name(user_app_config('etc/ssh'), Dir, 250 [ solutions(all), 251 file_errors(fail) 252 ]), 253 Error = error(_,_), 254 catch(make_directory_path(Dir), Error, fail), 255 file_directory_name(Dir, P0), 256 file_directory_name(P0, ConfigDir), 257 format(string(KeyCmd), 'ssh-keygen -A -f ~w', [ConfigDir]), 258 print_message(informational, ssh_server(create_host_keys(Dir))), 259 shell(KeyCmd), 260 !, 261 directory_file_path(Dir, ssh_host_ecdsa_key, KeyFile), 262 Options = [host_key_file(KeyFile)|Options0]. 263ensure_host_keys(Options, 264 [ host_key_file('etc/ssh/ssh_host_ecdsa_key') 265 | Options 266 ]) :- 267 print_message(informational, ssh_server(create_host_keys('etc/ssh'))), 268 make_directory_path('etc/ssh'), 269 shell('ssh-keygen -A -f .'). 270 271add_auth_methods(Options, Options) :- 272 option(auth_methods(_), Options), 273 !. 274add_auth_methods(Options, [auth_methods(Methods)|Options]) :- 275 findall(Method, option_auth_method(Options, Method), Methods). 276 277option_auth_method(Options, public_key) :- 278 option(authorized_keys_file(_), Options). 279option_auth_method(_Options, password) :- 280 predicate_property(verify_password(_,_,_), number_of_clauses(N)), 281 N > 0. 282 Options0, Options) (:- 284 option(authorized_keys_file(AuthKeysFile), Options0), 285 !, 286 ( AuthKeysFile == [] 287 -> select_option(authorized_keys_file(AuthKeysFile), Options0, Options) 288 ; Options = Options0 289 ). 290add_authorized_keys(Options, [authorized_keys_file(AuthKeysFile)|Options]) :- 291 expand_file_name('~/.ssh/authorized_keys', [AuthKeysFile]), 292 access_file(AuthKeysFile, read), 293 !. 294add_authorized_keys(Options, Options). 295 296%! setup_signals(+Options) 297% 298% Re-installs the `int` signal to start the debugger. Notably 299% library(http/http_unix_daemon) binds this to terminates the process. 300 301setup_signals(_Options) :- 302 E = error(_,_), 303 catch(on_signal(int, _, debug), E, print_message(warning, E)). 304 305%! run_client(+Server, +In, +Out, +Err, +Command, -RetCode) is det. 306% 307% Run Command using I/O from the triple <In, Out, Err> and bind 308% RetCode to the ssh shell return code. 309 310:- public run_client/6. 311 312run_client(Server, In, Out, Err, Command, RetCode) :- 313 set_alias, 314 setup_console(Server, In, Out, Err, Cleanup), 315 call_cleanup(ssh_toplevel(Command, RetCode), 316 shutdown_console(Cleanup)). 317 318:- if(current_predicate(thread_alias/1)). 319set_alias :- 320 current_prolog_flag(ssh_user, User), 321 thread_self(Me), 322 thread_property(Me, id(Id)), 323 format(atom(Alias), '~w@ssh/~w', [User, Id]), 324 thread_alias(Alias). 325:- endif. 326set_alias. 327 328% Used by has_console/0 in thread_util. 329 330:- dynamic thread_util:has_console/4. 331 332setup_console(Server, In, Out, Err, clean(Me, Cleanup)) :- 333 thread_self(Me), 334 assertz(thread_util:has_console(Me, In, Out, Err)), 335 set_stream(In, alias(user_input)), 336 set_stream(Out, alias(user_output)), 337 set_stream(Err, alias(user_error)), 338 set_stream(In, alias(current_input)), 339 set_stream(Out, alias(current_output)), 340 enable_colors, 341 enable_line_editing(Mode), 342 load_history(Mode, Server, Cleanup). 343 344shutdown_console(clean(TID, History)) :- 345 retractall(thread_util:has_console(TID, _In, _Out, _Err)), 346 save_history(History), 347 disable_line_editing. 348 349:- if(setting(color_term, true)). 350:- use_module(library(ansi_term)). 351:- endif. 352 353%! enable_colors is det. 354% 355% Enable ANSI colors on the remote shell. This is controlled by the 356% setting `color_term`. Note that we do not wish to inherit this as 357% the server may have different preferences. 358 359enable_colors :- 360 stream_property(user_input, tty(true)), 361 setting(color_term, true), 362 current_prolog_flag(ssh_term, Term), 363 Term \== dump, 364 !, 365 set_prolog_flag(color_term, true). 366enable_colors :- 367 set_prolog_flag(color_term, false). 368 369%! enable_line_editing is det. 370% 371% Enable line editing for the SSH session. We can do this if the SSH 372% session uses a pseudo terminal and we are using library(editline) as 373% command line editor (GNU readline uses global variables and thus can 374% only handle a single tty in the process). 375 376use_editline :- 377 exists_source(library(editline)), 378 ( current_prolog_flag(readline, editline) 379 -> true 380 ; \+ current_prolog_flag(readline, _) 381 ). 382 383:- if(use_editline). 384:- use_module(library(editline)). 385enable_line_editing(editline) :- 386 stream_property(user_input, tty(true)), 387 !, 388 debug(ssh(server), 'Setting up line editing', []), 389 set_prolog_flag(tty_control, true), 390 el_wrap. 391:- else. 392enable_line_editing(tty) :- 393 stream_property(user_input, tty(true)), 394 !, 395 set_prolog_flag(tty_control, true). 396:- endif. 397enable_line_editing(none) :- 398 set_prolog_flag(tty_control, false). 399 400:- if(current_predicate(el_unwrap/1)). 401disable_line_editing :- 402 el_wrapped(user_input), 403 !, 404 Error = error(_,_), 405 catch(el_unwrap(user_input), Error, true). 406:- endif. 407disable_line_editing. 408 409%! verify_password(+ServerName, +User:atom, +Passwd:string) is semidet. 410% 411% Hook that can be used to accept password based logins. This 412% predicate must succeeds to accept the User/Passwd combination. 413% 414% @arg ServerName is the name provided with the name(Name) option when 415% creating the server or the empty list. 416 417 418 /******************************* 419 * HISTORY * 420 *******************************/ 421 422:- multifile 423 prolog:history/2. 424 425%! load_history(+EditMode, +Server, -Cleanup) is det. 426% 427% Load command line history for Server, binding Cleanup to the 428% required command for save_history/1 429 430load_history(editline, Server, save(File)) :- 431 history_file(Server, File, 432 [ access(read), 433 file_errors(fail) 434 ]), 435 !, 436 prolog:history(user_input, load(File)). 437load_history(editline, Server, create(Server)) :- 438 !. 439load_history(_, _, nosave). 440 441%! save_history(+Action) is det. 442% 443% Save the history information according to action. 444 445save_history(save(File)) :- 446 catch(write_history(File), _, true), 447 !. 448save_history(create(Server)) :- 449 history_file(Server, File, 450 [ file_errors(fail), 451 solutions(all) 452 ]), 453 catch(write_history(File), _, true), 454 !. 455save_history(_). 456 457write_history(File) :- 458 file_directory_name(File, Dir), 459 make_directory_path(Dir), 460 prolog:history(user_input, save(File)). 461 462history_file(Server, Path, Options) :- 463 ( Server == [] 464 -> SName = default 465 ; SName = Server 466 ), 467 current_prolog_flag(ssh_user, User), 468 atomic_list_concat([ssh, history, SName, User], /, File), 469 absolute_file_name(user_app_config(File), Path, Options). 470 471 472 473%! ssh_toplevel(+Command, -RetCode) 474% 475% Run the toplevel goal for the SSH session. The default is `prolog`, 476% running the toplevel. Otherwise the argument is processed as a 477% single toplevel goal. 478 479ssh_toplevel(prolog, 0) :- 480 !, 481 version, 482 prolog. 483ssh_toplevel(Command, RetCode) :- 484 catch(term_string(Query, Command, [variable_names(Bindings)]), 485 Error, true), 486 ( var(Error) 487 -> catch_with_backtrace('$execute_query'(Query, Bindings, Truth), E2, true), 488 toplevel_finish(Truth, E2, RetCode) 489 ; print_message(error, Error), 490 RetCode = 3 491 ). 492 493toplevel_finish(_, Error, 2) :- 494 nonvar(Error), 495 !, 496 print_message(error, Error). 497toplevel_finish(true, _, 0). 498toplevel_finish(false, _, 1). 499 500 501 /******************************* 502 * CAPTURE MESSAGES * 503 *******************************/ 504 505:- dynamic 506 captured_messages/3. 507:- thread_local 508 thread_error_stream/1. 509 510usermessage_property(Level, stream(S)) :- 511 captured_messages(Level, S, _). 512 513%! capture_messages(+Level) is det. 514% 515% Redirect all messages of the indicated level to the console of the 516% current thread. This is part of the SSH library as it is notably 517% practical when connected through SSH. Consider using trace/1 on 518% some predicate. We catch capture the output using: 519% 520% ?- capture_messages(debug). 521% ?- trace(p/1). 522 523capture_messages(Level) :- 524 ( thread_error_stream(S) 525 -> true 526 ; thread_self(Me), 527 stream_property(S, alias(user_error)), 528 asserta(thread_error_stream(S)), 529 thread_at_exit(cleanup_message_capture) 530 ), 531 asserta(captured_messages(Level, S, Me)). 532 533cleanup_message_capture :- 534 thread_self(Me), 535 retractall(captured_messages(_,_,Me)). 536 537 538 /******************************* 539 * MESSAGES * 540 *******************************/ 541 542:- multifile 543 prolog:message//1. 544 545prologmessage(ssh_server(create_host_keys(Dir))) --> 546 [ 'SSH Server: Creating host keys in "~w"'-[Dir] ]