1:- module(os_lc, [lc_r/1, lc_r/2, lc_r/3, lc/3]).    2
    3:- use_module(library(print/table)).
 lc_r(+Extensions:list) is det
Recursively counts and prints a table of the number of lines within read-access files having one of the given Extensions found in the current directory or one of its sub-directories. Prints the results in line-count descending order with the total count appearing first against an asterisk, standing for all lines counted.
   13lc_r(Extensions) :-
   14    lc_r(Pairs0, [extensions(Extensions)]),
   15    sort(2, @>=, Pairs0, Pairs),
   16    maplist(arg(2), Pairs, Counts),
   17    sum_list(Counts, Sum),
   18    print_table(member(_-_, [(*)-Sum|Pairs])).
 lc_r(-Pairs, +Options) is det
Counts lines in files recursively within the current directory.
   24lc_r(Pairs, Options) :- lc_r(., Pairs, Options).
 lc_r(+Directory, -Pairs, +Options) is det
Counts lines within files starting at Directory.
   30lc_r(Directory, Pairs, Options) :-
   31    lc(Directory, Pairs, [recursive(true)|Options]).
 lc(+Directory, -Pairs, +Options) is det
Counts lines in files starting at Directory and using Options. Counts for each file concurrently in order to maintain high performance.
Arguments:
Pairs- is a list of atom-integer pairs where the relative path of a matching text file is the first pair-element, and the number of lines counted is the second pair-element.
   43lc(Directory, Pairs, Options) :-
   44    findall(Member0, directory_member(Directory, Member0,
   45                                      [ access(read)|Options
   46                                      ]), Members),
   47    concurrent_maplist(member_pair, Members, Pairs).
   48
   49:- public member_pair/2.   50
   51member_pair(Member, Member-Count) :-
   52    setup_call_cleanup(
   53        open(Member, read, Stream),
   54        stream_count(Stream, Count),
   55        close(Stream)).
 stream_count(+Stream, -Count:integer) is det
Counts lines in Stream. Works by reading and counting lines until end of stream. Count becomes the line count for the remaining codes within Stream. Only gives a complete count if Stream initially remains unread. The count excludes any last empty line.
   64stream_count(Stream, Count) :-
   65    read_line_to_codes(Stream, Codes),
   66    stream_count_(Codes, Stream, 0, Count).
   67
   68stream_count_(end_of_file, _, Count, Count) :- !.
   69stream_count_(_, Stream, Count0, Count) :-
   70    Count_ is Count0 + 1,
   71    read_line_to_codes(Stream, Codes),
   72    stream_count_(Codes, Stream, Count_, Count)