Skip to content

Commit

Permalink
check in prolog files
Browse files Browse the repository at this point in the history
  • Loading branch information
Anniepoo committed Jun 27, 2021
1 parent 8d0479e commit ce803b6
Show file tree
Hide file tree
Showing 9 changed files with 517 additions and 0 deletions.
6 changes: 6 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -30,3 +30,9 @@
*.exe
*.out
*.app

# editor backups
*~
*.*~


29 changes: 29 additions & 0 deletions prolog/board.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
:- module(board, [
board//0
]).

:- use_module(library(http/html_write)).
:- use_module(library(http/http_session)).

board_size(20, 20).

% TODO use setof's group-by to make nested lists of T
board -->
{ board_size(NumCols, NumRows),
setof(X, between(1, NumCols, X), Row),
setof(Y-Row, between(1, NumRows, Y), Board)
},
html(table(\rows(Board))).

rows([]) --> [].
rows([Y-Row |More]) -->
html([tr(\row(Y, Row)) | \rows(More)]).

row(_, []) --> [].
row(Y, [X | More]) -->
{( http_session_data(board(Y, X, T))
; T = grass
)},
html(td(img(src=T+".png"))),
row(Y, More).

54 changes: 54 additions & 0 deletions prolog/game.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
:- module(game, [
get_state/2,
init_global/0,
make_player_inited/1 % +S inited
]).

:- use_module(library(chr)).

:- chr_constraint
cur_ticks/2, % session, ticks the current time in ticks for session s
get_ticks/2, % session, Ticks transient getter of the current ticks
days_go_by/2, % session, ticks increment the current time (and make world go)
reset_time/1, % session reset the current time to start

chr_reset/1, % session transient reset the game state
inited/1, % session exists if this session initialized
make_player_inited/1, % session transient idempotic insure session inited

act/2, % session, actionname transient, causes this action to happen
potential_action/1, % actionname same as known_action but as CHR constraint
get_available_actions/2, % session, ActionName transient get all actions we can do now
collect_available_actions/2, % session, Actions transient, after we've made available_actions collect them
available_action/2, % session, actionname transient this action is available
acty_done/2, % session, actyname simple one time activities. succeeds if this acty done
acty/2, % session, actyname record we did this acty


thing/3, % session, type, status an individual object
count_things/3, % session, type, Count return the count of things
set_init_inventory/1, % session transient create the initial inventory

news/2, % session, news the news for this turn
get_news/2. % session, News getter for this turns news

get_state(S, Response) :-
( get_state_(S, Response)
-> true
; gtrace
).
get_state_(_S, _{ foo: 7}). % :-
% b_setval(session, S). S is the session #

/*******************************
* Global initialization.
*
* Things that happen once at startup.
*
*******************************/
init_global. % :-
% setof(X, known_action(X), List),
% maplist(potential_action, List).


make_player_inited(_S). % session
30 changes: 30 additions & 0 deletions prolog/gamepage.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
:- module(gamepage, []).
/** <module> serves the main game page
*
*/

:- use_module(library(http/thread_httpd)).
:- use_module(library(http/http_dispatch)).
:- use_module(library(chr)).
:- use_module(library(http/http_session)).
:- use_module(library(http/http_files)).
:- use_module(library(http/http_json)).
:- use_module(library(http/html_write)).


:- use_module(board).

:- http_handler('/', main_page, []).

main_page(_Request) :-
reply_html_page(title('Trans Haven'),
\haven_body).


haven_body -->
html([
h1('Trans haven'),
\board
]).


91 changes: 91 additions & 0 deletions prolog/happenings.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,91 @@
:- module(happenings, [random_happenings/2]).
/** <Module> happenings - random bits of stuff reported in letters
*
*/

:- use_module(game, [current_date/1, has/3]).
:- use_module(util).
:- use_module(library(chr)).

:- chr_constraint said/2, reset_said/1, not_said/2.

random_happenings(Who, Happenings) :-
b_getval(session, S),
random_between(1,2, N),
findall(X, (happening(Who, X), not_said(S, X)), OrdAllPossible),
( OrdAllPossible = []
->
reset_said(S),
random_happenings(Who, Happenings)
;
random_permutation(OrdAllPossible, AllPossible),
take(N, AllPossible, Happenings),
maplist(said(S), Happenings)
).

