Skip to content

Commit

Permalink
Merge pull request #2263 from aarroyoc/docs-toplevel
Browse files Browse the repository at this point in the history
Move argv/1 to library(os)
  • Loading branch information
mthom authored Jan 2, 2024
2 parents a475a8a + 47b5ae7 commit 5c89029
Show file tree
Hide file tree
Showing 8 changed files with 79 additions and 43 deletions.
4 changes: 4 additions & 0 deletions build/instructions_template.rs
Original file line number Diff line number Diff line change
Expand Up @@ -604,6 +604,8 @@ enum SystemClauseType {
KeySortWithConstantVarOrdering,
#[strum_discriminants(strum(props(Arity = "0", Name = "$inference_limit_exceeded")))]
InferenceLimitExceeded,
#[strum_discriminants(strum(props(Arity = "1", Name = "$argv")))]
Argv,
REPL(REPLCodePtr),
}

Expand Down Expand Up @@ -1869,6 +1871,7 @@ fn generate_instruction_preface() -> TokenStream {
&Instruction::CallRemoveModuleExports |
&Instruction::CallAddNonCountedBacktracking |
&Instruction::CallPopCount |
&Instruction::CallArgv |
&Instruction::CallEd25519SignRaw |
&Instruction::CallEd25519VerifyRaw |
&Instruction::CallEd25519SeedToPublicKey => {
Expand Down Expand Up @@ -2104,6 +2107,7 @@ fn generate_instruction_preface() -> TokenStream {
&Instruction::ExecuteRemoveModuleExports |
&Instruction::ExecuteAddNonCountedBacktracking |
&Instruction::ExecutePopCount |
&Instruction::ExecuteArgv |
&Instruction::ExecuteEd25519SignRaw |
&Instruction::ExecuteEd25519VerifyRaw |
&Instruction::ExecuteEd25519SeedToPublicKey => {
Expand Down
2 changes: 1 addition & 1 deletion src/bin/scryer-prolog.rs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,6 @@ fn main() -> std::process::ExitCode {

runtime.block_on(async move {
let mut wam = machine::Machine::new(Default::default());
wam.run_top_level(atom!("$toplevel"), (atom!("$repl"), 1))
wam.run_module_predicate(atom!("$toplevel"), (atom!("$repl"), 0))
})
}
33 changes: 32 additions & 1 deletion src/lib/os.pl
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,9 @@
unsetenv/1,
shell/1,
shell/2,
pid/1]).
pid/1,
raw_argv/1,
argv/1]).

:- use_module(library(error)).
:- use_module(library(charsio)).
Expand Down Expand Up @@ -110,3 +112,32 @@
must_be_chars(Cs) :-
must_be(list, Cs),
maplist(must_be(character), Cs).

%% raw_argv(-Argv)
%
% True iff Argv is the list of arguments that this program was started with (usually passed via command line).
% In contrast to `argv/1`, this version includes every argument, without any postprocessing, just as the operating
% system reports it to the system. This includes-flags of Scryer itself, which are not needed in general.
raw_argv(Argv) :-
can_be(list, Argv),
'$argv'(Argv).

