1/* <Legendary Heroes>, by <Zonghan Xu>. */
    2
    3:- dynamic i_am_at/1, in/1, at/2, holding/1, 
    4level/1, experience/1, nextLevelExp/1, attack/1, defense/1, health/1, fullhealth/1, money/1,
    5c_level/1, c_attack/1, c_defense/1, c_health/1, c_fullhealth/1,
    6hydra_health/1,
    7sell/1, wear/1, chest/1, casket/1.    8
    9:- retractall(at(_, _)), retractall(i_am_at(_)), retractall(alive(_)).   10
   11i_am_at(forest).
   12in(peace).
   13
   14path(forest, n, marketplace).
   15path(marketplace, s, forest).
   16
   17path(forest, s, marsh).
   18path(marsh, n, forest).
   19
   20path(forest, e, cave).
   21path(cave, w, forest).
   22
   23path(forest, w, grassland).
   24path(grassland, e, forest).
   25
   26
   27/* Houses' location information */
   28locate(woodenHouse, forest).
   29locate(shop, marketplace).
   30locate(witch, grassland).
   31locate(chest, marketplace).
   32locate(casket, forest).
   33
   34/* Items' location information */
   35at(key, grassland).
   36chest(close).
   37casket(close).
   38treasure(15).
   39masterpiece(pendant_of_courage).
   40
   41
   42/* Shop specific inforamtion */
   43sell([sword_of_hellfire, hellstorm_helmet]).
   44
   45/* Puzzle information */
   46solution(andrew).
   47reward(dragon_scale_shield).
   48
   49/* Attributes of equipments */
   50price(sword_of_hellfire, 20).
   51price(hellstorm_helmet, 10).
   52
   53attackplus(sword_of_hellfire, 15).
   54attackplus(hellstorm_helmet, 2).
   55attackplus(dragon_scale_shield, 0).
   56attackplus(pendant_of_courage, 5).
   57defenseplus(sword_of_hellfire, 1).
   58defenseplus(hellstorm_helmet, 12).
   59defenseplus(dragon_scale_shield, 5).
   60defenseplus(pendant_of_courage, 5).
   61
   62
   63/* Hero's initial state. */
   64level(5).
   65
   66experience(0).
   67
   68nextLevelExp(10).
   69
   70attack(10).
   71
   72defense(3).
   73
   74health(20).
   75
   76fullhealth(20).
   77
   78money(5).
   79
   80wear([]).
   81
   82holding(nothing).
   83
   84/* Creature's initial state. */
   85c_level(1).
   86
   87c_attack(1).
   88
   89c_defense(1).
   90
   91c_health(10).
   92
   93c_fullhealth(10).
   94
   95/* Hydra's initial state. */
   96hydra_level(20).
   97
   98hydra_attack(30).
   99
  100hydra_defense(20).
  101
  102hydra_health(50).
  103
  104hydra_fullhealth(50).
  105
  106/* These rules prints equipments shop has */
  107print_equipments_shop([Head|Tail]) :-
  108        write('We have '), write(Head), write('. '),
  109        price(Head, E_price),
  110        attackplus(Head, E_attack),
  111        defenseplus(Head, E_defense),
  112        write('Its price: '), write(E_price), write('. '), 
  113        write('Its attack: +'), write(E_attack), write('. '), 
  114        write('Its defense: +'), write(E_defense), write('.'), nl,
  115        print_equipments_shop(Tail).
  116
  117print_equipments_shop(_).
  118
  119/* These rules prints equipments you wear */
  120print_equipments([Head|Tail]) :-
  121        write('You are wearing '), write(Head), write('. '),
  122        attackplus(Head, E_attack),
  123        defenseplus(Head, E_defense),
  124        write('Its attack: +'), write(E_attack), write('. '), 
  125        write('Its defense: +'), write(E_defense), write('.'), nl,
  126        print_equipments(Tail).
  127
  128print_equipments(_).
  129
  130/* These rules tell you the current state of the hero */
  131state :-   
  132        level_state,
  133        experience_state,
  134        physical_state,
  135        health_state,
  136        !, nl.
  137
  138physical_state :-
  139        attack(A),
  140        defense(D),
  141        write('Your attack value is '), write(A), nl,
  142        write('Your defense value is '), write(D), nl.
  143
  144level_state :-
  145        level(L),
  146        write('Your current level is '), write(L), nl.
  147
  148experience_state :-
  149        experience(E),
  150        nextLevelExp(NE),
  151        write('Your current experience points is '), write(E), write('/'), write(NE), write('.'), nl.
  152
  153health_state :-
  154        health(H),
  155        fullhealth(FH),
  156        (
  157            H =< 0 ->
  158            retract(in(battle)),
  159            assert(in(peace)),
  160            write('Your health value is '), write(0), write('/'), write(FH), write('.'), nl,
  161            write('You are dead!'), nl,
  162            !, die, fail;
  163            H > 0 ->
  164            write('Your health value is '), write(H), write('/'), write(FH), write('.'), nl
  165        ).
  166
  167pocket :-
  168        money(M),
  169        write('Your current money is '), write(M), write(' unit(s).'), !, nl.
  170
  171i :-
  172        holding(H),
  173        write('You are currently holding '), write(H), !, write('.'), nl.
  174
  175equipment :-
  176        wear(E),
  177        E = [],
  178        write('You are wearing nothing now!'), !, nl.
  179
  180equipment :-
  181        wear(E),
  182        print_equipments(E), !, nl.
  183
  184/* These rules tell you the current state of the creature */
  185c_health_state :-
  186        c_health(CH),
  187        c_fullhealth(CFH),
  188        (
  189            CH =< 0 ->
  190            write('Its health value is '), write(0), write('/'), write(CFH), nl,
  191            write('The creature is dead! And the battle is over!'), nl,
  192            gain_exp,
  193            gain_money,
  194            retract(in(battle)),
  195            assert(in(peace));
  196            CH > 0 ->
  197            write('Its health value is '), write(CH), write('/'), write(CFH), nl
  198        ).
  199
  200hydra_health_state :-
  201        hydra_health(HH),
  202        hydra_fullhealth(HFH),
  203        (
  204            HH =< 0 ->
  205            write('Its health value is '), write(0), write('/'), write(HFH), nl,
  206            write('The hydra is dead! And the battle is over! You get the treasure [Celestial Necklace of Bliss] and you win the game!!!'), nl,
  207            finish;
  208            HH > 0 ->
  209            write('Its health value is '), write(HH), write('/'), write(HFH), nl
  210        ).
  211
  212/* These rules tell you how to gain money */
  213gain_money :-
  214        money(M),
  215        c_level(CL),
  216        Max_money is CL * 2,
  217        random(CL, Max_money, Gain_money),
  218        Current_money is M + Gain_money,
  219        retract(money(M)),
  220        assert(money(Current_money)),
  221        write('You gained '), write(Gain_money), write(' unit(s) of money.'), nl,
  222        pocket.
  223
  224/* These rules tell you how to gain experience and upgrade */
  225gain_exp :-
  226        level(L),
  227        experience(E),
  228        nextLevelExp(NE),
  229        attack(A),
  230        defense(D),
  231        fullhealth(FH),
  232
  233        c_level(CL),
  234        Max_Gain_exp is CL * 2,
  235        random(CL, Max_Gain_exp, Gain_exp),
  236        Current_exp is E + Gain_exp,
  237        (
  238            Current_exp < NE -> write('You gained '), write(Gain_exp), write(' points of experience.'), nl,
  239            retract(experience(E)),
  240            assert(experience(Current_exp)),
  241            experience_state;
  242
  243            Current_exp >= NE ->
  244            Remain_exp is Current_exp - NE,
  245            Current_level is L + 1,
  246            retract(experience(E)),
  247            assert(experience(Remain_exp)),
  248            retract(level(L)),
  249            assert(level(Current_level)),
  250
  251            Current_NE is NE + Current_level,
  252            retract(nextLevelExp(NE)),
  253            assert(nextLevelExp(Current_NE)),
  254
  255            Current_FH is FH + 5,
  256            Current_A is A + 2,
  257            Current_D is D + 1,
  258            retract(fullhealth(FH)),
  259            retract(attack(A)),
  260            retract(defense(D)),
  261            assert(fullhealth(Current_FH)),
  262            assert(attack(Current_A)),
  263            assert(defense(Current_D)),
  264
  265            write('You gained '), write(Gain_exp), write(' points of experience.'), nl,
  266            write('Congratulations, You upgrade! '), nl,
  267            level_state,
  268            experience_state,
  269            physical_state,
  270            write('Your maximum health is '), write(Current_FH), write(' now.'), nl
  271        ).
  272
  273
  274/* These rules tell the special situation, i.e. in battle */
  275is_battle :-
  276        in(battle),
  277        write('You are in battle now!'), nl,
  278        write('Enter commands using standard Prolog syntax.'), nl,
  279        write('Available commands in battle are:'), nl,
  280        write('attack.              -- to attack the creature.'), nl,
  281        write('escape.              -- to quit the battle.'), nl,
  282        !, nl.
  283
  284at_shop :-
  285        i_am_at(marketplace),
  286        locate(shop, marketplace),
  287        !, nl.
  288
  289at_shop :-
  290        write('You are not at the shop!'), 
  291        !, nl.
  292
  293/* These rules give the hero health back */
  294
  295
  296/* These rules tell how to enter into a house */
  297enter :-
  298        is_battle,
  299        !, nl.
  300
  301enter :-
  302        health(H),
  303        fullhealth(FH),
  304        i_am_at(forest),
  305        locate(woodenHouse, forest),
  306        retract(health(H)),
  307        assert(health(FH)),
  308        write('Oh, you got your energy back. You can adventure now!'), nl,
  309        health_state, !, nl.
  310
  311enter :-
  312        sell(E),
  313        i_am_at(marketplace),
  314        locate(shop, marketplace),
  315        (
  316            E = [] ->
  317            write('Sorry, all the equipments are sold out!'), !, fail, nl;
  318
  319            write('Hi, what would you wanna buy? Type[buy(equipment_exact_name).]'), nl,
  320            pocket,
  321            print_equipments_shop(E),
  322            !, nl
  323        ).       
  324
  325/* These rules tell how to buy a equipment */
  326buy(E) :-
  327        i_am_at(Marketplace),
  328        (
  329            Marketplace \= marketplace ->
  330            write('You are not at the shop!'), !, fail, nl;
  331
  332            sell(List),
  333            (
  334                \+ member(E, List) ->
  335                write('There is no such equipements called '), write(E), nl,
  336                write('Plsease type[buy(equipment_exact_name).]'), !, fail, nl;
  337                deal(E)
  338            )
  339        ).
  340
  341deal(E) :-
  342        money(M),
  343        price(E, P),
  344        (
  345            M < P ->
  346            write('You do not have enough money to buy!'), nl,
  347            fail;
  348            M >= P ->
  349            write('You successfully bought '), write(E), write('!'), nl,
  350            
  351            sell(Slist),
  352            delete(Slist, E, Current_Slist),
  353            retract(sell(Slist)),
  354            assert(sell(Current_Slist)),
  355
  356            wear(Wlist),
  357            append(Wlist, [E], Current_Wlist),
  358            retract(wear(Wlist)),
  359            assert(wear(Current_Wlist)),
  360
  361            Current_money is M - P,
  362            retract(money(M)),
  363            assert(money(Current_money)),
  364
  365            attack(A),
  366            defense(D),
  367            attackplus(E, Aplus),
  368            defenseplus(E, Dplus),
  369           
  370            Current_A is A + Aplus,
  371            Current_D is D + Dplus,
  372            retract(attack(A)),
  373            retract(defense(D)),
  374            assert(attack(Current_A)),
  375            assert(defense(Current_D)),
  376            physical_state,
  377            pocket,
  378            equipment
  379        ).
  380
  381/* These rules tell how to encounter a creature */
  382approach :-
  383        is_battle,
  384        !, nl.
  385        
  386approach :-
  387        i_am_at(marsh),
  388        battle(marsh),
  389        !, nl.
  390
  391approach :-
  392        i_am_at(cave),
  393        level(L),
  394        (
  395            L >= 7 ->  battle(cave), !, nl;
  396            L < 6 -> write('Uh oh, your level is too low [the minimum level should be above 7], try to make you stronger!'), !, nl
  397        ).
  398
  399approach :-
  400        i_am_at(grassland),
  401        puzzle(grassland),
  402        !, nl.
  403
  404approach :-
  405        open,
  406        !, nl.
  407
  408approach :- 
  409        write('Here is nothing!'), 
  410        !, nl.
  411
  412/* These rules tell how to solve puzzle */
  413open :-
  414        i_am_at(marketplace), !,
  415        holding(H),
  416        chest(State),
  417        (
  418            State = open ->
  419            write('This chest is open and nothing in it now!'), !, nl;
  420            (
  421                H \= key ->
  422                write('Uh oh, this chest need a key! Try to find it!'), !, nl;
  423                write('You open the chest!'), nl,
  424                write('The key disappeared!'), nl, 
  425                retract(holding(H)),
  426                assert(holding(nothing)),
  427                treasure(Gain_money),
  428
  429                money(M),
  430                Current_money is M + Gain_money,
  431                retract(money(M)),
  432                assert(money(Current_money)),
  433                write('You gained '), write(Gain_money), write(' unit(s) of money.'), nl,
  434                pocket,
  435
  436                retract(chest(close)),
  437                assert(chest(open)),
  438                !, nl  
  439            )
  440        ).
  441
  442open :-
  443        i_am_at(forest), !,
  444        holding(H),
  445        casket(State),
  446        (
  447            State = open ->
  448            write('This casket is open and nothing in it now!'), !, nl;
  449            (
  450                H \= key ->
  451                write('Uh oh, this casket need a key! Try to find it!'), !, nl;
  452
  453                retract(holding(H)),
  454                assert(holding(nothing)),
  455                masterpiece(M),
  456
  457                attack(A),
  458                defense(D),
  459                attackplus(M, Aplus),
  460                defenseplus(M, Dplus),
  461
  462                write('You open the casket!'), nl,
  463                write('The key disappeared!'), nl,
  464                write('You find '), write(M), write('.'), nl,
  465                write('Its attack: +'), write(Aplus), write('. '), nl,
  466                write('Its defense: +'), write(Dplus), write('.'), nl,
  467
  468                wear(Wlist),
  469                append(Wlist, [M], Current_Wlist),
  470                retract(wear(Wlist)),
  471                assert(wear(Current_Wlist)),
  472           
  473                Current_A is A + Aplus,
  474                Current_D is D + Dplus,
  475                retract(attack(A)),
  476                retract(defense(D)),
  477                assert(attack(Current_A)),
  478                assert(defense(Current_D)),
  479                physical_state,
  480
  481                retract(casket(close)),
  482                assert(casket(open)),
  483                !, nl  
  484            )
  485        ).
  486
  487/* These rules tell how to solve puzzle */
  488puzzle(Location) :-
  489        Location = grassland,
  490        write('The witch is giving you a puzzle.'), nl,
  491        write('Here is the puzzle: '), nl,
  492        write('1. Dudley did not walk out of the store with either Flubsub or Jarix, and his alien does not develop fins when placed in water.'), nl,
  493        write('2. Jarix (which is not the name of the alien Andrew picked)has eyes that glow in the dark.'), nl,
  494        write('3. Karen left the toy store with the alien Wattin.'), nl,
  495        write('4. Andrew does not member the alien that develops fins, and Dudley does not member the alien that blows bubbles.'), nl,
  496        write('The question is: who got the flubsub toy which has bubbles feature.'), nl,
  497        write('Type answer(name) to answer the questions. Options are: andrew, dudley, georgina, karen.'), !, nl.
  498
  499answer(Solution) :-
  500        i_am_at(Location),
  501        (
  502            Location \= grassland ->
  503            write('You are not talking with the witch!'), !, fail, nl;
  504
  505            (
  506                Solution = andrew ->
  507                write('You are right! The witch gave you Dragon Scale Shield as a reward!'), nl,
  508                gift, !, nl;
  509                write('You are wrong! Keep thinking and try again!'), !, nl
  510            )
  511            
  512        ).
  513
  514gift :-
  515        reward(E),
  516        wear(Wlist),
  517
  518        (
  519            member(E, Wlist) ->
  520            write('Uh oh, you have already had one Dragon Scale Shield, you cannot wear another one!'), 
  521            nl, !, fail;
  522
  523            append(Wlist, [E], Current_Wlist),
  524            retract(wear(Wlist)),
  525            assert(wear(Current_Wlist)),
  526
  527            attack(A),
  528            defense(D),
  529            attackplus(E, Aplus),
  530            defenseplus(E, Dplus),
  531           
  532            Current_A is A + Aplus,
  533            Current_D is D + Dplus,
  534            retract(attack(A)),
  535            retract(defense(D)),
  536            assert(attack(Current_A)),
  537            assert(defense(Current_D)),
  538            equipment,
  539            physical_state
  540        ).
  541
  542/* These rules tell how to fight with creature */
  543battle(Location) :-
  544        Location = marsh,
  545        retract(in(peace)),
  546        assert(in(battle)),
  547
  548        c_level(CL),
  549        c_attack(CA),
  550        c_defense(CD),
  551        c_health(CH),
  552        c_fullhealth(CFH),
  553
  554        random(2, 10, C_level),
  555        Max_C_Attack is C_level * 2,
  556        Max_C_Defense is C_level * 2,
  557        Max_health is C_level * 2,
  558        random(C_level, Max_C_Attack, C_Attack),
  559        random(C_level, Max_C_Defense, C_Defense),
  560        random(C_level, Max_health, C_fullhealth),
  561        
  562        retract(c_level(CL)),
  563        retract(c_attack(CA)),
  564        retract(c_defense(CD)),
  565        retract(c_health(CH)),
  566        retract(c_fullhealth(CFH)),
  567
  568        assert(c_level(C_level)),
  569        assert(c_attack(C_Attack)),
  570        assert(c_defense(C_Defense)),
  571        assert(c_health(C_fullhealth)),
  572        assert(c_fullhealth(C_fullhealth)),
  573
  574        write('You encounter a creature whose level is '), write(C_level), nl,
  575        write('Its attack value is '), write(C_Attack), nl,
  576        write('Its defense value is '), write(C_Defense), nl,
  577        c_health_state,
  578        is_battle, !, nl.
  579
  580
  581battle(Location) :-
  582        Location = cave,
  583        retract(in(peace)),
  584        assert(in(battle)),
  585
  586        hydra_level(CL),
  587        hydra_attack(CA),
  588        hydra_defense(CD),
  589
  590        write('You encounter a hydra whose level is '), write(CL), nl,
  591        write('Its attack value is '), write(CA), nl,
  592        write('Its defense value is '), write(CD), nl,
  593        hydra_health_state,
  594        is_battle, !, nl.
  595
  596/* These rules describe how to do in battle. */
  597min(Attack, Defense, Damage) :- 
  598        Attack =< Defense -> Damage is 1 ; Damage is Attack - Defense.
  599
  600attack :-
  601        \+in(battle),
  602        write('There is no creature to be attacked!'), !, nl.
  603
  604attack :-
  605        in(battle),
  606        i_am_at(marsh),
  607
  608        attack(A),
  609        defense(D),
  610        health(H),
  611
  612        c_attack(CA),
  613        c_defense(CD),
  614        c_health(CH),
  615
  616        min(A, CD, H_C_Damage),
  617        min(CA, D, C_H_Damage),
  618        
  619        write('Creature gave you '), write(C_H_Damage), write(' points of damage.'), nl,
  620        Remain_H is H - C_H_Damage,
  621        retract(health(H)),
  622        assert(health(Remain_H)),
  623        health_state,
  624
  625        write('You gave creature '), write(H_C_Damage), write(' points of damage.'), nl,
  626        Remain_CH is CH - H_C_Damage,
  627        retract(c_health(CH)),
  628        assert(c_health(Remain_CH)),
  629        c_health_state,
  630        !, nl.
  631
  632attack :-
  633        in(battle),
  634        i_am_at(cave),
  635        
  636        attack(A),
  637        defense(D),
  638        health(H),
  639
  640        hydra_attack(HA),
  641        hydra_defense(HD),
  642        hydra_health(HH),
  643
  644        min(A, HD, H_C_Damage),
  645        min(HA, D, C_H_Damage),
  646        
  647        write('Hydra gave you '), write(C_H_Damage), write(' points of damage.'), nl,
  648        Remain_H is H - C_H_Damage,
  649        retract(health(H)),
  650        assert(health(Remain_H)),
  651        health_state,
  652
  653        write('You gave Hydra '), write(H_C_Damage), write(' points of damage.'), nl,
  654        Remain_HH is HH - H_C_Damage,
  655        retract(hydra_health(HH)),
  656        assert(hydra_health(Remain_HH)),
  657        hydra_health_state,
  658        !, nl.
  659
  660escape :-
  661        in(battle),
  662        i_am_at(marsh),
  663        retract(in(battle)),
  664        assert(in(peace)),
  665        write('You have successfully escaped!'),
  666        !, nl.
  667
  668escape :-
  669        in(battle),
  670        i_am_at(cave),
  671        write('You cannot escape! Keep fighting!'),
  672        !, fail, nl.
  673        
  674escape :-
  675        write('There is no need to escape!'), nl.
  676
  677
  678/* These rules describe how to pick up an object. */
  679take(_) :-
  680        is_battle,
  681        !, nl.
  682
  683take(X) :-
  684        holding(X),
  685        write('You''re already holding it!'),
  686        !, nl.
  687
  688take(X) :-
  689        holding(Old),
  690        i_am_at(Place),
  691        at(X, Place),
  692        retract(at(X, Place)),
  693        retract(holding(Old)),
  694        assert(holding(X)),
  695        write('OK.'),
  696        !, nl.
  697
  698take(_) :-
  699        write('I don''t see it here.'),
  700        nl.
  701
  702
  703/* These rules describe how to put down an object. */
  704drop(_) :-
  705        is_battle,
  706        !, nl.
  707
  708drop(X) :-
  709        holding(X),
  710        i_am_at(Place),
  711        retract(holding(X)),
  712        assert(holding(nothing)),
  713        assert(at(X, Place)),
  714        write('OK.'),
  715        !, nl.
  716
  717drop(_) :-
  718        write('You aren''t holding it!'),
  719        nl.
  720
  721
  722/* These rules define the direction letters as calls to go/1. */
  723
  724n :- go(n).
  725
  726s :- go(s).
  727
  728e :- go(e).
  729
  730w :- go(w).
  731
  732
  733/* This rule tells how to move in a given direction. */
  734go(_) :-
  735        is_battle,
  736        !, nl.
  737
  738go(Direction) :-
  739        i_am_at(Here),
  740        path(Here, Direction, There),
  741        retract(i_am_at(Here)),
  742        assert(i_am_at(There)),
  743        !, look.
  744
  745go(_) :-
  746        write('You can''t go that way.').
  747
  748
  749/* This rule tells how to look about you. */
  750look :-
  751        is_battle,
  752        !, nl.
  753
  754look :-
  755        i_am_at(Place),
  756        describe(Place),
  757        nl,
  758        notice_objects_at(Place),
  759        nl,
  760        notice_specials_at(Place),
  761        nl.
  762
  763
  764/* These rules set up a loop to mention all the objects
  765   in your vicinity. */
  766notice_objects_at(_) :-
  767        is_battle,
  768        !, nl.
  769
  770notice_objects_at(Place) :-
  771        at(X, Place),
  772        write('There is a '), write(X), write(' here.'), nl,
  773        describe(X), nl,
  774        fail.
  775
  776notice_objects_at(_).
  777
  778
  779/* These rules set up a loop to mention all the specials
  780   in your vicinity. */
  781notice_specials_at(_) :-
  782        is_battle,
  783        !, nl.
  784
  785notice_specials_at(Place) :-
  786        locate(X, Place),
  787        write('There is a '), write(X), write(' here.'), nl,
  788        describe(X), nl,
  789        fail.
  790
  791notice_specials_at(_).
  792
  793
  794/* This rule tells how to die. */
  795
  796die :-
  797        finish.
  798
  799
  800/* Under UNIX, the "halt." command quits Prolog but does not
  801   remove the output window. On a PC, however, the window
  802   disappears before the final output can be seen. Hence this
  803   routine requests the user to perform the final "halt." */
  804
  805finish :-
  806        nl,
  807        write('The game is over. Please enter the "halt." command.'),
  808        nl.
  809
  810
  811/* This rule just writes out game instructions. */
  812
  813instructions :-
  814        nl,
  815        write('Enter commands using standard Prolog syntax.'), nl,
  816        write('Available commands are:'), nl,
  817        write('start.             -- to start the game.'), nl,
  818        write('n.  s.  e.  w.     -- to go in that direction.'), nl,
  819        write('enter.             -- to enter into building.'), nl,
  820        write('approach.          -- to approach to discover.'), nl,
  821        write('take(Object).      -- to pick up an object.'), nl,
  822        write('drop(Object).      -- to put down an object.'), nl,
  823        write('state.             -- to check the state of the hero.'), nl,
  824        write('look.              -- to look around you again.'), nl,
  825        write('pocket.            -- to check the money you have.'), nl,
  826        write('i.                 -- to check what you are holding.'), nl,
  827        write('equipment.         -- to check the equipment you wear.'), nl,
  828        write('instructions.      -- to see this message again.'), nl,
  829        write('halt.              -- to end the game and quit.'), nl,
  830        nl.
  831
  832
  833/* This rule prints out instructions and tells where you are. */
  834start :-
  835        is_battle,
  836        !, nl.
  837
  838start :-
  839        instructions,
  840        look.
  841
  842
  843/* These rules describe the various rooms.  Depending on
  844   circumstances, a room may have more than one description. */
  845
  846describe(forest) :- 
  847                write('You are in the forest.'), nl.
  848
  849describe(woodenHouse) :- 
  850                write('You can type [enter.] to have a sound sleep to get your energy back.'), nl.
  851
  852describe(marsh) :-
  853                write('You are in the marsh. There are a lot of creatures lurking around. You can type [approach.] to encounter and fight with them.'), nl.
  854
  855describe(marketplace) :-
  856                write('You are in the busy marketplace.'), nl.
  857
  858describe(shop) :-
  859                write('You can type [enter.] to see the equipment(s) seller currently has.'), nl.
  860
  861describe(cave) :-
  862                write('This is a big cave. And there is a hydra here! Type [approach.] to encoutner and fight with this monster!'), nl.
  863
  864describe(grassland) :-
  865                write('This is an eerie grassland. Something is waiting for you...'), nl.
  866
  867describe(witch) :-
  868                write('You can type [approach.] to chat with the witch.'), nl.
  869
  870describe(chest) :-
  871                write('The chest is locked! Type [approach.] to try to open it.'), nl.
  872
  873describe(casket) :-
  874                write('The casket is locked! Type [approach.] to try to open it.'), nl