% TODO this isn't ideal, as it's really only the 'sent' letter that
% should be 'said', but that's kind of a mess to implement.
% and I'm not even sure it's better gameplay

reset_said(S) \ said(S, _) <=> true.
reset_said(_) <=> true.

said(S, Str) \ not_said(S, Str) <=> fail.
not_said(_, _) <=> true.

:- discontiguous happening/2, happening/4.

happening(Who, What) :-
happening(Who, What, L, U),
integer(L),
integer(U),
current_date(between(L, U)).
happening(Who, What) :-
happening(Who, What, C, N),
memberchk(C, [ < , > , =< , >= , =:= , \= ]),
integer(N),
current_date(mo(T)),
call(C, T, N).

happening(annette, "I could think this was late February. Time to begin seeing jonquils coming up. Unfortunately, the birds appear to have similar misperception of where we are in the year's progression.", 2,3).
happening(annette, "This morning, the birds singing sounded more like spring than winter.", 10, 3).
happening(annette, "Soon, we will have to begin the enormous task of pruning the grapevines.", 3,4).
happening(annette, "A coyote got into the chickens. Killed the rooster, we'll have to get another one.").
happening(annette, "Hit a big rock with the tractor, and we may have to buy a wheel. Big expense.", 4, 10).
happening(annette, "Big sale at the church. We\'ll haul some of our rusted junk there to sell.").
happening(annette, "I try not to read the newspapers or look at the internet.").
happening(annette, "Friends gave us 8 ducks. I\'ve got them set up in a a tank with water, food, and a heat lamp.").
happening(annette, "Spent the last two days on TTB paperwork. What a headache.").
happening(annette, "Bill and Ethyl came by. Bill brought his banjo, Tom and he had fun playing tunes.").
happening(annette, "Found fruit flies around some garbage near the wine shed. Hope that\'s not a sign they're in the wine bins.").
happening(annette, "Tom shot a buck. Big mess dragging it back, but we\'re happily stocking the larder.", 8, 11).
happening(annette, "Deer in our vineyard. One trellis is pretty well wiped out. What they didn\'t eat, they knocked over.", 4, 9).
happening(annette, "The turkeys are doing a good job keeping down the grasshoppers.", 5, 10).
happening(annette, "Sorry for not writing, we\'ve been working til we drop to get the harvest in.", 8,9).
happening(annette, "Tom scraped enough snow that we can get in and out.", 12, 2).
happening(annette, "Saw a gopher hole in the vegetable garden. Poked in dryer sheets.", 3,11).
happening(annette, "The vineyard\'s far from the house. Made some wind chimes from old pipe, the sound keeps various critters away.").
happening(annette, "Been a mild winter so far.", 11, 3).
happening(annette, "Hoping for rain.", 4, 9).
happening(annette, "Pump for the house has died. Another expense. Sigh.").
happening(annette, "Neighbor\s cow in the field. We\'re not happy.", 3, 11).
happening(annette, "Going to build some shelves in the wine shed.", 10, 6).


happening(priscilla, "I\'m clueless about this stuff. Please help us.", < , 12).
happening(priscilla, "Sometimes I think it\'d be better to give up and move back to town.") :-
current_date(turn(N)),
N > 6,
N < 24.
happening(priscilla, "I'm sure sick of living in a trailer and eating canned beans") :-
has(house, < , 1),
has(trailer, > , 0).
happening(priscilla,
["I can\'t believe we were living in a tent. I told George it\'s move back to town or get a divorce",
"He wanted to soldier on, but finally agreed. We had a good cry. ",
"We're in a small apartment in town. George is interviewing, I've gotten a job at Nixon Elementary.",
"(The game is over - click restart to play again)"]) :-
has(house, < , 1),
has(trailer, < , 1).
happening(priscilla,
"Do I have to feed the chickens something? They seem sickly."). % TODO make this conditional
143 changes: 143 additions & 0 deletions prolog/oldstuff.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,143 @@

/*******************************
* Old stuff below here, move above if you use it
*******************************/

:- if(false).