%% argv(-Argv)
%
% True if Argv is the list of arguments that this program was started with (usually passed via command line).
% In this version, only arguments specific to the program are passed. To differentiate between the system
% arguments and the program arguments, we use `--` as a separator.
%
% Example:
% ```
% % Call with scryer-prolog -f -- -t hello
% ?- argv(X).
% X = ["-t", "hello"].
% ```
argv(Argv) :-
can_be(list, Argv),
'$argv'(Argv0),
( append(_, ["--"|Argv], Argv0) ->
true
; Argv = []
).
2 changes: 1 addition & 1 deletion src/loader.pl
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@
load_context(Module),
abolish(Module:'$initialization_goals'/1),
unload_evacuable(Evacuable),
( clause('$toplevel':argv(_), _) ->
( clause('$toplevel':started, _) ->
% let the toplevel call loader:write_error/1
throw(Error)
; '$print_message_and_fail'(Error)
Expand Down
8 changes: 8 additions & 0 deletions src/machine/dispatch.rs
Original file line number Diff line number Diff line change
Expand Up @@ -4147,6 +4147,14 @@ impl Machine {
try_or_throw!(self.machine_st, self.js_eval());
step_or_fail!(self, self.machine_st.p = self.machine_st.cp);
}
&Instruction::CallArgv => {
try_or_throw!(self.machine_st, self.argv());
step_or_fail!(self, self.machine_st.p += 1);
}
&Instruction::ExecuteArgv => {
try_or_throw!(self.machine_st, self.argv());
step_or_fail!(self, self.machine_st.p = self.machine_st.cp);
}
&Instruction::CallCurrentTime => {
self.current_time();
step_or_fail!(self, self.machine_st.p += 1);
Expand Down
25 changes: 1 addition & 24 deletions src/machine/mod.rs
Original file line number Diff line number Diff line change
Expand Up @@ -228,7 +228,7 @@ impl Machine {
self.machine_st.throw_exception(err);
}

fn run_module_predicate(
pub fn run_module_predicate(
&mut self,
module_name: Atom,
key: PredicateKey,
Expand Down Expand Up @@ -307,29 +307,6 @@ impl Machine {
}
}

pub fn run_top_level(
&mut self,
module_name: Atom,
key: PredicateKey,
) -> std::process::ExitCode {
let mut arg_pstrs = vec![];

for arg in env::args() {
arg_pstrs.push(put_complete_string(
&mut self.machine_st.heap,
&arg,
&self.machine_st.atom_tbl,
));
}

self.machine_st.registers[1] = heap_loc_as_cell!(iter_to_heap_list(
&mut self.machine_st.heap,
arg_pstrs.into_iter()
));

self.run_module_predicate(module_name, key)
}

pub fn set_user_input(&mut self, input: String) {
self.user_input = Stream::from_owned_string(input, &mut self.machine_st.arena);
}
Expand Down
21 changes: 21 additions & 0 deletions src/machine/system_calls.rs
Original file line number Diff line number Diff line change
Expand Up @@ -4950,6 +4950,27 @@ impl Machine {
}
}

#[inline(always)]
pub(crate) fn argv(&mut self) -> CallResult {
let args = self.deref_register(1);

let mut args_pstrs = vec![];
for arg in env::args() {
args_pstrs.push(put_complete_string(
&mut self.machine_st.heap,
&arg,
&self.machine_st.atom_tbl,
));
}
let cell = heap_loc_as_cell!(iter_to_heap_list(
&mut self.machine_st.heap,
args_pstrs.into_iter()
));

unify!(self.machine_st, args, cell);
Ok(())
}

#[inline(always)]
pub(crate) fn current_time(&mut self) {
let timestamp = self.systemtime_to_timestamp(SystemTime::now());
Expand Down
27 changes: 11 additions & 16 deletions src/toplevel.pl
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
:- module('$toplevel', [argv/1,
copy_term/3]).
:- module('$toplevel', [copy_term/3, started/0]).

:- use_module(library(atts), [call_residue_vars/2]).
:- use_module(library(charsio)).
Expand All @@ -9,11 +8,13 @@
:- use_module(library(lambda)).
:- use_module(library(lists)).
:- use_module(library(si)).
:- use_module(library(os)).

:- use_module(library('$project_atts')).
:- use_module(library('$atts')).

:- dynamic(disabled_init_file/0).
:- dynamic(started/0).

load_scryerrc :-
( '$home_directory'(HomeDir) ->
Expand All @@ -26,24 +27,18 @@
; true
).

:- dynamic(argv/1).

'$repl'([_|Args0]) :-
\+ argv(_),
( append(Args1, ["--"|Args2], Args0) ->
asserta('$toplevel':argv(Args2)),
'$repl' :-
asserta('$toplevel':started),
raw_argv(Args0),
( append(Args1, ["--"|_], Args0) ->
Args = Args1
; asserta('$toplevel':argv([])),
Args = Args0
; Args = Args0
),
delegate_task(Args, []),
(\+ disabled_init_file -> load_scryerrc ; true),
repl.
'$repl'(_) :-
( \+ argv(_) -> asserta('$toplevel':argv([]))
( Args = [_|TaskArgs] ->
delegate_task(TaskArgs, [])
; true
),
load_scryerrc,
(\+ disabled_init_file -> load_scryerrc ; true),
repl.

delegate_task([], []).
Expand Down

0 comments on commit 5c89029

Please sign in to comment.