Advertisement
simserver

gdlGameV1: gdlGame.pl

Dec 11th, 2015
15
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
Prolog 26.00 KB | None | 0 0
  1. /* -*- Mode:Prolog; coding:UTF-8; -*- */
  2.  
  3. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  4. % Gameserver-Spielengine fuer GDL Card Game
  5. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  6.  
  7. :- module(gdlGame,[initMatch_gdlGame/8, play_gdlGame/9, joinMatch_gdlGame/7]).
  8.  
  9. :- use_module(library(file_systems)).
  10. :- use_module(library(lists)).
  11. :- use_module(remoteaiwrapper).
  12. :- ensure_loaded(simutils).
  13.  
  14.  
  15. %% joinMatch_ownGDL(+MatchId,+PlayerDetails,+Oldworld,-Newworld,-Views, -Round, -Phase) is det.
  16. joinMatch_gdlGame(_MatchId,_PlayerDetails,_Oldworld,_Newworld,_Views, _Round, _Phase) :-
  17.         throw('In diesem Spiel ist ein nachtraegliches Betreten nicht moeglich.').
  18.  
  19. %% initMatch_ownGDL(+MatchId, +MatchOptions, +PlayerList, +PlayerDetails, -Worldout, -Views, -Round, -Phase) is det.
  20. initMatch_gdlGame(MatchId, MatchOptions, _PlayerList, _PlayerDetails,  WorldOut, Views, "1", "default") :-
  21.         processMatchOptions(MatchId,MatchOptions,GdlCode,VisCode),
  22.        
  23.         importGdlCode(MatchId,GdlCode),
  24.         processVisCode(VisCode,VisDict),
  25.        
  26.         % fuellt alle 2500 Kartenpositionen mit leeren Platzhalterkarten
  27.         putInvisibleCards(ViewCards0),
  28.        
  29.         % initialisiert die World-Variable
  30.         World = [gdl-[],
  31.                  vis-VisDict,
  32.                  view-ViewCards0,
  33.                  state-0,
  34.                  action-noop],
  35.        
  36.         % fuellt die "gdl" anhand der "init"-Fakten
  37.         updateGdl(World,World1),
  38.        
  39.         % formt aus den Fakten in "gdl" die View
  40.         updateView(World1,World2),
  41.         worldget(view,World2,ViewCards),
  42.        
  43.         % gibt die erlaubten Aktionen der Spieler im aktuellen Zustand aus
  44.         allowedActions(World2,player1,Player1AllowedActions),
  45.         allowedActions(World2,player2,Player2AllowedActions),
  46.        
  47.         Player1View = view(player1,ViewCards,[],Player1AllowedActions,[],[],undo(0,[]),[]),
  48.         Player2View = view(player2,ViewCards,[],Player2AllowedActions,[],[],undo(0,[]),[]),
  49.        
  50.        
  51.         % Outputs an Java
  52.         WorldOut = World2,
  53.         Views = [Player1View,Player2View],
  54.        
  55.         debprintln('finish InitMatch'),
  56.         true.
  57.  
  58. %% play_ownGDL(+Player, +GuiAction, +MatchNumber, +WorldIn, -WorldOut, -Views, -Matchstate, -Round, -Phase)
  59. play_gdlGame(_Player, GuiAction, _MatchNumber, WorldIn, WorldOut, Views, Matchstate, "1", "default") :-
  60.         % holt das VisualizationDictionairy
  61.         worldget(vis,WorldIn,Vis),
  62.        
  63.         % gibt die GuiAction in die "World"-Variable
  64.         worldput(action,WorldIn,GuiAction,World0),
  65.        
  66.         % aktualisiert die "gdl"-Fakten anhand der neuen GuiAction
  67.         updateGdl(World0,World1),
  68.        
  69.         % bei Spielende den Sieger auswerten
  70.         (terminal(World1) ->
  71.          worldget(player1,Vis,Player1),
  72.          worldget(player2,Vis,Player2),
  73.          goal(World1,Player1,Player1GdlPoints),
  74.          goal(World1,Player2,Player2GdlPoints),
  75.          n_numberToNumber(Player1GdlPoints,Player1Points),
  76.          n_numberToNumber(Player2GdlPoints,Player2Points),
  77.          (Player1Points < Player2Points ->
  78.           Player1Result = lost,
  79.           Player2Result = won
  80.          ;
  81.           (Player1Points > Player2Points ->
  82.            Player1Result = won,
  83.            Player2Result = lost
  84.           ; % Player1Points = Player2Points
  85.            Player1Result = draw,
  86.            Player2Result = draw
  87.           )
  88.          ),
  89.          Matchstate0 = matchstate(finished,[player(player1,Player1Result,Player1Points),player(player2,Player2Result,Player2Points)])
  90.         ;
  91.          Matchstate0 = matchstate(running(0),[])
  92.         ),
  93.        
  94.         % erstellt die Views für die Spieler
  95.         updateView(World1,World2),
  96.         worldget(view,World2,ViewCards),
  97.        
  98.         % gibt die erlaubten Aktionen der Spieler wieder
  99.         (Matchstate0 = matchstate(running(0),[]) ->
  100.          allowedActions(World2,player1,Player1AllowedActions),
  101.          allowedActions(World2,player2,Player2AllowedActions)
  102.         ; % keine Aktionen bei Spielende
  103.          Player1AllowedActions = [],
  104.          Player2AllowedActions = []
  105.         ),
  106.        
  107.         Player1View = view(player1,ViewCards,[],Player1AllowedActions,[],[],undo(0,[]),[]),
  108.         Player2View = view(player2,ViewCards,[],Player2AllowedActions,[],[],undo(0,[]),[]),
  109.        
  110.        
  111.        
  112.        
  113.         % Outputs an Java
  114.         WorldOut = World2,
  115.         Views = [Player1View,Player2View],
  116.         Matchstate = Matchstate0,
  117.        
  118.         % gibt den Matchstate im Terminal aus (TODO: an die Oberflaeche bringen)
  119.         debprintln('Matchstate:'-Matchstate),
  120.         true.
  121.  
  122.  
  123.  
  124. % verarbeitet die Matchoptionen: gibt die Codes der angegebenen Files aus
  125. processMatchOptions(MatchId,MatchOptions,GdlCode,VisCode) :-
  126.         % get GDL-Code
  127.         (worldget(gdlfile, MatchOptions, GdlfileName) ->      
  128.          match_file_fullpath(MatchId, GdlfileName, FullGdlfileName),
  129.          file2string(FullGdlfileName,GdlCode)
  130.         ;
  131.          throw('Keine GDL-File angegeben!')
  132.         ),
  133.         % get VIS-Code
  134.         (worldget(visfile,MatchOptions,VisfileName) ->        
  135.          match_file_fullpath(MatchId,VisfileName,FullVisfileName),
  136.          file2string(FullVisfileName,VisCode)
  137.         ;
  138.          throw('Keine VIS-File angegeben!')
  139.         ).
  140. %
  141. % Bestimmt zu Match-ID und Dateiname vollstaendigen Pfad und wirft Ausnahmen, falls Uploadverzeichnis oder Datei nicht existieren.
  142. match_file_fullpath(MatchId,Filename,Fullpath) :-
  143.         atom_number(MatchIdAtom,MatchId),
  144.         (Filename = '' ->
  145.          throw('Benoetigtes File nicht ausgewaehlt!!!')
  146.         ;
  147.          true
  148.         ),
  149.         uploadfolder(Ufolder),
  150.         (directory_member_of_directory(Ufolder,MatchIdAtom,_) ->
  151.          true
  152.         ;
  153.          throw('Verzeichnis mit hochgeladenen Dateien existiert nicht!')
  154.         ),
  155.         atom_concat(Ufolder,MatchIdAtom,FullDirPathAtom),
  156.         file_members_of_directory(FullDirPathAtom,Set),
  157.         (worldget(Filename,Set,Fullpath) ->
  158.          true
  159.         ;
  160.          throw('Datei existiert nicht!')
  161.         ).
  162.  
  163. % speichert verarbeiteten GDL-Code in den temporären Matchfolder und importiert ihn
  164. importGdlCode(MatchId,GDLcode) :-
  165.         gdlToProlog(GDLcode,PrologCode),
  166.         atom_codes(PrologAtom,PrologCode),
  167.        
  168.         uploadfolder(Ufolder),
  169.         atom_number(MatchIdAtom,MatchId),
  170.         PrologFile = '/gdlAsProlog.pl',        
  171.         atom_concat(Ufolder,MatchIdAtom,FullDirPathAtom),
  172.         atom_concat(FullDirPathAtom,PrologFile,FullPathFile),
  173.        
  174.         open(FullPathFile,write,StreamWrite),
  175.         write(StreamWrite,PrologAtom),
  176.         close(StreamWrite),
  177.        
  178.         use_module(FullPathFile).
  179. %
  180. % verarbeitet GDL-Code, sodass er als Prolog-Code verwendet werden kann
  181. gdlToProlog(GDLcode,PrologCode) :-
  182.         select(-1,GDLcode,GDLcode0),                    % entfernt die -1 am Ende      
  183.         code_deleteComments(GDLcode0,Code0),            % loescht Kommentarzeilen
  184.         code_replace(38,Code0,44,Code1),                % ersetzt "&" durch ","
  185.         code_replace(126,Code1,[92,43],Code2),          % ersetzt "~" durch "\+"
  186.         code_numbersToAtoms(Code2,Code3),               % stellt Zahlen "n_" voran
  187.         code_deleteEmptyRows(Code3,Code4),              % loescht Leerzeilen
  188.         code_replace(32,Code4,[],Code5),                % loescht alle Leerzeichen
  189.         code_addDots(Code5,PrologCode0),                % fuegt Punkte ein        
  190.         code_addWorldVar(PrologCode0,PrologCode).       % fuegt die World-Variable hinzu
  191.  
  192. % transformiert erhaltenen Visualisierungscode in ein VisualizationDictionary um
  193. processVisCode(VisCode,VisDict) :-
  194.         select(-1,VisCode,Code0),            % entfernt die -1 am Ende      
  195.         code_deleteComments(Code0,Code1),    % loescht Kommentarzeilen
  196.         code_deleteEmptyRows(Code1,Code),    % loescht leere Zeilen
  197.         getVisDict(Code,VisDict).
  198. %
  199. getVisDict([],[]).
  200. getVisDict(VisCode,[PrefixAtom-SuffixAtom]) :-
  201.         \+member(10,VisCode),
  202.         sublist(VisCode,[60,45],PrefixLength,PartLength,_SuffixLength),
  203.         append_length(Prefix,PartSuffix,VisCode,PrefixLength),
  204.         append_length(_Part,Suffix2,PartSuffix,PartLength),
  205.         code_numbersToAtoms(Suffix2,Suffix3),
  206.         atom_codes(PrefixAtom,Prefix),
  207.         atom_codes(SuffixAtom,Suffix3).
  208. getVisDict(VisCode,[Prefix2Atom-Suffix2Atom|VisDict]) :-
  209.         sublist(VisCode,[10],PrefixLength1,PartLength1,_SuffixLength1),
  210.         append_length(Prefix1,PartSuffix1,VisCode,PrefixLength1),
  211.         append_length(_Part1,Suffix1,PartSuffix1,PartLength1),
  212.         sublist(Prefix1,[60,45],PrefixLength2,PartLength2,_SuffixLength2),
  213.         append_length(Prefix2,PartSuffix2,Prefix1,PrefixLength2),
  214.         append_length(_Part2,Suffix2,PartSuffix2,PartLength2),
  215.         code_numbersToAtoms(Suffix2,Suffix3),
  216.         atom_codes(Prefix2Atom,Prefix2),
  217.         atom_codes(Suffix2Atom,Suffix3),
  218.         getVisDict(Suffix1,VisDict).
  219.  
  220.  
  221. % fuellt alle Position mit unsichtbaren Platzhalterkarten
  222. putInvisibleCards(ViewCards) :-
  223.         getAllPositions(AllPositions),
  224.         putInvisibleCards(ViewCards,AllPositions).
  225. putInvisibleCards([],[]).
  226. putInvisibleCards([PositionAtom-card(none-0)|ViewCards],[Position|Positions]) :-
  227.         atom_number(PositionAtom,Position),
  228.         putInvisibleCards(ViewCards,Positions).
  229. %
  230. % gibt alle moeglichen Position-IDs zurueck (50x50 Grid)
  231. getAllPositions(AllPositions) :-
  232.         range(1,50,Range),
  233.         getAllPositions(AllPositions,Range,Range).
  234. getAllPositions([],[],_).
  235. getAllPositions([],_,[]).
  236. getAllPositions(AllPositions,[X|Xs],Ys) :-
  237.         getAllPositions1(Positions1,X,Ys),
  238.         getAllPositions(Positions2,Xs,Ys),
  239.         append([Positions1,Positions2],AllPositions).
  240. getAllPositions1(_,_,[]).
  241. getAllPositions1([Z|Positions],X,[Y|Ys]) :-
  242.         Z1 is 10000 + Y,
  243.         Z2 is 100 * X,
  244.         Z is Z1 + Z2,
  245.         getAllPositions1(Positions,X,Ys).
  246.  
  247.  
  248. % bestimmt anhand der "init" und "next" Literale die Fakten des folgenden Zustands
  249. updateGdl(WorldIn,WorldOut) :-
  250.         worldget(state,WorldIn,State),
  251.         (State = 0 ->
  252.          findall(InitVar,init(WorldIn,InitVar),Vars)
  253.         ;
  254.          findall(NextVar,next(WorldIn,NextVar),Vars)
  255.         ),
  256.         updateGdl(WorldIn,WorldOut0,Vars),
  257.         NextState is State + 1,
  258.         worldput(state,WorldOut0,NextState,WorldOut).
  259. %
  260. updateGdl(World,World,[]).
  261. updateGdl(WorldIn,WorldOut,[Var|Vars]) :-
  262.         worldget(gdl,WorldIn,Gdl),
  263.         worldget(state,WorldIn,State),
  264.         State1 is State + 1,
  265.         atom_number(State1Atom,State1),
  266.        
  267.         Var =.. [Constant|World_Terms],
  268.         World_Terms = [_World|Terms],
  269.         length(Terms,Length),
  270.         atom_number(LengthAtom,Length),
  271.         atom_concat(Constant,LengthAtom,ConstantLength),
  272.                
  273.         (worldget(ConstantLength,Gdl,GdlVars) ->
  274.          Terms0 = [State1Atom|Terms],
  275.          setValues(GdlVars,Terms0,GdlVars1),
  276.          worldput(ConstantLength,Gdl,GdlVars1,Gdl1),
  277.          worldput(gdl,WorldIn,Gdl1,World1),
  278.          updateGdl(World1,WorldOut,Vars)
  279.         ;
  280.          Length1 is Length + 1,
  281.          listsLength0(GdlVars,Length1),
  282.          worldput(ConstantLength,Gdl,GdlVars,Gdl1),
  283.          worldput(gdl,WorldIn,Gdl1,World1),
  284.          updateGdl(World1,WorldOut,[Var|Vars])
  285.         ).
  286. %
  287. setValues([],[],[]).
  288. setValues([Var|Vars],[Term|Terms],[[Term|Var]|VarsOut]) :-
  289.         setValues(Vars,Terms,VarsOut).
  290.  
  291.  
  292. % bestimmt anhand des "legal" Literals die erlaubten Aktionen der Spieler im aktuellen Zustand
  293. allowedActions(World,Player,AllowedActions) :-
  294.         worldget(vis,World,Vis),
  295.         worldget(Player,Vis,PlayerGdl),
  296.         findall(Action,legal(World,PlayerGdl,Action),Actions),
  297.         allowedActions1(World,Actions,AllowedActions).
  298. allowedActions1(_,[],[]).
  299. allowedActions1(World,[Action|Actions],AllowedActions) :-
  300.         worldget(vis,World,Vis),
  301.         Action =.. [Constant|World_Terms],
  302.         (World_Terms = [] ->
  303.          ActionAtom = Constant
  304.         ;
  305.          World_Terms = [_World|Terms],
  306.          ActionTerm =.. [Constant|Terms],
  307.          atom_term(ActionAtom,ActionTerm)
  308.         ),
  309.         worldget(GameActionAtom,Vis,ActionAtom),
  310.         (GameActionAtom = noop ->
  311.          AllowedActions = []
  312.         ;
  313.          atom_term(GameActionAtom,GameActionTerm),
  314.          GameActionTerm =.. [click,GameActionNumber],
  315.          allowedActions1(World,Actions,AllowedActions0),
  316.          AllowedActions = [GameActionNumber-[click]|AllowedActions0]
  317.         ).
  318.  
  319.  
  320. % aktualisiert die darzustellenden Karten
  321. updateView(WorldIn,WorldOut) :-
  322.         getGdlFacts(WorldIn,cardPosition,States,PosFacts),
  323.         getGdlFacts(WorldIn,cardSuit,_,SuitFacts),
  324.         getGdlFacts(WorldIn,cardValue,_,ValFacts),
  325.        
  326.         getViewCards(WorldIn,States,PosFacts,SuitFacts,ValFacts,ViewCardsNew),
  327.        
  328.         worldget(view,WorldIn,ViewCardsOld),
  329.         updateViewCards(ViewCardsOld,ViewCardsNew,ViewCardsUpdate),
  330.        
  331.         worldput(view,WorldIn,ViewCardsUpdate,WorldOut).
  332. %
  333. % gibt Karten und ihre Position im aktuellen Zustand zurueck
  334. getViewCards(_,[],[],[],[],[]).
  335. getViewCards(World,[StateAtom|States],[Pos|PosFacts],SuitIn,ValIn,[Pos1-card(Suit1-Val1)|ViewCards]) :-
  336.         worldget(state,World,State),
  337.         atom_number(StateAtom,State),
  338.         worldget(vis,World,Vis),
  339.        
  340.         worldget_np(Pos1,Vis,Pos),
  341.         (worldget(none,Vis,None) ->
  342.          worldget(none,Vis,None)
  343.         ;
  344.          None = none
  345.         ),
  346.         (worldget('0',Vis,Zero) ->
  347.          worldget('0',Vis,Zero)
  348.         ;
  349.          Zero = '0'
  350.         ),
  351.         (SuitIn = [] ->
  352.          (ValIn = [Zero|_] ->
  353.           Suit1 = none
  354.          ;
  355.           Suit1 = c
  356.          ),
  357.          SuitFacts = []
  358.         ;
  359.          SuitIn = [Suit|SuitFacts],
  360.          worldget_np(Suit1,Vis,Suit)
  361.         ),
  362.         (ValIn = [] ->
  363.          (SuitIn = [None|_] ->
  364.           Val1 = 0
  365.          ;
  366.           Val1 = a
  367.          ),
  368.          ValFacts = []
  369.         ;
  370.          ValIn = [Val|ValFacts],        
  371.          worldget_np(Val1,Vis,Val)
  372.         ),
  373.         getViewCards(World,States,PosFacts,SuitFacts,ValFacts,ViewCards).
  374. getViewCards(World,[_|States],[_|PosFacts],SuitIn,ValIn,ViewCards) :-
  375.         (SuitIn = [] ->
  376.          SuitFacts = []
  377.         ;
  378.          SuitIn = [_|SuitFacts]
  379.         ),
  380.         (ValIn = [] ->
  381.          ValFacts = []
  382.         ;
  383.          ValIn = [_|ValFacts]
  384.         ),
  385.         getViewCards(World,States,PosFacts,SuitFacts,ValFacts,ViewCards).
  386. %
  387. % worldget-Prädikat, das keinen Spieler zurueckliefert
  388. worldget_np(NotPlayer,Vis,In) :-
  389.         worldget(NotPlayer,Vis,In),
  390.         dif(player1,NotPlayer),
  391.         dif(player2,NotPlayer).
  392. %
  393. updateViewCards(ViewCards,[],ViewCards).
  394. updateViewCards(ViewCardsOld,[Key-Value|ViewCardsUpdate],ViewCardsNew) :-
  395.         worldput(Key,ViewCardsOld,Value,ViewCardsNew1),
  396.         updateViewCards(ViewCardsNew1,ViewCardsUpdate,ViewCardsNew).
  397.  
  398.  
  399. % gibt angeforderte Fakten zurueck
  400. getGdlFacts(World,Key,States,Facts) :-
  401.         worldget(vis,World,Vis),
  402.         worldget(Key,Vis,FactAtom),
  403.         (FactAtom = '' ->
  404.          States = [],
  405.          Facts = []
  406.         ;
  407.          atom_codes(FactAtom,FactCode),
  408.          termList(FactCode,FactTerms),
  409.          getFacts(World,FactTerms,States,Facts)
  410.         ).
  411. %
  412. termList([],[]).
  413. termList(FactCode,FactTerm) :-
  414.         \+member(10,FactCode),
  415.         atom_codes(FactAtom,FactCode),
  416.         atom_term(FactAtom,FactTerm).
  417. termList(FactCode,[PrefixTerm|TermList]) :-
  418.         sublist(FactCode,[43],PrefixLength,PartLength,_SuffixLength),
  419.         append_length(Prefix,PartSuffix,FactCode,PrefixLength),
  420.         append_length(_Part,Suffix,PartSuffix,PartLength),
  421.         atom_codes(PrefixAtom,Prefix),
  422.         atom_term(PrefixAtom,PrefixTerm),
  423.         termList(Suffix,TermList).
  424. %
  425. getFacts(_,[],[],[]).
  426. getFacts(World,FactTerm,States,Facts) :-
  427.         worldget(gdl,World,Gdl),
  428.         FactTerm =.. [FactName_n,FactNumber_n],
  429.         n_numberToAtom(FactName_n,FactName),
  430.         n_numberToNumber(FactNumber_n,FactNumber),
  431.          
  432.         (worldget(FactName,Gdl,GdlFacts) ->
  433.          GdlFacts = [States|_],
  434.          nth0(FactNumber,GdlFacts,Facts)
  435.         ;
  436.          States = [],
  437.          Facts = []
  438.         ).
  439. getFacts(World,[FactTerm|FactTerms],States,Facts) :-
  440.         worldget(gdl,World,Gdl),
  441.         FactTerm =.. [FactName_n,FactNumber_n],
  442.         n_numberToAtom(FactName_n,FactName),
  443.         n_numberToNumber(FactNumber_n,FactNumber),
  444.          
  445.         (worldget(FactName,Gdl,GdlFacts) ->
  446.          nth0(FactNumber,GdlFacts,Facts0),
  447.          getFacts(World,FactTerms,States,Facts1),
  448.          combineFacts(Facts,Facts0,Facts1)
  449.         ;
  450.          getFacts(World,FactTerms,States,Facts)        
  451.         ).
  452. %
  453. combineFacts([],[],[]).
  454. combineFacts([CombinedFact|CombinedFacts],[Fact0|Facts0],[Fact1|Facts1]) :-
  455.         atom_concat(Fact0,'+',Fact0Plus),
  456.         atom_concat(Fact0Plus,Fact1,CombinedFact),
  457.         combineFacts(CombinedFacts,Facts0,Facts1).
  458.  
  459. % loescht "n_" aus zu Atomen gezwungenen Zahlen
  460. n_numberToNumber(N_number,Number) :-
  461.         atom_codes(N_number,N_numberCode),
  462.         delete_n_(N_numberCode,NumberCode),
  463.         number_codes(Number,NumberCode).
  464. n_numberToAtom(N_number,AtomNumber) :-
  465.         atom_codes(N_number,N_numberCode),
  466.         delete_n_(N_numberCode,NumberCode),
  467.         atom_codes(AtomNumber,NumberCode).
  468. %
  469. delete_n_([],[]).
  470. delete_n_([110,95|Points],Numbers) :-
  471.         delete_n_(Points,Numbers),!.
  472. delete_n_([Number|Points],[Number|Numbers]) :-
  473.         delete_n_(Points,Numbers),!.
  474.  
  475.  
  476. /*------------------------ GDL Predicates ------------------------*/
  477. % GDL: distinct
  478. distinct(_,X,Y) :-
  479.         dif(X,Y).
  480.  
  481. % GDL: true
  482. true(World,Literal) :-
  483.         worldget(state,World,State),
  484.         atom_number(StateAtom,State),
  485.         worldget(gdl,World,Gdl),
  486.        
  487.         Literal =.. [Constant|World_Terms],
  488.         World_Terms = [_World|Terms],
  489.         length(Terms,Length),
  490.         atom_number(LengthAtom,Length),
  491.         atom_concat(Constant,LengthAtom,ConstantLength),
  492.         worldget(ConstantLength,Gdl,GdlTerms),
  493.        
  494.         Terms0 = [StateAtom|Terms],
  495.        
  496.         checkFacts(GdlTerms,Terms0).
  497.  
  498. % GDL: does
  499. does(World,Player,Action) :-
  500.         worldget(state,World,State),
  501.         atom_number(StateAtom,State),
  502.         worldget(vis,World,Vis),
  503.        
  504.         getGdlFacts(World,lead,LeadStates,LeadFacts),
  505.         LeadTerms = [LeadStates,LeadFacts],
  506.         PlayerTerms = [StateAtom,Player],
  507.         checkFacts(LeadTerms,PlayerTerms),
  508.        
  509.         worldget(action,World,GameAction),
  510.         atom_term(GameActionAtom,GameAction),
  511.         worldget(GameActionAtom,Vis,ActionAtom),
  512.         Action =.. [Constant|World_Terms],
  513.         World_Terms = [_World|Terms],
  514.         Action0 =.. [Constant|Terms],
  515.         atom_term(ActionAtom,Action0).
  516.  
  517. % supporting GDL Predicates
  518. checkFacts([],[]).
  519. checkFacts([GdlTerm|GdlTerms],[Term|Terms]) :-
  520.         nth1(N,GdlTerm,Term),
  521.         checkFacts(GdlTerms,Terms,N).
  522. checkFacts([],[],_).
  523. checkFacts([GdlTerm|GdlTerms],[Term|Terms],N) :-
  524.         nth1(N,GdlTerm,Term),
  525.         checkFacts(GdlTerms,Terms,N).
  526. /*---------------------- End: GDL Predicates ---------------------*/
  527.  
  528. /*------------------------- GDL Parsing --------------------------*/
  529. % loescht ab allen ";" bis Zeilenende (Kommentare)
  530. code_deleteComments([],[]).      
  531. code_deleteComments(Code,Code) :-
  532.         \+member(59,Code).
  533. code_deleteComments(CodeIn,CodeOut) :-
  534.         sublist(CodeIn,[59],PrefixLength1,_PartLength1,_SuffixLength1),
  535.         append_length(Prefix1,Suffix1,CodeIn,PrefixLength1),
  536.         sublist(Suffix1,[10],PrefixLength2,PartLength2,_PartLength2),
  537.         AppendPosition is PrefixLength2 + PartLength2,
  538.         append_length(_Prefix2,Suffix2,Suffix1,AppendPosition),
  539.         code_deleteComments(Suffix2,Code),
  540.         append([Prefix1,Code],CodeOut).
  541.  
  542. % ersetzt X durch Y
  543. code_replace(_,[],_,[]).
  544. code_replace(X,Code,_,Code) :-
  545.         (is_list(X) -> Xs = X ; Xs = [X]),
  546.         \+sublist(Code,Xs,_,_,_).
  547. code_replace(X,CodeIn,Y,CodeOut) :-
  548.         (is_list(X) -> Xs = X ; Xs = [X]),
  549.         (is_list(Y) -> Ys = Y ; Ys = [Y]),
  550.         sublist(CodeIn,Xs,PrefixLength,PartLength,_SuffixLength),
  551.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  552.         append_length(_Part,Suffix,PartSuffix,PartLength),
  553.         code_replace(Xs,Suffix,Ys,Code),
  554.         append([Prefix,Ys,Code],CodeOut).
  555.  
  556. % ersetzt Zahlen "0"-"9" durch "n_0"-"n_9" (zwingt Zahlen zu Atome)
  557. code_numbersToAtoms(CodeIn,CodeOut) :-
  558.         code_numbersToAtoms(48,57,CodeIn,CodeOut).
  559. code_numbersToAtoms(LastNumber,LastNumber,CodeIn,CodeOut) :-
  560.         code_replace(LastNumber,CodeIn,[110,95,LastNumber],CodeOut).
  561. code_numbersToAtoms(Number,LastNumber,CodeIn,CodeOut) :-
  562.         code_replace(Number,CodeIn,[110,95,Number],Code),
  563.         NextNumber is Number +1,
  564.         code_numbersToAtoms(NextNumber,LastNumber,Code,CodeOut).
  565.  
  566. % loescht leere Zeilen am Anfang, Ende und nach leeren Zeilen
  567. code_deleteEmptyRows(CodeIn,CodeOut) :-
  568.         CodeIn = [10|Rest],
  569.         code_deleteEmptyRows(Rest,CodeOut).
  570. code_deleteEmptyRows(CodeIn,CodeOut) :-
  571.         last(Rest,10,CodeIn),
  572.         code_deleteEmptyRows(Rest,CodeOut).
  573. code_deleteEmptyRows(Code,Code) :-
  574.         \+nextto(10,10,Code).
  575. code_deleteEmptyRows(CodeIn,CodeOut) :-
  576.         code_replace([10,10],CodeIn,10,Code),
  577.         code_deleteEmptyRows(Code,CodeOut).
  578.  
  579. % fuegt Punkte an Zeilenenden ohne "-" oder "," ein
  580. code_addDots([],[]).
  581. code_addDots(Code,Code) :-
  582.         last(_,46,Code),
  583.         \+member(10,Code).
  584. code_addDots(CodeIn,CodeOut) :-
  585.         append(CodeIn,[46],CodeOut),
  586.         \+member(10,CodeIn).
  587. code_addDots(CodeIn,CodeOut) :-
  588.         sublist(CodeIn,[10],PrefixLength,PartLength,_SuffixLength),
  589.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  590.         append_length(Part,Suffix,PartSuffix,PartLength),
  591.         last(Prefix,Last),
  592.         dif(Last,45),
  593.         dif(Last,44),
  594.         code_addDots(Suffix,Code),
  595.         append([Prefix,[46],Part,Code],CodeOut).
  596. code_addDots(CodeIn,CodeOut) :-
  597.         sublist(CodeIn,[10],PrefixLength,PartLength,_SuffixLength),
  598.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  599.         append_length(Part,Suffix,PartSuffix,PartLength),
  600.         code_addDots(Suffix,Code),
  601.         append([Prefix,Part,Code],CodeOut).
  602.  
  603. % fuegt jedem Literal die Variable "World" als ersten Term hinzu
  604. code_addWorldVar([],[]).
  605. code_addWorldVar(Code,Code) :-
  606.         \+member(10,Code),
  607.         subseq0(Code,"World").
  608. code_addWorldVar(CodeIn,CodeOut) :-
  609.         \+member(10,CodeIn),
  610.         code_addWorldVar_check(CodeIn,CodeOut).
  611. code_addWorldVar(CodeIn,CodeOut) :-
  612.         sublist(CodeIn,[10],PrefixLength,PartLength,_SuffixLength),
  613.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  614.         append_length(Part,Suffix,PartSuffix,PartLength),
  615.         code_addWorldVar_check(Prefix,Prefix1),
  616.         code_addWorldVar(Suffix,Code),
  617.         append([Prefix1,Part,Code],CodeOut).
  618. %
  619. code_addWorldVar_check([],[]).
  620. code_addWorldVar_check(CodeIn,CodeOut) :-
  621.         \+member(40,CodeIn),
  622.         sublist(CodeIn,[58,45],PrefixLength,PartLength,_SuffixLength),
  623.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  624.         append_length(Part,Suffix,PartSuffix,PartLength),
  625.         append([Prefix,"(World)",Part,Suffix],CodeOut).
  626. code_addWorldVar_check(CodeIn,CodeOut) :-
  627.         \+member(40,CodeIn),
  628.         sublist(CodeIn,[44],PrefixLength,PartLength,_SuffixLength),
  629.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  630.         append_length(Part,Suffix,PartSuffix,PartLength),
  631.         append([Prefix,"(World)",Part,Suffix],CodeOut).
  632. code_addWorldVar_check(CodeIn,CodeOut) :-
  633.         \+member(40,CodeIn),
  634.         sublist(CodeIn,[46],PrefixLength,PartLength,_SuffixLength),
  635.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  636.         append_length(Part,Suffix,PartSuffix,PartLength),
  637.         append([Prefix,"(World)",Part,Suffix],CodeOut).
  638. code_addWorldVar_check(CodeIn,CodeOut) :-
  639.         code_addWorldVar_bracket(CodeIn,CodeOut).
  640. %
  641. code_addWorldVar_bracket([],[]).
  642. code_addWorldVar_bracket(Code,Code) :-
  643.         \+member(40,Code).
  644. code_addWorldVar_bracket(CodeIn,CodeOut) :-
  645.         sublist(CodeIn,[40],PrefixLength,PartLength,_SuffixLength),
  646.         append_length(Prefix,PartSuffix,CodeIn,PrefixLength),
  647.         append_length(Part,Suffix,PartSuffix,PartLength),
  648.         code_addWorldVar_bracket(Suffix,Code),
  649.         append([Prefix,Part,"World,",Code],CodeOut).
  650. /*----------------------- End: GDL Parsing -----------------------*/
  651.  
  652. /*---------------------------- Utility ---------------------------*/
  653. % gibt eine angegebene Anzahl an leeren Listen zurueck
  654. listsLength0([],0).
  655. listsLength0([E|L],Number) :-
  656.         length(E,0),
  657.         NextNumber is Number - 1,
  658.         listsLength0(L,NextNumber).
  659.  
  660. % transformiert Atom zu Term oder Term zu Atom
  661. atom_term([],[]).
  662. atom_term(Atom,Term) :-
  663.         (var(Atom) ->
  664.          Term =.. [Functor|Arguments],
  665.          (Arguments = [] ->
  666.           Atom = Functor
  667.          ;
  668.           atom_concat(Functor,'(',FunctorBracket),
  669.           atom_term(FunctorBracket,Arguments,Atom0),
  670.           atom_concat(Atom0,')',Atom)
  671.          )
  672.         ;
  673.          atom_concat(Atom,'.',AtomDot),
  674.          atom_codes(AtomDot,AtomCode),
  675.          read_from_codes(AtomCode,Term)
  676.         ).
  677. atom_term(Atom,Atom,[]).
  678. atom_term(AtomIn,[Argument],AtomOut) :-
  679.         (number(Argument) ->
  680.          atom_number(ArgumentAtom,Argument)
  681.         ;
  682.          ArgumentAtom = Argument
  683.         ),
  684.         atom_concat(AtomIn,ArgumentAtom,AtomOut).
  685. atom_term(AtomIn,[Argument|Arguments],AtomOut) :-
  686.         (number(Argument) ->
  687.          atom_number(ArgumentAtom,Argument)
  688.         ;
  689.          ArgumentAtom = Argument
  690.         ),
  691.         atom_concat(AtomIn,ArgumentAtom,Atom0),
  692.         atom_concat(Atom0,',',Atom),
  693.         atom_term(Atom,Arguments,AtomOut).
  694. /*------------------------- End: Utility -------------------------*/
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement