1:- module('plammar/state', [ 2 initial_state/2, 3 state_space/3, 4 set_context/3, 5 set_context/4, 6 get_context/2, 7 get_context/3, 8 get_context/4, 9 del_context/3, 10 del_context/5, 11 inc_context/4, 12 dec_context/4, 13 inc_state/4, 14 state_warn/3 15 ]). 16 17:- use_module(library(lists), [append/3]). 18:- use_module(library(option), [merge_options/3, option/2, option/3, select_option/4]). 19 20:- use_module(util). 21 22initial_state(Options, SN) :- 23 option(initial_state(Initial_State), Options, []), 24 S0 = [ 25 pos(1:0), 26 warnings([]) 27 ], 28 merge_options(S0, Initial_State, SN). 29 30set_context(S0, SN, Value) :- 31 option(context(Context0), S0, []), 32 set_option(value(Value), Context0, Context1), 33 set_option(context(Context1), S0, SN). 34 35set_context(S0, SN, Namespace, Value) :- 36 \+ is_list(Value), 37 option(context(Context0), S0, []), 38 What0 =.. [Namespace, NS0], 39 option(What0, Context0, []), 40 set_option(Value, NS0, NS1), 41 What1 =.. [Namespace, NS1], 42 set_option(What1, Context0, Context1), 43 set_option(context(Context1), S0, SN). 44 45set_context(S0, S0, _Namespace, []). 46set_context(S0, SN, Namespace, [V|Vs]) :- 47 set_context(S0, S1, Namespace, V), 48 set_context(S1, SN, Namespace, Vs). 49 50get_context(S0, Value) :- 51 option(context(Context0), S0, []), 52 option(value(Value), Context0, no_context). 53 54get_context(S0, Namespace, Value) :- 55 get_context(S0, Namespace, Value, no_context). 56 57get_context(S0, Namespace, Value, Default) :- 58 option(context(Context0), S0, []), 59 What0 =.. [Namespace, NS0], 60 option(What0, Context0, []), 61 option(Value, NS0, Default). 62 63del_context(S0, SN, Value) :- 64 option(context(Context0), S0, []), 65 select_option(value(Value), Context0, Context1, no_context), 66 set_option(context(Context1), S0, SN). 67 68del_context(S0, SN, Namespace, Value, Default) :- 69 option(context(Context0), S0, []), 70 What0 =.. [Namespace, NS0], 71 option(What0, Context0, []), 72 select_option(Value, NS0, NS1, Default), 73 What1 =.. [Namespace, NS1], 74 set_option(What1, Context0, Context1), 75 set_option(context(Context1), S0, SN). 76 77inc_context(S0, SN, Namespace, Prop) :- 78 What0 =.. [Prop, Value0], 79 del_context(S0, S1, Namespace, What0, 0), 80 Value1 is Value0 + 1, 81 What1 =.. [Prop, Value1], 82 set_context(S1, SN, Namespace, What1). 83 84dec_context(S0, SN, Namespace, Prop) :- 85 What0 =.. [Prop, Value0], 86 del_context(S0, S1, Namespace, What0, 1), 87 Value1 is Value0 - 1, 88 What1 =.. [Prop, Value1], 89 set_context(S1, SN, Namespace, What1). 90 91inc_state(S0, SN, Namespace, Prop) :- 92 What_NS0 =.. [Namespace, NS0], 93 select_option(What_NS0, S0, S1, []), 94 What0 =.. [Prop, Value0], 95 select_option(What0, NS0, NS1, 0), 96 Value1 is Value0 + 1, 97 What1 =.. [Prop, Value1], 98 merge_options([What1], NS1, NSN), 99 What_NS1 =.. [Namespace, NSN], 100 merge_options([What_NS1], S1, SN). 101 102state_space(S0, SN, cols(N)) :- 103 option(pos(L0:C0), S0), 104 L1 = L0, 105 C1 is C0 + N, 106 set_option(pos(L1:C1), S0, SN). 107 108state_space(S0, SN, rows(N)) :- 109 option(pos(L0:_C0), S0), 110 L1 is L0 + N, 111 C1 = 0, 112 set_option(pos(L1:C1), S0, SN). 113 114state_warn(S0, SN, List) :- 115 option(warnings(Warnings0), S0, []), 116 option(pos(L0:C0), S0), 117 Warning = warn([pos(L0:C0)|List]), 118 append(Warnings0, [Warning], Warnings1), 119 merge_options([warnings(Warnings1)], S0, SN)