Building a port scanner

The next version adds library(persistency).

:- use_module(library(persistency)).

:- working_directory(_,'C:\\Users\\Eric\\Documents\\Port Scans').

:- persistent
    port_scan_result(port:integer,result:atom).

:- initialization(db_attach('port_scan_result.journal', [])).

exists_port_scan_result(Request,Response) :-
    port_scan_result(Request,Response).

add_port_scan_result(Request,Response) :-
    with_mutex(port_scan_result_journal, assert_port_scan_result(Request,Response)).

concurrent_scan_02(IP_address,Low_port,High_port,Number_of_threads) :-
    concurrent_forall(
        between(Low_port,High_port,Port),
        port_scan_02(IP_address,Port),
        [threads(Number_of_threads)]
    ).

port_scan_02(IP_address,Port) :-
    catch(
        setup_call_cleanup(
            tcp_socket(Socket),
            (
                % Open stream socket based on TCP/IP which uses IP address and port number, i.e. INET socket
                tcp_connect(Socket, IP_address:Port),
                (
                    exists_port_scan_result(Port,open), !
                ;
                    add_port_scan_result(Port,open)
                )
            ),
            tcp_close_socket(Socket)
        ),
        error(_,_),
        (
            exists_port_scan_result(Port,closed), !
        ;
            add_port_scan_result(Port,closed)
        )
    ).

Example run.

NB halt. is needed so that the data is written to the file. Until halt all of the data resides as facts in the Prolog database.

?- concurrent_scan_02('140.211.166.101',75,84,3).
true.

?- halt.

File: port_scan_result.journal

created(1593621240.60769).
assert(port_scan_result(77,closed)).
assert(port_scan_result(76,closed)).
assert(port_scan_result(75,closed)).
assert(port_scan_result(80,open)).
assert(port_scan_result(78,closed)).
assert(port_scan_result(79,closed)).
assert(port_scan_result(81,closed)).
assert(port_scan_result(83,closed)).
assert(port_scan_result(82,closed)).
assert(port_scan_result(84,closed)).

A more comprehensive example.

?- time(concurrent_scan_02('140.211.166.101',1,65536,8192)).
% 196,642 inferences, 0.547 CPU in 175.149 seconds (0% CPU, 359574 Lips)
true.

8192 threads checking 65536 ports in ~3 minutes.