1% ectest/ec_reader_test_foundations.e:1
    2% translate: begining  File: ectest/ec_reader_test_foundations.e.pro 
    3% 
    4% 
    5% 
    6% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    7% ; FILE: foundations/Root.e
    8% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    9% ectest/ec_reader_test_foundations.e:7
   10% 
   11% ;
   12% ; Copyright (c) 2005 IBM Corporation and others.
   13% ; All rights reserved. This program and the accompanying materials
   14% ; are made available under the terms of the Common Public License v1.0
   15% ; which accompanies this distribution, and is available at
   16% ; http://www.eclipse.org/legal/cpl-v10.html
   17% ;
   18% ; Contributors:
   19% ; IBM - Initial implementation
   20% ;
   21% ectest/ec_reader_test_foundations.e:18
   22% sort boolean
   23sort(boolean).
   24
   25% sort integer
   26sort(integer).
   27
   28% reified sort predicate
   29reified_sort(predicate).
   30
   31% reified sort function
   32reified_sort(function).
   33
   34% 
   35% ; End of file.
   36% ectest/ec_reader_test_foundations.e:24
   37% 
   38% 
   39% 
   40% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
   41% ; FILE: foundations/EC.e
   42% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
   43% ectest/ec_reader_test_foundations.e:30
   44% 
   45% ;
   46% ; Copyright (c) 2005 IBM Corporation and others.
   47% ; All rights reserved. This program and the accompanying materials
   48% ; are made available under the terms of the Common Public License v1.0
   49% ; which accompanies this distribution, and is available at
   50% ; http://www.eclipse.org/legal/cpl-v10.html
   51% ;
   52% ; Contributors:
   53% ; IBM - Initial implementation
   54% ;
   55% ; Event Calculus (EC)
   56% ;
   57% ; @incollection{MillerShanahan:2002,
   58% ;   author = "Rob Miller and Murray Shanahan",
   59% ;   year = "2002",
   60% ;   title = "Some alternative formulations of the event calculus",
   61% ;   editor = "Antonis C. Kakas and Fariba Sadri",
   62% ;   booktitle = "Computational Logic: Logic Programming and Beyond: Essays in Honour of \uppercase{R}obert \uppercase{A}. \uppercase{K}owalski, Part \uppercase{II}",
   63% ;   series = "Lecture Notes in Computer Science",
   64% ;   volume = "2408",
   65% ;   pages = "452--490",
   66% ;   address = "Berlin",
   67% ;   publisher = "Springer",
   68% ; }
   69% ;
   70% ectest/ec_reader_test_foundations.e:56
   71% 
   72% sort time: integer
   73subsort(time, integer).
   74
   75% sort offset: integer
   76subsort(offset, integer).
   77
   78% 
   79% reified sort fluent
   80reified_sort(fluent).
   81
   82% reified sort event
   83reified_sort(event).
   84
   85% ectest/ec_reader_test_foundations.e:62
   86% 
   87% predicate Happens(event,time)
   88predicate(happens(event, time)).
   89
   90% predicate HoldsAt(fluent,time)
   91predicate(holds_at(fluent, time)).
   92
   93% predicate ReleasedAt(fluent,time)
   94predicate(releasedAt(fluent, time)).
   95
   96% predicate Initiates(event,fluent,time)
   97predicate(initiates(event, fluent, time)).
   98
   99% predicate Terminates(event,fluent,time)
  100predicate(terminates(event, fluent, time)).
  101
  102% ectest/ec_reader_test_foundations.e:68
  103% predicate Releases(event,fluent,time)
  104predicate(releases(event, fluent, time)).
  105
  106% predicate Trajectory(fluent,time,fluent,offset)
  107predicate(trajectory(fluent, time, fluent, offset)).
  108
  109% 
  110% ; End of file.
  111% 
  112% 
  113% ectest/ec_reader_test_foundations.e:74
  114% 
  115% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  116% ; FILE: foundations/DEC.e
  117% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  118% 
  119% ;
  120% ; Copyright (c) 2005 IBM Corporation and others.
  121% ; All rights reserved. This program and the accompanying materials
  122% ; are made available under the terms of the Common Public License v1.0
  123% ; which accompanies this distribution, and is available at
  124% ; http://www.eclipse.org/legal/cpl-v10.html
  125% ;
  126% ; Contributors:
  127% ; IBM - Initial implementation
  128% ;
  129% ; Discrete Event Calculus (DEC)
  130% ;
  131% ; @article{Mueller:2004a,
  132% ;   author = "Erik T. Mueller",
  133% ;   year = "2004",
  134% ;   title = "Event calculus reasoning through satisfiability",
  135% ;   journal = "Journal of Logic and Computation",
  136% ;   volume = "14",
  137% ;   number = "5",
  138% ;   pages = "703--730",
  139% ; }
  140% ;
  141% ectest/ec_reader_test_foundations.e:101
  142% 
  143% sort time: integer
  144subsort(time, integer).
  145
  146% sort offset: integer
  147subsort(offset, integer).
  148
  149% 
  150% reified sort fluent
  151reified_sort(fluent).
  152
  153% reified sort event
  154reified_sort(event).
  155
  156% ectest/ec_reader_test_foundations.e:107
  157% 
  158% predicate Happens(event,time)
  159predicate(happens(event, time)).
  160
  161% predicate HoldsAt(fluent,time)
  162predicate(holds_at(fluent, time)).
  163
  164% predicate ReleasedAt(fluent,time)
  165predicate(releasedAt(fluent, time)).
  166
  167% 
  168% predicate Initiates(event,fluent,time)
  169predicate(initiates(event, fluent, time)).
  170
  171% ectest/ec_reader_test_foundations.e:113
  172% predicate Terminates(event,fluent,time)
  173predicate(terminates(event, fluent, time)).
  174
  175% predicate Releases(event,fluent,time)
  176predicate(releases(event, fluent, time)).
  177
  178% 
  179% ectest/ec_reader_test_foundations.e:116
  180% [fluent,time]% 
  181% (HoldsAt(fluent,time) &
  182%  !ReleasedAt(fluent,time+1) &
  183%  !({event} Happens(event,time) & Terminates(event,fluent,time))) ->
  184% HoldsAt(fluent,time+1).
  185holds_at(Fluent, Time), not(releasedAt(Fluent, Time+1)), not(exists([Event],  (happens(Event, Time), terminates(Event, Fluent, Time)))) ->
  186	holds_at(Fluent, Time+1).
  187
  188% 
  189% 
  190% ectest/ec_reader_test_foundations.e:122
  191% [fluent,time]% 
  192% (!HoldsAt(fluent,time) &
  193%  !ReleasedAt(fluent,time+1) &
  194%  !({event} Happens(event,time) & Initiates(event,fluent,time))) ->
  195% !HoldsAt(fluent,time+1).
  196not(holds_at(Fluent, Time)), not(releasedAt(Fluent, Time+1)), not(exists([Event],  (happens(Event, Time), initiates(Event, Fluent, Time)))) ->
  197	not(holds_at(Fluent, Time+1)).
  198
  199% 
  200% 
  201% ectest/ec_reader_test_foundations.e:128
  202% [fluent,time]% 
  203% (!ReleasedAt(fluent,time) &
  204%  !({event} Happens(event,time) & Releases(event,fluent,time))) ->
  205% !ReleasedAt(fluent,time+1).
  206not(releasedAt(Fluent, Time)), not(exists([Event],  (happens(Event, Time), releases(Event, Fluent, Time)))) ->
  207	not(releasedAt(Fluent, Time+1)).
  208
  209% 
  210% 
  211% ectest/ec_reader_test_foundations.e:133
  212% [fluent,time]% 
  213% (ReleasedAt(fluent,time) &
  214%  !({event} Happens(event,time) &
  215%    (Initiates(event,fluent,time) |
  216%     Terminates(event,fluent,time)))) ->
  217% ReleasedAt(fluent,time+1).
  218releasedAt(Fluent, Time), not(exists([Event],  (happens(Event, Time), (initiates(Event, Fluent, Time);terminates(Event, Fluent, Time))))) ->
  219	releasedAt(Fluent, Time+1).
  220
  221% 
  222% ectest/ec_reader_test_foundations.e:139
  223% 
  224% ectest/ec_reader_test_foundations.e:140
  225% [event,fluent,time]% 
  226% (Happens(event,time) & Initiates(event,fluent,time)) ->
  227% (HoldsAt(fluent,time+1) & !ReleasedAt(fluent,time+1)).
  228happens(Event, Time), initiates(Event, Fluent, Time) ->
  229	holds_at(Fluent, Time+1),
  230	not(releasedAt(Fluent, Time+1)).
  231
  232% 
  233% 
  234% ectest/ec_reader_test_foundations.e:144
  235% [event,fluent,time]% 
  236% (Happens(event,time) & Terminates(event,fluent,time)) ->
  237% (!HoldsAt(fluent,time+1) & !ReleasedAt(fluent,time+1)).
  238happens(Event, Time), terminates(Event, Fluent, Time) ->
  239	not(holds_at(Fluent, Time+1)),
  240	not(releasedAt(Fluent, Time+1)).
  241
  242% 
  243% 
  244% ectest/ec_reader_test_foundations.e:148
  245% [event,fluent,time]% 
  246% (Happens(event,time) & Releases(event,fluent,time)) ->
  247% ReleasedAt(fluent,time+1).
  248happens(Event, Time), releases(Event, Fluent, Time) ->
  249	releasedAt(Fluent, Time+1).
  250
  251% 
  252% 
  253% ; End of file.
  254% 
  255% ectest/ec_reader_test_foundations.e:154
  256% 
  257% 
  258% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  259% ; FILE: foundations/ECCausal.e
  260% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  261% 
  262% ;
  263% ; Copyright (c) 2005 IBM Corporation and others.
  264% ; All rights reserved. This program and the accompanying materials
  265% ; are made available under the terms of the Common Public License v1.0
  266% ; which accompanies this distribution, and is available at
  267% ; http://www.eclipse.org/legal/cpl-v10.html
  268% ;
  269% ; Contributors:
  270% ; IBM - Initial implementation
  271% ;
  272% ; Causal Constraints
  273% ;
  274% ; @inproceedings{Shanahan:1999a,
  275% ;   author = "Murray Shanahan",
  276% ;   year = "1999",
  277% ;   title = "The ramification problem in the event calculus",
  278% ;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}ixteenth \uppercase{I}nternational \uppercase{J}oint \uppercase{C}onference on \uppercase{A}rtificial \uppercase{I}ntelligence",
  279% ;   pages = "140--146",
  280% ;   address = "San Mateo, CA",
  281% ;   publisher = "Morgan Kaufmann",
  282% ; }
  283% ;
  284% ectest/ec_reader_test_foundations.e:182
  285% 
  286% predicate Started(fluent,time)
  287predicate(started(fluent, time)).
  288
  289% predicate Stopped(fluent,time)
  290predicate(stopped(fluent, time)).
  291
  292% 
  293% ectest/ec_reader_test_foundations.e:186
  294% [fluent,time]% 
  295% Started(fluent,time) <->
  296% (HoldsAt(fluent,time) |
  297%  ({event} Happens(event,time) & Initiates(event,fluent,time))).
  298started(Fluent, Time) <->
  299	(   holds_at(Fluent, Time)
  300	;   exists([Event],
  301		   (happens(Event, Time), initiates(Event, Fluent, Time)))
  302	).
  303
  304% 
  305% 
  306% ectest/ec_reader_test_foundations.e:191
  307% [fluent,time]% 
  308% Stopped(fluent,time) <->
  309% (!HoldsAt(fluent,time) |
  310%  ({event} Happens(event,time) & Terminates(event,fluent,time))).
  311stopped(Fluent, Time) <->
  312	(   not(holds_at(Fluent, Time))
  313	;   exists([Event],
  314		   (happens(Event, Time), terminates(Event, Fluent, Time)))
  315	).
  316
  317% 
  318% 
  319% predicate Initiated(fluent,time)
  320predicate(initiated(fluent, time)).
  321
  322% ectest/ec_reader_test_foundations.e:197
  323% predicate Terminated(fluent,time)
  324predicate(terminated(fluent, time)).
  325
  326% 
  327% ectest/ec_reader_test_foundations.e:199
  328% [fluent,time]% 
  329% Initiated(fluent,time) <->
  330% (Started(fluent,time) &
  331%  !({event} Happens(event,time) & Terminates(event,fluent,time))).
  332initiated(Fluent, Time) <->
  333	started(Fluent, Time),
  334	not(exists([Event],
  335		   (happens(Event, Time), terminates(Event, Fluent, Time)))).
  336
  337% 
  338% 
  339% ectest/ec_reader_test_foundations.e:204
  340% [fluent,time]% 
  341% Terminated(fluent,time) <->
  342% (Stopped(fluent,time) &
  343%  !({event} Happens(event,time) & Initiates(event,fluent,time))).
  344terminated(Fluent, Time) <->
  345	stopped(Fluent, Time),
  346	not(exists([Event],
  347		   (happens(Event, Time), initiates(Event, Fluent, Time)))).
  348
  349% 
  350% 
  351% ; End of file.
  352% ectest/ec_reader_test_foundations.e:210
  353% 
  354% 
  355% 
  356% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  357% ; FILE: foundations/ECTraj.e
  358% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  359% ectest/ec_reader_test_foundations.e:216
  360% 
  361% ;
  362% ; Copyright (c) 2005 IBM Corporation and others.
  363% ; All rights reserved. This program and the accompanying materials
  364% ; are made available under the terms of the Common Public License v1.0
  365% ; which accompanies this distribution, and is available at
  366% ; http://www.eclipse.org/legal/cpl-v10.html
  367% ;
  368% ; Contributors:
  369% ; IBM - Initial implementation
  370% ;
  371% ; @incollection{MillerShanahan:2002,
  372% ;   author = "Rob Miller and Murray Shanahan",
  373% ;   year = "2002",
  374% ;   title = "Some alternative formulations of the event calculus",
  375% ;   editor = "Antonis C. Kakas and Fariba Sadri",
  376% ;   booktitle = "Computational Logic: Logic Programming and Beyond: Essays in Honour of \uppercase{R}obert \uppercase{A}. \uppercase{K}owalski, Part \uppercase{II}",
  377% ;   series = "Lecture Notes in Computer Science",
  378% ;   volume = "2408",
  379% ;   pages = "452--490",
  380% ;   address = "Berlin",
  381% ;   publisher = "Springer",
  382% ; }
  383% ;
  384% ectest/ec_reader_test_foundations.e:240
  385% 
  386% predicate Clipped(time,fluent,time)
  387predicate(clipped(time, fluent, time)).
  388
  389% predicate Declipped(time,fluent,time)
  390predicate(declipped(time, fluent, time)).
  391
  392% 
  393% predicate Trajectory(fluent,time,fluent,offset)
  394predicate(trajectory(fluent, time, fluent, offset)).
  395
  396% predicate AntiTrajectory(fluent,time,fluent,offset)
  397predicate(antiTrajectory(fluent, time, fluent, offset)).
  398
  399% ectest/ec_reader_test_foundations.e:246
  400% 
  401% ectest/ec_reader_test_foundations.e:247
  402% [event,fluent,fluent2,offset,time]% 
  403% Happens(event,time) &
  404% Initiates(event,fluent,time) &
  405% 0 < offset &
  406% Trajectory(fluent,time,fluent2,offset) &
  407% !Clipped(time,fluent,time+offset) ->
  408% HoldsAt(fluent2,time+offset).
  409happens(Event, Time), initiates(Event, Fluent, Time), 0<Offset, trajectory(Fluent, Time, Fluent2, Offset), not(clipped(Time, Fluent, Time+Offset)) ->
  410	holds_at(Fluent2, Time+Offset).
  411
  412% ectest/ec_reader_test_foundations.e:253
  413% 
  414% 
  415% ectest/ec_reader_test_foundations.e:255
  416% [event,fluent,fluent2,offset,time]% 
  417% Happens(event,time) &
  418% Terminates(event,fluent,time) &
  419% 0 < offset &
  420% AntiTrajectory(fluent,time,fluent2,offset) &
  421% !Declipped(time,fluent,time+offset) ->
  422% HoldsAt(fluent2,time+offset).
  423happens(Event, Time), terminates(Event, Fluent, Time), 0<Offset, antiTrajectory(Fluent, Time, Fluent2, Offset), not(declipped(Time, Fluent, Time+Offset)) ->
  424	holds_at(Fluent2, Time+Offset).
  425
  426% ectest/ec_reader_test_foundations.e:261
  427% 
  428% 
  429% ; End of file.
  430% ectest/ec_reader_test_foundations.e:264
  431% translate: ending  File: ectest/ec_reader_test_foundations.e.pro