├── .gitignore ├── README.md ├── anglify.pl ├── fairy.pl ├── fairystory.graphml ├── fairystory.png ├── planner.pl ├── plannerb4refactor.pl ├── project.odp ├── run.pl ├── snail.pl ├── snailgarden.graphml ├── states.graphml ├── states.png └── talespin.pl /.gitignore: -------------------------------------------------------------------------------- 1 | *.*~ 2 | *~ 3 | chatfeedback.txt 4 | 5 | 6 | -------------------------------------------------------------------------------- /README.md: -------------------------------------------------------------------------------- 1 | # Talespin 2 | 3 | This is my version of the project for the Introduction to SWI-Prolog class. 4 | 5 | Anne Ogborn 6 | 7 | 8 | ## Install 9 | 10 | Just have a recent (tested on 7.7.18) SWI-Prolog install 11 | 12 | clone this repo 13 | 14 | ## Run 15 | 16 | cd talespin/ 17 | swipl run.pl 18 | ?- print_story. 19 | 20 | ## License 21 | 22 | /* 23 | * 24 | * Copyright 2018, Anne Ogborn 25 | 26 | Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 27 | 28 | 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 29 | 30 | 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 31 | 32 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 33 | */ 34 | 35 | 36 | -------------------------------------------------------------------------------- /anglify.pl: -------------------------------------------------------------------------------- 1 | /* 2 | * 3 | * Copyright 2018, Anne Ogborn 4 | 5 | Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 6 | 7 | 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 8 | 9 | 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 10 | 11 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 12 | */ 13 | :- module(anglify, [ 14 | anglify/2 15 | ]). 16 | /** Anglify the snail stories 17 | * 18 | */ 19 | anglify(Semantics, English) :- 20 | phrase(as_english([genre(snail)], EnglishList, _), Semantics), 21 | list_english(EnglishList, English), 22 | !. % lame, but ez 23 | 24 | as_english(Ctx, [], Ctx) --> []. 25 | as_english(Ctx, [English | Rest], CtxOut) --> 26 | happening(Ctx, English, Ctx1), 27 | as_english(Ctx1, Rest, CtxOut). 28 | 29 | happening(Ctx, E, Ctx1) --> 30 | [moveall(_, B), moveall(B, C)], 31 | format_desc(Ctx, 'They traveled from ~w and on to ~w.', 32 | [friend(B), friend(C)], 33 | Ctx1, E). % remember E is a string 34 | happening(Ctx, E, Ctx1) --> 35 | [moveall(_, B)], 36 | format_desc(Ctx, 'They crawled along to ~w.', [place(B)], Ctx1, E). 37 | happening(Ctx, E, Ctx) --> 38 | [E], 39 | {string(E)}. 40 | happening(Ctx, E, Ctx1) --> 41 | [blocked_by(Loc, stone)], 42 | format_desc(Ctx, 43 | 'They found the path to ~w blocked by a big round rock!', 44 | [place(Loc)], 45 | Ctx1, 46 | E). 47 | happening(Ctx, E, Ctx1) --> 48 | [unblocked(Friend, stone)], 49 | format_desc(Ctx, 50 | '~w pushed and tugged, and pushed and tugged, and rolled the rock away.', 51 | [friend(Friend)], 52 | Ctx1, 53 | E). 54 | happening(Ctx, E, Ctx1) --> 55 | [gardener_appears], 56 | format_desc(Ctx, '~w', [friend(cratchet)], Ctx1, E). 57 | happening(Ctx, E, Ctx1) --> 58 | [join_party(Friend)], 59 | format_desc(Ctx, 60 | 'Pomatia\'s friend ~w suddenly appeared, and agreed to go along.', 61 | [friend(Friend)], 62 | Ctx1, 63 | E). 64 | happening(Ctx, 65 | "They all had a grand time at the tea party. They drank tea, and ate scones, or leaves, or whatever suited them. Finally it was time to leave.", 66 | Ctx) --> 67 | [attended_tea_party]. 68 | happening(Ctx, 69 | "When everyone arrived at the party, they discovered Froggy crying disconsolately in the middle of a bare patch of ground. \"Mrs. Cratchet\", he sobbed, \"came and pulled up all the mushrooms, including my beautiful Toadstool home!", 70 | Ctx) --> 71 | [mushrooms_gone]. 72 | happening(Ctx, 73 | "A caterpillar was sitting to one side of the patch, looking at a broken hookah. \"Oh dear\", it said, \"This won\'t do at all. It blew a beautiful blue cloud, and the mushrooms reappeared.", 74 | Ctx) --> 75 | [magic_mushrooms_fix]. 76 | happening(Ctx, 77 | "Mrs. Cratchet went back inside to watch her soap opera. The garden residents sighed with relief.", Ctx) --> 78 | [gardener_leaves]. 79 | happening(Ctx, 80 | "Mrs. Cratchet picked up the rock and threw it at them! The rock wasn\'t in the way any longer!" 81 | , Ctx) --> 82 | [gardener_threw_stone]. 83 | happening(Ctx, 84 | "Pomatia had a particular hard berry they liked to use as a ball. Pomatia decided to take the ball with them." 85 | , Ctx) --> 86 | [take_ball]. 87 | happening(Ctx, 88 | "The friends played with Pomatia\'s ball." 89 | , Ctx) --> 90 | [play_ball]. 91 | happening(Ctx, "", Ctx) --> 92 | [theme(_)]. 93 | happening(Ctx, 94 | "One day Pomatia was invited to tea at the mushrooms beyond the pond. Froggy lived there, and always gave such grand tea parties.", Ctx) --> 95 | [start_message(_)]. 96 | happening(Ctx, "Pomatia bopped their ball with their head. \"Oh No!\" The ball went Splash! in the pond!", Ctx) --> 97 | [lost_ball_in_water]. 98 | happening(Ctx, "The ball drifted to the edge of the pond. Pomatia raced (slowly) to catch it. \"Oh No! The ball will float away!\" But the ball stayed near the edge, and Pomatia was able to grab it.", Ctx) --> 99 | [recover_ball_from_water]. 100 | 101 | happening(Ctx, E, Ctx) --> 102 | [A], 103 | {atom_string(A, E)}. 104 | 105 | format_desc(Ctx, Format, Args, CtxOut, String) --> [], 106 | { 107 | args_atoms(Ctx, Args, AtomArgs, CtxOut), 108 | format(string(String), Format, AtomArgs) 109 | }. 110 | 111 | args_atoms(Ctx, [], [], Ctx). 112 | args_atoms(Ctx, [place(A) | Tail], [Atom | TailOut], Ctx1) :- 113 | memberchk(genre(Genre), Ctx), 114 | Genre:place_desc(A, Short, Long), 115 | ( memberchk(A, Ctx) 116 | -> 117 | Atom = Short, 118 | args_atoms(Ctx, Tail, TailOut, Ctx1) 119 | ; 120 | Atom = Long, 121 | args_atoms([A | Ctx], Tail, TailOut, Ctx1) 122 | ). 123 | args_atoms(Ctx, [friend(A) | Tail], [Atom | TailOut], Ctx1) :- 124 | memberchk(genre(Genre), Ctx), 125 | Genre:friend_desc(A, Short, Long), 126 | ( memberchk(A, Ctx) 127 | -> 128 | Atom = Short, 129 | args_atoms(Ctx, Tail, TailOut, Ctx1) 130 | ; 131 | Atom = Long, 132 | args_atoms([A | Ctx], Tail, TailOut, Ctx1) 133 | ). 134 | 135 | list_english(List, English) :- 136 | atomics_to_string(List, '\n', English). 137 | -------------------------------------------------------------------------------- /fairy.pl: -------------------------------------------------------------------------------- 1 | /* 2 | * 3 | * Copyright 2018, Anne Ogborn 4 | 5 | Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 6 | 7 | 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 8 | 9 | 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 10 | 11 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 12 | */ 13 | :- module(fairy, []). 14 | 15 | :- multifile planner:max_plan_len/2. 16 | 17 | planner:max_plan_len(fairy, 12). 18 | 19 | action(bake_pie, 20 | action{ 21 | pre: [loc(home), has_flour, has_berries], 22 | negpre: [], 23 | add: [has_pie], 24 | remove: [has_flour, has_berries], 25 | desc: [$0, used, the, flour, and, berries, 26 | to, bake, a, delicious, pie] 27 | }). 28 | action(walk_to_woods, 29 | action{ 30 | pre: [loc(home)], 31 | negpre: [wolf], 32 | add: [loc(woods)], 33 | remove: [loc(_)], 34 | desc: [$0, walked, deep, into, the, woods] 35 | }). 36 | action(walk_to_grannys, 37 | action{ 38 | pre: [loc(woods)], 39 | negpre: [wolf], 40 | add: [loc(grannys)], 41 | remove: [loc(_)], 42 | desc: [$0, walked, to, grannys, house] 43 | }). 44 | action(greet_by_granny, 45 | action{ 46 | pre: [loc(grannys)], 47 | negpre: [], 48 | add: [saw_granny], 49 | remove: [], 50 | desc: [$0, saw, her, granny] 51 | }). 52 | action(leave_grannys, 53 | action{ 54 | pre: [loc(grannys)], 55 | negpre: [], 56 | add: [loc(woods)], 57 | remove: [loc(_)], 58 | desc: [$0, walked, into, the, woods, headed, home] 59 | }). 60 | action(arrive_home, 61 | action{ 62 | pre: [loc(woods)], 63 | negpre: [wolf], 64 | add: [loc(home)], 65 | remove: [loc(_)], 66 | desc: [$0, arrived, home] 67 | }). 68 | 69 | -------------------------------------------------------------------------------- /fairystory.graphml: -------------------------------------------------------------------------------- 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | 10 | 11 | 12 | 13 | 14 | 15 | 16 | 17 | 18 | 19 | 20 | 21 | 22 | 23 | 24 | start 25 | 26 | 27 | 28 | 29 | 30 | 31 | 32 | 33 | 34 | 35 | 36 | 37 | 38 | 39 | 40 | 41 | 42 | woods 43 | 44 | 45 | 46 | 47 | 48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 | 58 | 59 | 60 | grannies 61 | 62 | 63 | 64 | 65 | 66 | 67 | 68 | 69 | 70 | 71 | 72 | 73 | 74 | 75 | 76 | 77 | 78 | has_pie 79 | 80 | 81 | 82 | 83 | 84 | 85 | 86 | 87 | 88 | 89 | 90 | 91 | 92 | 93 | 94 | 95 | 96 | bake_pie 97 | 98 | 99 | 100 | 101 | 102 | 103 | 104 | 105 | 106 | 107 | 108 | 109 | 110 | 111 | 112 | 113 | 114 | 115 | walk_to_woods 116 | 117 | 118 | 119 | 120 | 121 | 122 | 123 | 124 | 125 | 126 | 127 | 128 | 129 | 130 | 131 | 132 | 133 | 134 | walk_to_grannies 135 | 136 | 137 | 138 | 139 | 140 | 141 | 142 | 143 | 144 | 145 | 146 | 147 | 148 | 149 | 150 | 151 | 152 | 153 | 154 | 155 | saw_granny 156 | 157 | 158 | 159 | 160 | 161 | 162 | 163 | 164 | 165 | 166 | 167 | 168 | 169 | 170 | 171 | 172 | 173 | 174 | 175 | 176 | leave_grannies 177 | 178 | 179 | 180 | 181 | 182 | 183 | 184 | 185 | 186 | 187 | 188 | 189 | 190 | 191 | 192 | 193 | 194 | 195 | 196 | 197 | 198 | arrive_home 199 | 200 | 201 | 202 | 203 | 204 | 205 | 206 | 207 | 208 | 209 | 210 | 211 | 212 | 213 | 214 | 215 | 216 | 217 | walk_to_woods 218 | 219 | 220 | 221 | 222 | 223 | 224 | 225 | 226 | 227 | 228 | 229 | 230 | 231 | 232 | 233 | 234 | -------------------------------------------------------------------------------- /fairystory.png: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/SWI-Prolog-Education/talespin-annie/d750de657fdf5657d36e68835115c8d12ac7f2c6/fairystory.png -------------------------------------------------------------------------------- /planner.pl: -------------------------------------------------------------------------------- 1 | /* Part of SWI-Prolog 2 | 3 | Author: Anne Ogborn 4 | E-mail: anne@swi-prolog.org 5 | WWW: http://www.swi-prolog.org 6 | Copyright (c) 2018, Anne Ogborn 7 | All rights reserved. 8 | 9 | Redistribution and use in source and binary forms, with or without 10 | modification, are permitted provided that the following conditions 11 | are met: 12 | 13 | 1. Redistributions of source code must retain the above copyright 14 | notice, this list of conditions and the following disclaimer. 15 | 16 | 2. Redistributions in binary form must reproduce the above copyright 17 | notice, this list of conditions and the following disclaimer in 18 | the documentation and/or other materials provided with the 19 | distribution. 20 | 21 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 | "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 | LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 | FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 | COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 | INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 | BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 | LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 | CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 | LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 | ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 | POSSIBILITY OF SUCH DAMAGE. 33 | */ 34 | :- module(planner, [ 35 | plan/4, 36 | apply_action_dict/3 37 | ]). 38 | /** A STRIPS type planner. 39 | * 40 | * This planner depends on action modules, called 'genres', as sets 41 | * of actions. See 42 | * the 'fairy.pl' example for format. 43 | * 44 | * 45 | */ 46 | :- license(bsd). 47 | 48 | % ! plan(+InitConditions:list, +Genre:atom, -Plan:list, +Options:list) 49 | % ! is nondet 50 | % 51 | % Given a set of initial conditions and a Genre, generate different 52 | % plans on backtracking 53 | % 54 | % @arg InitConditions is a list of conditions at the start. Goals 55 | % should be listed as goal(X), and when all X appear in the conditions, 56 | % planning terminates 57 | % @arg Genre is an atomic genre, allowing actions to be defined for 58 | % different genres. 59 | % @arg Plan - a list of action names 60 | % @arg Options - the only available options are order(random) 61 | % (default), which randomizes at each step, and order(first), which 62 | % takes actions in lexical order 63 | % 64 | plan(InitConditions, Genre, Plan, Options) :- 65 | ( member(order(Order), Options) 66 | ; Order = random 67 | ), 68 | list_to_ord_set(InitConditions, OrdCond), 69 | plan_(Genre, 70 | Order, 71 | /*Open*/ [OrdCond-[]], 72 | /* Closed*/[OrdCond], 73 | RPlan), 74 | reverse(RPlan, Plan). 75 | 76 | % Genre is the *|module name|* of the actions 77 | % Order is the argument of the order/1 option 78 | % Open is a list of nodes to explore, as State-Story pairs 79 | % Closed is a list of states to never again put on Open 80 | % RPlan is the plan, with the last action first, 81 | % 82 | % if the Open list is exhausted, 83 | plan_(_, _, [], _, _) :- 84 | !, 85 | fail. 86 | % 87 | % if we've reached a goal state we have a solution. 88 | plan_(_Genre, 89 | _Order, 90 | [State-Story |_], 91 | _Closed, 92 | Story) :- 93 | debug(planner(current), '~q ~q', [State, Story]), 94 | at_goal(State). 95 | % if we have a shaggy dog story, discard from Open 96 | plan_(Genre, 97 | Order, 98 | [_State-Story | Open], 99 | Closed, 100 | FullStory) :- 101 | length(Story, Len), 102 | ( max_plan_len(Genre, MaxLen) 103 | *-> true 104 | ; MaxLen = 18 105 | ), 106 | Len > MaxLen, 107 | plan_(Genre, Order, Open, Closed, FullStory). 108 | % process head of Open 109 | plan_(Genre, 110 | Order, 111 | [State-Story | Open], 112 | Closed, 113 | FullStory) :- 114 | ordered_possible_action_states(State, Genre, Order, PossibleActions), 115 | actions_children(State, Genre, PossibleActions, Children), 116 | add_unclosed_children_to_open(Story, 117 | Closed, 118 | PossibleActions, 119 | Children, % list of states 120 | Open, 121 | Open1), 122 | add_unique( 123 | Closed, 124 | Children, 125 | Closed1), 126 | plan_(Genre, Order, Open1, [State | Closed1], FullStory). 127 | 128 | 129 | %! ordered_possible_action_states(+State:state, +Genre:atom, 130 | %! +Order:atom, -Possible:list) is det 131 | % 132 | % Give a state list and Genre, return the possible actions 133 | % as a list of action names, sorted in order found if Order=first 134 | % and in random order if Order=random 135 | % 136 | ordered_possible_action_states(State, 137 | Genre, 138 | Order, 139 | Possible) :- 140 | possible_actions(State, Genre, RawPossible), 141 | ( Order = random 142 | -> random_permutation(RawPossible, Possible) 143 | ; RawPossible = Possible 144 | ). 145 | 146 | 147 | %! add_unclosed_children_to_open(+Story:listpair, +Closed:list, 148 | %! +Actions:list, +Children:list, +OpenIn:list, 149 | %! -OpenOut:list) is det 150 | % 151 | % True when OpenOut is the new Open list resulting from adding 152 | % the State-Story pairs in Children to the open list, 153 | % discarding those already in the closed list. 154 | % 155 | % @arg Story the current story so far 156 | % @arg Closed list of States we should ignore 157 | % @arg Actions list of actions that got the children in Children 158 | % @arg Children list of States resulting from the current state via 159 | % the action in the corresponding position of Actions 160 | % @arg OpenIn list of State-Story pairs not yet processed, to be added 161 | % to 162 | % @arg OpenOut the new Open, after adding the Children with the stories 163 | % 164 | % we have no more children to add 165 | add_unclosed_children_to_open( _Story, 166 | _Closed, 167 | _, % action 168 | [], % children 169 | Open, 170 | Open) :- 171 | !. % green 172 | % in the closed set 173 | add_unclosed_children_to_open( Story, 174 | Closed, 175 | [_Action | Actions], 176 | [Child | Children], 177 | Open, 178 | OpenOut) :- 179 | memberchk(Child, Closed), % its in the closed set 180 | !, % green 181 | add_unclosed_children_to_open(Story, 182 | Closed, 183 | Actions, 184 | Children, 185 | Open, 186 | OpenOut). 187 | % already in the open set 188 | add_unclosed_children_to_open( Story, 189 | Closed, 190 | [Action | Actions], 191 | [Child | Children], 192 | Open, 193 | OpenOut) :- 194 | memberchk(Child-_, Open), % it's already in the open set 195 | debug(planner(dup_open), '~q', [Child-[Action | Story]]), 196 | !, % green 197 | add_unclosed_children_to_open(Story, 198 | Closed, 199 | Actions, 200 | Children, 201 | Open, 202 | OpenOut). 203 | % main case 204 | add_unclosed_children_to_open( Story, 205 | Closed, 206 | [Action | Actions], 207 | [Child | Children], 208 | Open, 209 | OpenOut) :- 210 | append(Open, [Child-[Action | Story]], OpenX), 211 | !, % green 212 | add_unclosed_children_to_open(Story, 213 | Closed, 214 | Actions, 215 | Children, 216 | OpenX, 217 | OpenOut). 218 | 219 | % ! add_unique(+In:list, +New:list, 220 | %! -Out:list) is det 221 | % 222 | % prepend those elements of New which are not in 223 | % the In set. Elements of New are added in reverse order, 224 | % and second occurances of elements of New are ignored. 225 | % 226 | add_unique(In, [], In) :- 227 | !. % green 228 | add_unique(In, [NewH| New], Out) :- 229 | memberchk(NewH, In), 230 | !, % green 231 | add_unique(In, New, Out). 232 | add_unique(In, [NewH| New], [NewH | Out]) :- 233 | add_unique(In, New, Out). 234 | 235 | %! at_goal(+State:list) is det 236 | % 237 | % succeeds if we're at the final goal 238 | % 239 | at_goal(Cond) :- 240 | check_goals(Cond, Cond), 241 | !. % green 242 | 243 | check_goals([], _). 244 | check_goals([goal(Goal)|T], Cond) :- 245 | memberchk(Goal, Cond), 246 | check_goals(T, Cond). 247 | check_goals([H|T], Cond) :- 248 | H \= goal(_), 249 | check_goals(T, Cond). 250 | 251 | %! possible_actions(+Cond:list, +Genre:atom, -Possible) is det 252 | % 253 | % succeeds when Possible is the list of actions that can be performed 254 | % from Cond using Genre as the action list. 255 | % 256 | possible_actions(Cond, Genre, Possible) :- 257 | findall(Name, possible_action(Cond, Genre, Name), Possible). 258 | 259 | possible_action(Cond, Genre, Name) :- 260 | Genre:action(Name, Act), 261 | action{ pre:Pre, 262 | negpre: NegPre 263 | } :< Act, 264 | maplist(is_in(Cond), Pre), 265 | maplist(not_in(Cond), NegPre). 266 | 267 | % famulus to swap memberchk's args 268 | is_in(List, Member) :- 269 | memberchk(Member, List). 270 | 271 | not_in(List, Member) :- 272 | \+ memberchk(Member, List). 273 | 274 | %! actions_children(+State:list, 275 | %! +Genre:list, 276 | %! +PossibleActions:list, 277 | %! -Children:list) is det 278 | % 279 | % succeeds when Children is a list of new states resulting 280 | % from applying the members of PossibleActions to State 281 | % 282 | % @arg State the current state 283 | % @arg Genre the module name of the actions 284 | % @arg PossibleActions a list of atom action names. Assumed possible 285 | % @arg Children The subsequent states 286 | % 287 | actions_children(State, Genre, PossibleActions, Children) :- 288 | maplist(apply_action(State, Genre), PossibleActions, Children). 289 | 290 | apply_action(State, Genre, Name, NewState) :- 291 | Genre:action(Name, Action), 292 | apply_action_dict(State, Action, NewState). 293 | 294 | apply_action_dict(State, Action, NewState) :- 295 | action{ 296 | add: Add, 297 | remove: Remove 298 | } :< Action, 299 | my_subtract(State, Remove, S1), 300 | list_to_ord_set(Add, OrdAdd), 301 | ord_union(S1, OrdAdd, NewState). 302 | 303 | %! my_subtract(+A:list, +B:list, -C:list) is det 304 | % 305 | % ord_subtract uses the standard term order, which isn't happy 306 | % when we have a not fully ground term. To avoid it, we build our 307 | % own subtract 308 | % 309 | % Succeeds when C = A - B as set operation, where A must be ground 310 | % and B possibly contains partially ground elements which remove 311 | % all elements of A they unify with 312 | % 313 | my_subtract([], _, []). 314 | my_subtract([H|T], Remove, TOut) :- 315 | memberchk(H, Remove), 316 | !, 317 | my_subtract(T, Remove, TOut). 318 | my_subtract([H|T], Remove, [H|TOut]) :- 319 | my_subtract(T, Remove, TOut). 320 | 321 | 322 | :- multifile planner:max_plan_len/2. 323 | 324 | max_plan_len(nothing, 18). 325 | -------------------------------------------------------------------------------- /plannerb4refactor.pl: -------------------------------------------------------------------------------- 1 | :- module(planner, [ 2 | plan/4 3 | ]). 4 | /** A planner. 5 | * 6 | * Released under the terms of the SWI-Prolog license 7 | * 8 | * The planner depends on action modules, called 'genres' 9 | * 10 | * 11 | */ 12 | 13 | % ! plan(+InitConditions:list, +Genre:atom, -Plan:list, +Options:list) 14 | % ! is nondet 15 | % 16 | % Given a set of initial conditions and a Genre, generate random plans 17 | % on backtracking 18 | % 19 | % @arg InitConditions is a list of conditions at the start. Goals 20 | % should be listed as goal(X), and when all X appear in the conditions, 21 | % planning terminates 22 | % @arg Genre is an atomic genre, allowing actions to be defined for 23 | % different genres. 24 | % @arg Plan - a list of action names 25 | % @arg Options - the only available options are order(random) 26 | % (default), which randomizes at each step, and order(first), which 27 | % takes actions in lexical order 28 | % 29 | plan(InitConditions, Genre, Plan, Options) :- 30 | ( member(order(Order), Options) 31 | ; Order = random 32 | ), 33 | empty_queue, 34 | list_to_ord_set(InitConditions, OrdCond), 35 | plan_(Genre, 36 | Order, 37 | /*Open*/ [OrdCond], 38 | /* Closed*/[OrdCond], 39 | RPlan), 40 | reverse(RPlan, Plan). 41 | 42 | % Genre is the module of the actions 43 | % Order is the argument of the order/1 option 44 | % Open is a list of nodes to explore, as State-Story pairs 45 | % Closed is a list of nodes to never again put on Open 46 | % RPlan is the plan, with the last action first 47 | % 48 | % if the Open list is exhausted, 49 | plan_(_, _, [], _, _) :- 50 | !, 51 | fail. 52 | % 53 | % if we've reached a goal state we have a solution. 54 | plan_(_Genre, 55 | _Order, 56 | [State-Story |_], 57 | _Closed, 58 | Story) :- 59 | at_goal(State). 60 | plan_(Genre, 61 | Order, 62 | [State-Story | Open], 63 | Closed, 64 | FullStory) :- 65 | ordered_possible_action_states(State-Story, Genre, Order, Possible), 66 | add_unique_children_to_open(State-Story, Genre, Possible, Open, Open1), 67 | plan_(Genre, Order, Open1, [State | Closed], FullStory). 68 | 69 | 70 | 71 | plan_(Cond, _Genre, Prev, _, _, _) :- 72 | member(Cond, Prev), % we've been here before 73 | !, 74 | fail. 75 | plan_(Cond, Genre, _Prev, _SoFar, _Plan, _Order) :- 76 | possible_actions(Cond, Genre, []), % no move from here 77 | !, 78 | fail. 79 | plan_(Cond, _, _, _, _, _) :- 80 | member(dead, Cond), % dead end 81 | !, 82 | fail. 83 | plan_(Cond, Genre, Prev, SoFar, Plan, Order) :- 84 | add_queue(SoFar, Cond), 85 | pop_queue(FirstSoFar, FirstCond), 86 | possible_actions(FirstCond, Genre, RawPossible), 87 | ( Order = random 88 | -> once(random_permutation(RawPossible, Possible)) 89 | ; RawPossible = Possible 90 | ), 91 | member(Action, Possible), 92 | apply_action(Action, FirstCond, Genre, NewCond), 93 | debug(planner(action), '~w', [Action]), 94 | debug(planner(step), '~w ~w ~w', [FirstCond, Action, NewCond]), 95 | plan_(NewCond, Genre, [Cond | Prev], [Action | FirstSoFar], Plan, Order). 96 | 97 | at_goal(Cond) :- 98 | check_goals(Cond, Cond), 99 | !. % green 100 | 101 | check_goals(_, []). 102 | check_goals([goal(Goal)|T], Cond) :- 103 | memberchk(Goal, Cond), 104 | check_goals(T, Cond). 105 | check_goals([H|T], Cond) :- 106 | H \= goal(_), 107 | check_goals(T, Cond). 108 | 109 | possible_actions(Cond, Genre, Possible) :- 110 | findall(Name, possible_action(Cond, Genre, Name), Possible). 111 | 112 | possible_action(Cond, Genre, Name) :- 113 | Genre:action(Name, Act), 114 | action{ pre:Pre, 115 | negpre: NegPre 116 | } :< Act, 117 | maplist(is_in(Cond), Pre), 118 | maplist(not_in(Cond), NegPre). 119 | 120 | is_in(List, Member) :- 121 | memberchk(Member, List). 122 | 123 | not_in(List, Member) :- 124 | \+ memberchk(Member, List). 125 | 126 | :- dynamic q/2. % q(PlanSoFar, CurrentCondition) 127 | 128 | empty_queue :- 129 | retractall(q(_,_)). 130 | 131 | add_queue(PartialPlan, Cond) :- 132 | assertz(q(PartialPlan, Cond)). 133 | 134 | pop_queue(PartialPlan, Cond) :- 135 | once(q(PartialPlan, Cond)), 136 | retractall(q(PartialPlan, Cond)). 137 | 138 | apply_action(Name, Cond, Genre, NewCond) :- 139 | Genre:action(Name, Action), 140 | action{ 141 | add: Add, 142 | remove: Remove 143 | } :< Action, 144 | my_subtract(Cond, Remove, C1), 145 | list_to_ord_set(Add, OrdAdd), 146 | ord_union(C1, OrdAdd, NewCond). 147 | 148 | 149 | my_subtract([], _, []). 150 | my_subtract([H|T], Remove, TOut) :- 151 | memberchk(H, Remove), 152 | !, 153 | my_subtract(T, Remove, TOut). 154 | my_subtract([H|T], Remove, [H|TOut]) :- 155 | my_subtract(T, Remove, TOut). 156 | 157 | -------------------------------------------------------------------------------- /project.odp: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/SWI-Prolog-Education/talespin-annie/d750de657fdf5657d36e68835115c8d12ac7f2c6/project.odp -------------------------------------------------------------------------------- /run.pl: -------------------------------------------------------------------------------- 1 | :- module(run, [print_story/0]). 2 | 3 | :-use_module(talespin). 4 | :-use_module(anglify). 5 | :-use_module(fairy). 6 | :-use_module(snail). 7 | 8 | /* 9 | * 10 | * Copyright 2018, Anne Ogborn 11 | 12 | Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 13 | 14 | 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 15 | 16 | 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 17 | 18 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 19 | */ 20 | 21 | 22 | go(E) :- 23 | snail:init_conditions(S), 24 | story(S, snail, [], Story), 25 | print_term(Story, []), 26 | anglify(Story, E). 27 | 28 | print_story :- 29 | go(E), 30 | writeln(E). 31 | -------------------------------------------------------------------------------- /snail.pl: -------------------------------------------------------------------------------- 1 | /* 2 | * 3 | * Copyright 2018, Anne Ogborn 4 | 5 | Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 6 | 7 | 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 8 | 9 | 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 10 | 11 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 12 | */ 13 | :- module(snail, 14 | /*[action/2, 15 | event/3, 16 | init_conditions/1, 17 | friend_desc/3, 18 | place_desc/3]). */ 19 | []). 20 | /** snail stories 21 | * 22 | * These are parables, with different messages 23 | * TBD - haven't made all these 24 | * 25 | * 1) having fun with your friends is more important than accomplishing 26 | * an unimportant goal 27 | * 28 | * 2) when you hurt someone you have to say you're sorry 29 | * 30 | * 3) helping your friends 31 | * 32 | * 4) don't laugh at people because they're different 33 | * someone laughs at someone's difference, and they run away. 34 | * they are told it's wrong, and they hunt down the victim and 35 | * apologize 36 | * 37 | * 5) being sad is part of life. 38 | * someone is sad, and they meet a friend and the friend is nice to 39 | * them and they feel better. 40 | * 41 | * 6) it's OK to ask for help 42 | * Snail finds a rock under their tomato 43 | * plant while they're away. Only beetle is able to move the rock. 44 | * 45 | * 46 | */ 47 | :- discontiguous action/2, event/3, add_event/2. 48 | 49 | :- multifile planner:max_plan_len/2. 50 | 51 | planner:max_plan_len(snail, 12). 52 | 53 | init_conditions([not_inited, goal(has_goals)]). 54 | 55 | /******************************* 56 | * Initialization 57 | *******************************/ 58 | 59 | action(initialize, 60 | action{ 61 | pre: [not_inited], 62 | negpre: [stuck], 63 | add: [has_goals, theme(Message), 64 | loc(tomato), 65 | loc(tomato, ball), 66 | goal(attended_tea_party), 67 | goal(loc(tomato))], 68 | remove: [not_inited], 69 | desc: [theme(Message), start_message(['One day ', $0, ' was invited to a tea party put on by froggy amidst the mushrooms.'])] 70 | }) :- 71 | theme(Message). 72 | 73 | /******************************* 74 | * Movement 75 | *******************************/ 76 | 77 | action(move(A, B), 78 | action{ 79 | pre: [loc(A)], 80 | negpre: [stuck, blocked(B)], % blocked(B) means we know B is blocke 81 | add: [loc(B)], 82 | remove: [loc(A)], 83 | desc: [moveall(A,B)] 84 | }) :- 85 | uroute(A,B). 86 | 87 | % a random friend joins the party 88 | event(move(A, B), 89 | 0.02, 90 | action{ 91 | pre:[], 92 | negpre:[party(C)], % event cant happen if C is in party already 93 | add: [party(C), loc(B)], 94 | remove: [loc(A)], 95 | desc: [join_party(C), moveall(A,B)] 96 | }) :- 97 | can_join_party(C). 98 | 99 | 100 | /******************************* 101 | * The Rock * 102 | *******************************/ 103 | 104 | % a stone blocks the way 105 | % can only happen once 106 | event(move(_,B), 107 | 0.2, 108 | action{ 109 | pre:[], 110 | negpre: [blocked(B), has_been_blocked(stone)], 111 | add: [blocked(B), blocked_by(stone), has_been_blocked(stone)], 112 | remove: [], 113 | desc: [blocked_by(B, stone)] 114 | }). 115 | 116 | action(remove_by_friend(stone), 117 | action{ 118 | pre: [loc(A), blocked(B), blocked_by(stone), party(Friend)], 119 | negpre: [], 120 | add: [helped(Friend)], 121 | remove: [blocked(B), blocked_by(stone), had_adventure], 122 | desc: [unblocked(Friend, stone)] 123 | }) :- 124 | uroute(A,B), 125 | strong(Friend). 126 | action(remove_by_gardner(stone), 127 | action{ 128 | pre: [loc(A), blocked(B), blocked_by(stone), gardener], 129 | negpre: [], 130 | add: [gardener_threw_stone], 131 | remove: [blocked(B), blocked_by(stone)], 132 | desc: [gardener_threw_stone] 133 | }) :- 134 | uroute(A,B). 135 | 136 | /******************************* 137 | * Pomatia's ball * 138 | *******************************/ 139 | 140 | event(move(tomato,NewLoc), 141 | 0.5, 142 | action{ 143 | pre: [loc(tomato), loc(tomato, ball)], 144 | negpre: [carried(ball)], 145 | add: [loc(NewLoc), carried(ball), goal(has_played)], 146 | remove: [loc(tomato), loc(_, ball)], 147 | desc: [take_ball, moveall(tomato, NewLoc)] 148 | }) :- 149 | uroute(tomato, NewLoc). 150 | 151 | action(play_ball, 152 | action{ 153 | pre: [carried(ball)], 154 | negpre: [gardener, has_played], 155 | add: [has_played], 156 | remove: [], 157 | desc: [play_ball] 158 | }). 159 | 160 | % lose the ball in the water 161 | % % crummy event because we're unlikely to play with ball near water 162 | event(play_ball, 163 | 1.0, 164 | action{ 165 | pre:[loc(pond), carried(ball)], 166 | negpre: [has_lost_ball], 167 | add: [has_lost_ball, ball_in_water, goal(carried(ball))], 168 | remove: [carried(ball)], 169 | desc: [lost_ball_in_water] 170 | }). 171 | 172 | 173 | action(recover_ball, 174 | action{ 175 | pre: [loc(pond), ball_in_water], 176 | negpre: [], 177 | add: [carried(ball)], 178 | remove: [ball_in_water], 179 | desc: [recover_ball_from_water] 180 | }). 181 | 182 | /******************************* 183 | * Universal Events * 184 | *******************************/ 185 | 186 | 187 | % we have events that apply any time and don't interfere with the 188 | % original action. 189 | event(OrigAction, 190 | Prob, 191 | action{ 192 | pre: EPre, 193 | negpre: ENegPre, 194 | add: TotalAdd, 195 | remove: TotalRemove, 196 | desc: TotalDesc 197 | }) :- 198 | add_event(Prob, 199 | action{ 200 | pre: EPre, 201 | negpre: ENegPre, 202 | add: EAdd, 203 | remove: ERemove, 204 | desc: EDesc 205 | }), 206 | action(OrigAction, ActionDict), 207 | append(ActionDict.add, EAdd, TotalAdd), 208 | append(ActionDict.remove, ERemove, TotalRemove), 209 | append(ActionDict.desc, EDesc, TotalDesc). 210 | 211 | /******************************* 212 | * The Gardener 213 | *******************************/ 214 | 215 | % the gardener appears. 216 | add_event( 217 | 0.1, 218 | action{ 219 | pre: [], 220 | negpre: [gardener], 221 | add: [gardener, had_adventure, gardener_has_appeared], 222 | remove: [], 223 | desc: [gardener_appears] 224 | }). 225 | 226 | % the gardener leaves 227 | add_event( 228 | 0.1, 229 | action{ 230 | pre: [gardener], 231 | negpre: [], 232 | add: [], 233 | remove: [gardener], 234 | desc: [gardener_leaves] 235 | }). 236 | 237 | /******************************* 238 | * The tea party 239 | *******************************/ 240 | 241 | action(tea_party, 242 | action{ 243 | pre: [loc(mushrooms)], 244 | negpre: [], 245 | add: [attended_tea_party], 246 | remove: [], 247 | desc: [attended_tea_party] 248 | }). 249 | 250 | event(tea_party, 251 | 0.4, 252 | action{ 253 | pre:[loc(mushrooms), gardener_has_appeared], 254 | negpre: [mushrooms_gone, saved_froggy_home], 255 | add: [mushrooms_gone, goal(saved_froggy_home)], 256 | remove: [goal(attended_tea_party)], 257 | desc: [mushrooms_gone] 258 | }). 259 | 260 | /******************************* 261 | * Froggy's home * 262 | *******************************/ 263 | 264 | action(magic_fix, 265 | action{ 266 | pre: [mushrooms_gone, goal(saved_froggy_home)], 267 | negpre: [], 268 | add: [saved_froggy_home], 269 | remove: [goal(saved_froggy_home), mushrooms_gone], 270 | desc: [magic_mushrooms_fix] 271 | }). 272 | 273 | 274 | theme(help). % Friends help each other 275 | % theme(friends_before_things). 276 | % theme(friends_before_activities). 277 | % theme(apologizing). 278 | 279 | /******************************* 280 | * Routes around the garden * 281 | * Places Pomatia and friends * 282 | * go in their garden world * 283 | *******************************/ 284 | 285 | route(tomato, sidewalk). 286 | route(tomato, weed). 287 | route(sidewalk, weed). 288 | route(sidewalk, pond). 289 | route(pond, ants). 290 | route(mushrooms, pond). 291 | 292 | place_desc(tomato, 'Pomatia\'s cozy tomato plant', 293 | 'Pomatia\'s home, a sturdy tomato plant in a shady part of the garden'). 294 | place_desc(sidewalk, 'the garden path', 295 | 'the brick path that wound through the garden'). 296 | place_desc(weed, 'the large weed', 297 | 'a large weed that Mrs. Cratchet never seemed to pull'). 298 | place_desc(pond, 'the ornamental pond', 299 | 'a nice ornamental pond, with a little fountain, and lily pads that Froggy loved'). 300 | place_desc(ants, 'the anthill', 301 | 'a large anthill in a corner of the garden, home to the busy ants'). 302 | place_desc(mushrooms, 'the mushrooms', 303 | 'a large group of mushrooms under a willow tree, where Mr. Froggy lived'). 304 | 305 | uroute(A,B) :- route(A,B). 306 | uroute(A,B) :- route(B,A). 307 | 308 | /******************************* 309 | * Friends * 310 | * 311 | * Pomatia's friends. Pomatia * 312 | * froggy, and Mrs. Cratchet * 313 | * handled special * 314 | *******************************/ 315 | 316 | 317 | % only friends who can join the party 318 | friend(beetle). 319 | friend(grasshopper). 320 | friend(worm). 321 | friend(ladybug). 322 | can_join_party(X) :- member(X, [beetle, grasshopper, worm, ladybug]). 323 | 324 | friend_desc(beetle, 'Beetle', 325 | 'Beetle, a large and iridescent blue-green beetle'). 326 | friend_desc(grasshopper, 'Hopper', 327 | 'Hopper, a rather nervous grasshopper'). 328 | friend_desc(worm, 'Wormy', 329 | 'Wormy, a nice chubby, jolly earthworm'). 330 | friend_desc(ladybug, 'Miss Priscilla', 331 | 'Miss Priscilla, a very dainty (and quite fashionable) ladybug'). 332 | friend_desc(cratchet, 'Mrs. Cratchet came back out to the garden.', 333 | 'Suddenly old Mrs. Cratchet, who owned the garden, appeared! All the creatures were afraid of Ms. Cratchet, who threw stones at them.'). 334 | 335 | strong(beetle). 336 | strong(worm). 337 | 338 | % use botanicula for friend can help ideas 339 | % spiders make ropes, beetles move heavy things 340 | % grasshoppers jump 341 | % ladybug has no 'special powers' but is good at emotional work 342 | 343 | 344 | % make the child a rock saver - 'but I'm little', 'to us you are big' 345 | % it could rain 346 | % don't forget emotional action is action 347 | % has a tummy ache that turns out to be an egg(??) 348 | % Pomatia loses their ball in the lily pond. 349 | 350 | % Pomatia could find lose their ball in the pond 351 | -------------------------------------------------------------------------------- /snailgarden.graphml: -------------------------------------------------------------------------------- 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | 10 | 11 | 12 | 13 | 14 | 15 | 16 | 17 | 18 | 19 | 20 | 21 | 22 | 23 | 24 | Tomato Plant 25 | (Snail's home) 26 | 27 | 28 | 29 | 30 | 31 | 32 | 33 | 34 | 35 | 36 | 37 | 38 | 39 | 40 | 41 | 42 | 43 | The sidewalk 44 | 45 | 46 | 47 | 48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 | 58 | 59 | 60 | 61 | The big 62 | weed 63 | 64 | 65 | 66 | 67 | 68 | 69 | 70 | 71 | 72 | 73 | 74 | 75 | 76 | 77 | 78 | 79 | 80 | The celery 81 | (a food snail likes) 82 | 83 | 84 | 85 | 86 | 87 | 88 | 89 | 90 | 91 | 92 | 93 | 94 | 95 | 96 | 97 | 98 | 99 | the ornamental 100 | pond 101 | 102 | 103 | 104 | 105 | 106 | 107 | 108 | 109 | 110 | 111 | 112 | 113 | 114 | 115 | 116 | 117 | 118 | the ants 119 | 120 | 121 | 122 | 123 | 124 | 125 | 126 | 127 | 128 | 129 | 130 | 131 | 132 | 133 | 134 | 135 | 136 | The mushrooms 137 | (picnic location) 138 | 139 | 140 | 141 | 142 | 143 | 144 | 145 | 146 | 147 | 148 | 149 | 150 | 151 | 152 | 153 | 154 | 155 | 156 | 157 | 158 | 159 | 160 | 161 | 162 | 163 | 164 | 165 | 166 | 167 | 168 | 169 | 170 | 171 | 172 | 173 | 174 | 175 | 176 | 177 | 178 | 179 | 180 | 181 | 182 | 183 | 184 | 185 | 186 | 187 | 188 | 189 | 190 | 191 | 192 | 193 | 194 | 195 | 196 | 197 | 198 | 199 | 200 | 201 | 202 | 203 | 204 | 205 | 206 | 207 | 208 | 209 | 210 | 211 | 212 | 213 | 214 | 215 | 216 | 217 | 218 | 219 | 220 | 221 | 222 | 223 | 224 | 225 | 226 | 227 | 228 | 229 | 230 | 231 | 232 | 233 | 234 | 235 | 236 | 237 | 238 | 239 | 240 | 241 | 242 | 243 | 244 | -------------------------------------------------------------------------------- /states.graphml: -------------------------------------------------------------------------------- 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | 10 | 11 | 12 | 13 | 14 | 15 | 16 | 17 | 18 | 19 | 20 | 21 | 22 | 23 | 24 | Horizontal Swim Lanes 25 | start 26 | 27 | 28 | 29 | 30 | 31 | 32 | layer 1 33 | 34 | 35 | 36 | 37 | 38 | 39 | layer 2 40 | 41 | 42 | 43 | 44 | 45 | 46 | layer 3 47 | 48 | 49 | 50 | 51 | 52 | 53 | layer 4 54 | 55 | 56 | 57 | 58 | 59 | 60 | layer 5 61 | 62 | 63 | 64 | 65 | 66 | 67 | layer 6 68 | 69 | 70 | 71 | 72 | 73 | 74 | 75 | 76 | 77 | 78 | 79 | 80 | 81 | 82 | 83 | 84 | 85 | 86 | 87 | 88 | 89 | 90 | 91 | 92 | 93 | 94 | 95 | 96 | 97 | 98 | 99 | 100 | 101 | 102 | 103 | 104 | 105 | 106 | 107 | 108 | 109 | 110 | 111 | 112 | 113 | 114 | 115 | 116 | 117 | 118 | 119 | 120 | 121 | 122 | 123 | 124 | 125 | 126 | 127 | 128 | 129 | Start State 130 | 131 | 132 | 133 | 134 | 135 | 136 | 137 | 138 | 139 | 140 | 141 | 142 | 143 | 144 | 145 | 146 | 147 | at_grannys 148 | 149 | 150 | 151 | 152 | 153 | 154 | 155 | 156 | 157 | 158 | 159 | 160 | 161 | 162 | 163 | 164 | 165 | at_grannys 166 | 167 | 168 | 169 | 170 | 171 | 172 | 173 | 174 | 175 | 176 | 177 | 178 | 179 | 180 | 181 | 182 | 183 | at_home 184 | 185 | 186 | 187 | 188 | 189 | 190 | 191 | 192 | 193 | 194 | 195 | 196 | 197 | 198 | 199 | 200 | 201 | at_home 202 | 203 | 204 | 205 | 206 | 207 | 208 | 209 | 210 | 211 | 212 | 213 | 214 | 215 | 216 | 217 | 218 | 219 | at_home 220 | 221 | 222 | 223 | 224 | 225 | 226 | 227 | 228 | 229 | 230 | 231 | 232 | 233 | 234 | 235 | 236 | 237 | at_home 238 | 239 | 240 | 241 | 242 | 243 | 244 | 245 | 246 | 247 | 248 | 249 | 250 | 251 | 252 | 253 | 254 | 255 | at_home 256 | 257 | 258 | 259 | 260 | 261 | 262 | 263 | 264 | 265 | 266 | 267 | 268 | 269 | 270 | 271 | 272 | 273 | happy_granny 274 | 275 | 276 | 277 | 278 | 279 | 280 | 281 | 282 | 283 | 284 | 285 | 286 | 287 | 288 | 289 | 290 | 291 | happy_granny 292 | 293 | 294 | 295 | 296 | 297 | 298 | 299 | 300 | 301 | 302 | 303 | 304 | 305 | 306 | 307 | 308 | 309 | has_pie 310 | 311 | 312 | 313 | 314 | 315 | 316 | 317 | 318 | 319 | 320 | 321 | 322 | 323 | 324 | 325 | 326 | 327 | in_woods 328 | 329 | 330 | 331 | 332 | 333 | 334 | 335 | 336 | 337 | 338 | 339 | 340 | 341 | 342 | 343 | 344 | 345 | in_woods 346 | 347 | 348 | 349 | 350 | 351 | 352 | 353 | 354 | 355 | 356 | 357 | 358 | 359 | 360 | 361 | 362 | 363 | in_woods 364 | 365 | 366 | 367 | 368 | 369 | 370 | 371 | 372 | 373 | 374 | 375 | 376 | 377 | 378 | 379 | 380 | 381 | in_woods 382 | 383 | 384 | 385 | 386 | 387 | 388 | 389 | 390 | 391 | 392 | 393 | 394 | 395 | 396 | 397 | 398 | 399 | in_woods 400 | 401 | 402 | 403 | 404 | 405 | 406 | 407 | 408 | 409 | 410 | 411 | 412 | 413 | 414 | 415 | 416 | 417 | in_woods 418 | 419 | 420 | 421 | 422 | 423 | 424 | 425 | 426 | 427 | 428 | 429 | 430 | 431 | 432 | 433 | 434 | 435 | 436 | 437 | 438 | 439 | 440 | walk_to_woods 441 | 442 | 443 | 444 | 445 | 446 | 447 | 448 | 449 | 450 | 451 | 452 | 453 | 454 | 455 | 456 | 457 | 458 | 459 | 460 | 461 | 462 | 463 | 464 | 465 | 466 | 467 | 468 | 469 | 470 | 471 | 472 | 473 | 474 | 475 | 476 | 477 | 478 | 479 | 480 | 481 | 482 | 483 | 484 | 485 | 486 | 487 | 488 | 489 | 490 | 491 | 492 | 493 | 494 | 495 | 496 | 497 | 498 | 499 | 500 | 501 | 502 | 503 | 504 | 505 | 506 | 507 | 508 | 509 | 510 | 511 | 512 | 513 | 514 | 515 | 516 | 517 | 518 | 519 | 520 | 521 | 522 | 523 | 524 | 525 | 526 | 527 | 528 | 529 | 530 | 531 | 532 | 533 | 534 | 535 | 536 | 537 | 538 | 539 | 540 | 541 | 542 | 543 | 544 | 545 | 546 | 547 | 548 | 549 | 550 | 551 | 552 | 553 | 554 | 555 | 556 | 557 | 558 | 559 | 560 | 561 | 562 | 563 | 564 | 565 | 566 | 567 | 568 | 569 | 570 | 571 | 572 | 573 | 574 | 575 | 576 | 577 | 578 | 579 | 580 | 581 | 582 | 583 | 584 | 585 | 586 | 587 | 588 | 589 | 590 | 591 | 592 | 593 | 594 | 595 | 596 | 597 | 598 | 599 | 600 | 601 | 602 | 603 | 604 | 605 | 606 | 607 | 608 | 609 | 610 | 611 | 612 | 613 | 614 | 615 | 616 | 617 | 618 | 619 | 620 | 621 | 622 | 623 | 624 | 625 | 626 | 627 | 628 | 629 | 630 | 631 | 632 | 633 | 634 | -------------------------------------------------------------------------------- /states.png: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/SWI-Prolog-Education/talespin-annie/d750de657fdf5657d36e68835115c8d12ac7f2c6/states.png -------------------------------------------------------------------------------- /talespin.pl: -------------------------------------------------------------------------------- 1 | /* Part of SWI-Prolog 2 | 3 | Author: Anne Ogborn 4 | E-mail: anne@swi-prolog.org 5 | WWW: http://www.swi-prolog.org 6 | Copyright (c) 2018, Anne Ogborn 7 | All rights reserved. 8 | 9 | Redistribution and use in source and binary forms, with or without 10 | modification, are permitted provided that the following conditions 11 | are met: 12 | 13 | 1. Redistributions of source code must retain the above copyright 14 | notice, this list of conditions and the following disclaimer. 15 | 16 | 2. Redistributions in binary form must reproduce the above copyright 17 | notice, this list of conditions and the following disclaimer in 18 | the documentation and/or other materials provided with the 19 | distribution. 20 | 21 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 | "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 | LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 | FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 | COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 | INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 | BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 | LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 | CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 | LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 | ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 | POSSIBILITY OF SUCH DAMAGE. 33 | */ 34 | :- module(talespin, [ 35 | story/4 36 | ]). 37 | /** implements the Tale-Spin story generation algorithm 38 | * 39 | * 1. Plan 40 | * 2. simulate plan moving forward. Randomly pick 'events', then 41 | * have outcome be event's outcome, not action's outcome. 42 | * 3. following an event, replan 43 | */ 44 | :- use_module(planner). 45 | 46 | %! story(+Init:list, +Genre:atom, +Options:List, -Story:list) is det 47 | % 48 | % @arg Init list of initial conditions 49 | % @arg Genre module name of the story genre 50 | % @arg Options Options list for plan/4 51 | % @arg Story bound to a story as a list of semantic occurances 52 | % 53 | story(Init, Genre, Options, Story) :- 54 | repeat, % because of randomization story_ sometimes fails. 55 | story_(Init, Genre, Options, Story), 56 | !. 57 | story_(Init, Genre, Options, Story) :- 58 | plan(Init, Genre, Plan, Options), 59 | simulate(Init, Genre, Options, Plan, XStory), 60 | flatten(XStory, Story). 61 | 62 | simulate(_, _, _, [], []). 63 | simulate(State, Genre, Options, [Action|Remains], [Desc | RemDesc]) :- 64 | ( 65 | event_happens(State, Action, Genre, Event) 66 | -> 67 | apply_action_dict(State, Event, NewState), 68 | plan(NewState, Genre, NewPlan, Options), 69 | Desc = Event.desc, 70 | simulate(NewState, Genre, Options, NewPlan, RemDesc) 71 | ; 72 | Genre:action(Action, Dict), 73 | apply_action_dict(State, Dict, NewState), 74 | Desc = Dict.desc, 75 | simulate(NewState, Genre, Options, Remains, RemDesc) 76 | ). 77 | 78 | event_happens(State, Action, Genre, EventDict) :- 79 | ( setof(Pair, possible_event(State, Genre, Action, Pair), Possible) 80 | -> true 81 | ; Possible = [] 82 | ), 83 | random_permutation(Possible, RandPossible), 84 | maybe_pick_one(RandPossible, EventDict). 85 | 86 | maybe_pick_one([], _) :- !, fail. 87 | maybe_pick_one([P-H | _], H) :- 88 | P > random_float, 89 | !. 90 | maybe_pick_one([_ | T], Out) :- 91 | maybe_pick_one(T, Out). 92 | 93 | possible_event(State, Genre, ActionName, Prob-Dict) :- 94 | Genre:event(ActionName, Prob, Dict), 95 | maplist(is_in(State), Dict.pre), 96 | maplist(not_in(State), Dict.negpre). 97 | 98 | % famulus to swap memberchk's args 99 | is_in(List, Member) :- 100 | memberchk(Member, List). 101 | 102 | not_in(List, Member) :- 103 | \+ memberchk(Member, List). 104 | 105 | --------------------------------------------------------------------------------