home *** CD-ROM | disk | FTP | other *** search
-
- /*
- * param.pro -- 5/6/'86
- *
- * this program demonstrates how to access the command line
- * parameters from a turbo prolog program.
- *
- * we use a dos function $62 if the version of dos is
- * 3.0 or greater, and function $51 for 2.xx (an undocumented
- * function) the potential problem is that certain nameless
- * programs install themselves on function $51, so be warned.
- */
-
- include "EXAMPL66.PRO" /* This example includes some */
- /* handy DOS routines */
-
- domains
- strlist = string*
- predicates
- write_list(strlist)
-
- clauses
- write_list([]).
- write_list([H|T]) :-
- write(H, " "),
- write_list(T).
-
- predicates
- get_psp(integer)
- get_params(string, integer)
- m_p(string, integer, integer, strlist, strlist)
- cmd_line(integer, strlist)
- append(strlist, strlist, strlist)
-
- clauses
- /* get the psp segment
- * first clause is for version 3.0 or higher
- */
- get_psp(PSP) :-
- dosver(Version),
- Version >= 3.0,
- !,
- bios($21,reg($6200,0,0,0,0,0,0,0),
- reg(_,PSP,_,_,_,_,_,_)).
- /* for version 2.xx */
- get_psp(PSP) :-
- !,
- bios($21,reg($5100,0,0,0,0,0,0,0),
- reg(_,PSP,_,_,_,_,_,_)).
-
- /* get parameter vector */
- get_params(P_string, PSP) :-
- ptr_dword(P, PSP, $81),
- frontchar(P, _, P_string).
-
- /* split vector into list of strings */
- m_p(P, Ac, Ac, Av, Av) :-
- frontchar(P, C, _),
- char_int(C, N),
- N = 13.
- m_p(P, Ac, T, Av, V) :-
- fronttoken(P, S1, P1),
- !,
- append(V, [S1], V1),
- T1 = T + 1,
- m_p(P1, Ac, T1, Av, V1).
-
- /* make typical argc, argv form for convience */
- cmd_line(Argc, Argv) :-
- get_psp(PSP),
- get_params(P, PSP),
- m_p(P, Argc, 0, Argv, []).
-
-
- append([], X, X).
- append([H|T], L1, [H|L2]) :-
- append(T, L1, L2).
-
- goal
- clearwindow,
- cmd_line(Ac, Av),
- write(Ac), nl,
- write_list(Av), nl.