This module implements predicates and macros for easily threading
records (as in, library(record)
) as state.
- author
- - Eyal Dechter <eyaldechter@gmail.com>
- state(?State:record)// is det
-
- author
- - Markus Triska
Predicate passes state using DCG semi-context notation.
- state(?StateIn:record, ?StateOut:record)// is semidet
-
- author
- - Markus Triska
- run_state(+StateIn:record, ?StateOut:record, +Goal) is nondet
- Run stateful computation Goal with initial state StateIn and resulting state StateOut.
NB: run_state is subject to goal expansion.
go(State) :-
default_my_state(State0),
run_state(State0, State,
(
put(my_state, a, 2),
get(my_state, a, A)
)
- gets(+Constructor:atom, +FieldValues:list(field(value)))// is det
- NB: run_state is subject to goal expansion.
Example:
gets(my_state, [my_field(Value1), my_term(Value2)]
- puts(+Constructor:atom, +FieldValues:list(field(value)))// is det
- NB: run_state is subject to goal expansion.
Example:
puts(my_state, [my_int(1), my_term(a)]
- get(+Constructor:atom, +Field:atom, ?Value:value)// is det
- NB: run_state is subject to goal expansion.
Example:
get(my_state, my_int, Int)
- put(+Constructor:atom, +Field:atom, +Value:value)// is det
- NB: run_state is subject to goal expansion.
Example:
put(my_state, my_int, 1)
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- mod_state(Arg1, Arg2, Arg3)