:- chr_constraint

thing/3, % session, name, status
new_thing/2, % session, name, []
new_thing/3, % session, name, status
make_player_inited/1, % session
inited/1, % session

act/2, % session, action
available_action/2, % session, action

collect_things/2,
thing_to_collect/3,
all_things/2,

collect_assets/2,
asset_to_collect/3,
all_assets/2,

collect_status/2,
status_to_collect/4,
all_status/2,

collect_available_actions/2,
available_action_to_collect/2,
all_available_actions/2,

collect_env/2,
env_to_collect/3,
all_env/2,

env/3,
status/4,
time_passing/1,
time_event/2,
error/3,
collect_errors/3,
id_counter/1.

act(S, buy_cow), asset(S, money, M0)
<=>
M0 >= 60 |
M is M0 - 60,
new_thing(S, cow, ok),
asset(S, money, M).

act(S, buy_cow) <=> error(S, 'cannot_afford', []).

%
% End turn game logic
%
act(S, end_turn) <=> time_passing(S).

time_passing(S) ==> time_event(S, tick).

time_event(S, tick), env(S, time, T0) <=> T is T0 + 1, env(S, time, T).

time_event(_, _) <=> true.
time_passing(_) <=> true.

% reset to the start of game state. Not same as make_player_inited
% which establishes initial conditions when session first seen
%
% chr_reset(S) \ thing(S, _, _) <=> true.
% chr_reset(S) \ asset(S, _, _) <=> true.
chr_reset(S) <=>
env(S, time, 1),
asset(S, money, 100),
new_thing(S, field, []),
new_thing(S, trailer, [condition-run_down]),
new_thing(S, cow, [sick-false]).

new_thing(S, Type) <=> new_thing(S, Type, []).
new_thing(S, Type, Statuses), id_counter(NewId) <=>
NextId is NewId + 1,
thing(S, Type, NewId),
id_counter(NextId),
maplist(new_status(S, NewId), Statuses).

new_status(S, Id, Name-Value) <=> status(S, Id, Name, Value).


collect_things(S, _), thing(S, Name, Id) ==> thing_to_collect(S, Name, Id).
collect_things(S, L) <=> all_things(S, L).

thing_to_collect(S, Name, Id), all_things(S, L) <=>
L = [[Name, Id] |L1],
all_things(S, L1).
all_things(_, L) <=> L = [].


collect_assets(S, _), asset(S, Name, Amount) ==> asset_to_collect(S, Name, Amount).
collect_assets(S, L) <=> all_assets(S, L).

asset_to_collect(S, Name, Amount), all_assets(S, L) <=>
L = [[Name, Amount] |L1],
all_assets(S, L1).
all_assets(_, L) <=> L = [].


collect_available_actions(S, _), available_action(S, Name) ==> available_action_to_collect(S, Name).
collect_available_actions(S, L) <=> all_available_actions(S, L).

available_action_to_collect(S, Name), all_available_actions(S, L) <=>
L = [Name |L1],
all_available_actions(S, L1).
all_available_actions(_, L) <=> L = [].


collect_env(S, _), env(S, Key, Value) ==> env_to_collect(S, Key, Value).
collect_env(S, L) <=> all_env(S, L).

env_to_collect(S, Key, Value), all_env(S, L) <=>
L = [[Key,Value] |L1],
all_env(S, L1).
all_env(_, L) <=> L = [].


collect_status(S, _), status(S, Id, Key, Value) ==> status_to_collect(S, Id, Key, Value).
collect_status(S, L) <=> all_status(S, L).

status_to_collect(S, Id, Key, Value), all_status(S, L) <=>
L = [[Id,Key,Value] |L1],
all_status(S, L1).
all_status(_, L) <=> L = [].


collect_errors(S, SoFar, Ret), error(S, Fmt, Vars) <=>
format(string(Str), Fmt, Vars),
string_concat(SoFar, Str, NewSoFar),
collect_errors(S, NewSoFar, Ret).
collect_errors(_, SoFar, Ret) <=> SoFar = Ret.



:- endif.
Empty file added prolog/run.pl
Empty file.
Loading

0 comments on commit ce803b6

Please sign in to comment.