9month('Jan',1,31).
   10month('Feb',2,29).
   11month('Mar',3,31).
   12month('Apr',4,30).
   13month('May',5,31).
   14month('Jun',6,30).
   15month('Jul',7,31).
   16month('Aug',8,31).
   17month('Sep',9,30).
   18month('Oct',10,31).
   19month('Nov',11,30).
   20month('Dec',12,31).
   21
   22dayOfWeek('monday','Mon').
   23dayOfWeek('tuesday','Tue').
   24dayOfWeek('wednesday','Wed').
   25dayOfWeek('thursday','Thu').
   26dayOfWeek('friday','Fri').
   27dayOfWeek('saturday','Sat').
   28dayOfWeek('sunday','Sun').
   29
   30number_addendum(1,'st').
   31number_addendum(2,'nd').
   32number_addendum(3,'rd').
   33number_addendum(4,'th').
   34number_addendum(5,'th').
   35number_addendum(6,'th').
   36number_addendum(7,'th').
   37number_addendum(8,'th').
   38number_addendum(9,'th').
   39number_addendum(10,'th').
   40number_addendum(11,'th').
   41number_addendum(12,'th').
   42number_addendum(12,'th').
   43number_addendum(13,'th').
   44number_addendum(14,'th').
   45number_addendum(15,'th').
   46number_addendum(16,'th').
   47number_addendum(17,'th').
   48number_addendum(18,'th').
   49number_addendum(19,'th').
   50number_addendum(20,'th').
   51number_addendum(21,'st').
   52number_addendum(22,'nd').
   53number_addendum(23,'rd').
   54number_addendum(24,'th').
   55number_addendum(25,'th').
   56number_addendum(26,'th').
   57number_addendum(27,'th').
   58number_addendum(28,'th').
   59number_addendum(29,'th').
   60number_addendum(30,'th').
   61number_addendum(31,'st').
   62
   63
   64long_to_short_day_of_month(L,S) :-
   65	number_addendum(S,Ext),
   66	atomic_list_concat([S,Ext],'',L).
   67
   68getEvents(Events,Comparison) :-
   69	setof([A,B],Y^M^D^H^Mi^S^Z^(significantDateForEvent(A,[Y-M-D,H:Mi:S]),
   70		       Z = [Y-M-D,H:Mi:S],
   71		       julian:form_time(Z,B)),List),
   72	setof(Date,Key^member([Key,Date],List),Dates),
   73	predsort(julian:compare_time,Dates,Tmp1),
   74	setof(Date,Tmp1^member(Date,Tmp1),SortedDates),
   76	
   77	getCurrentDateTime(Now),
   79	findall([[PrintedDateTime,EnglishDescription,Gloss],Tasks],
   80		(
   81		 member(Date,SortedDates),
   82		 julian:form_time([Date,[Y-M-D,H:Mi:S]]),
   83		 printDateTime([Y-M-D,H:Mi:S],PrintedDateTime),
   84		 julian:compare_time(Comparison,Now,[Y-M-D,H:Mi:S]),
   85		 DateTime = [Y-M-D,H:Mi:S],
   86		 findall([task(TaskID2,Desc),MeetingAgenda,MeetingParticipants,MeetingLocations,MeetingPhoneNumbers],
   87			 (member([TaskID2,Date],List),
   88			  meetingInfo(TaskID2,_,Desc,MeetingParticipants,MeetingAgenda,MeetingLocations,MeetingPhoneNumbers)),
   89			 Tasks),
   90		 englishDescriptionOfTimeUntil(Now,[Y-M-D,H:Mi:S],EnglishDescription),
   91		 generateGlossFor([Y-M-D,H:Mi:S],Gloss)
   92		 ),
   93		Events)
   93.
   94
   95meetingInfo(TaskID,DateTime,Desc,MeetingParticipants,MeetingAgenda,MeetingLocations,MeetingPhoneNumbers) :-
   96	significantDateForEvent(TaskID,DateTime),
   97	description(TaskID,Desc),
   98	meetingAgenda(TaskID,MeetingParticipants,MeetingAgenda),
   99	meetingLocations(TaskID,MeetingLocations),
  100	meetingPhoneNumbers(TaskID,MeetingParticipants,MeetingPhoneNumbers).
  101
  102generateGlossFor([Y-M-D,H:Mi:S],Gloss) :-
  103	form_time([dow(DayOfWeek),Y-M-D]),
  104	dayOfWeek(DayOfWeek,DOW),
  105	month(Month,M,_),
  106	long_to_short_day_of_month(DayOfMonth,D),
  107	(H > 12 -> (H12 is H - 12, AmPm = 'PM') ;
  108	 (H = 12 -> (H12 is 12, AmPm = 'PM') ;
  109	  (H = 0 -> (H12 is 12, AmPm = 'AM') ;
  110	   (H < 12 -> (H12 is H, AmPm = 'AM'))))),
  111	format(atom(Mi0),'~|~`0t~w~2|', Mi),
  112	atomic_list_concat([DOW,' ',Month,' ',DayOfMonth,' ',Y,' at ',H12,':',Mi0,' ',AmPm],Gloss),!.
  132sortDeadlines(Deadlines) :-
  133	findall([X,Y],(deadline(X,Z),julian:form_time(Z,Y)),List),
  135	setof(Date,Key^member([Key,Date],List),Dates),
  137	predsort(julian:compare_time,Dates,SortedDates),
  138	findall([DateTime,Tasks],
  139		(
  140		 member(Date,SortedDates),
  141		 julian:form_time([Date,[Y-M-D,H:Mi:S]]),
  142		 DateTime = [Y-M-D,H:Mi:S],
  143		 findall(TaskID2,(member([TaskID2,Date2],List),Date=Date2),Tasks)
  144		),
  145		Deadlines)
  145.
  146
  147englishDescriptionOfTimeUntil(From,To,EnglishDescription) :-
  148	julian_daysUntilDate_precise(From,To,_,DaysEstimated),
  150	Abs is abs(DaysEstimated),
  152	((DaysEstimated < 0) ->
  153	 (
  154	  FloorDays is floor(Abs),
  155	  (Abs > 1.0) -> ((Abs < 2.0) -> (Template = ['1 day ago',[]]) ; (Template = ['~d days ago',[FloorDays]])) ;
  156	  (
  157	   
  158	   Hours is Abs * 24.0,
  160	   FloorHours is floor(Hours),
  162	   
  163	   ((Hours > 1.0) -> ((Hours < 2.0) -> (Template = ['1 hour ago',[]]) ; (Template = ['~d hours ago',[FloorHours]])) ;
  164	   (
  165	    
  166	    Minutes is Hours * 60.0,
  168	    FloorMinutes is floor(Minutes),
  170	    (Minutes > 1.0) -> ((Minutes < 2.0) -> (Template = ['1 minute ago',[]]) ; (Template = ['~d minutes ago',[FloorMinutes]])) ;
  171	    (Template = ['less than a minute ago',[]]))
  171)
  171)
  171)
  171 ;
  172	 (
  173	  FloorDays is floor(Abs),
  174	  (Abs > 1.0) -> ((Abs < 2.0) -> (Template = ['in 1 day',[]]) ; (Template = ['in ~d days',[FloorDays]])) ;
  175	  (
  176	   
  177	   Hours is Abs * 24.0,
  179	   FloorHours is floor(Hours),
  181	   
  182	   ((Hours > 1.0) -> ((Hours < 2.0) -> (Template = ['in 1 hour',[]]) ; (Template = ['in ~d hours',[FloorHours]])) ;
  183	   (
  184	    
  185	    Minutes is Hours * 60.0,
  187	    FloorMinutes is floor(Minutes),
  189	    (Minutes > 1.0) -> ((Minutes < 2.0) -> (Template = ['in 1 minute',[]]) ; (Template = ['in ~d minutes',[FloorMinutes]])) ;
  190	    (Template = ['less than in a minute',[]]))
  190)
  190)
  190)
  191	)
  191,
  192	append([atom(EnglishDescription)],Template,Appended),
  193	Call =.. [format|Appended],
  194	Call
  194.
  195
  196printDateTime([Y-M-D,H:Mi:S],PrintedDateTime) :-
  198	format(atom(PrintedDateTime),'~d-~d-~d,~d:~d:~d',[Y,M,D,H,Mi,S])
  198.
  199
  200getCurrentDateTime(DateTime) :-
  201	currentTimeZone(TimeZone),
  202	getCurrentDateTimeForTimeZone(TimeZone,DateTime).
  203
  204getCurrentDate([TmpDate]) :-
  205	currentTimeZone(TimeZone),
  206	getCurrentDateTimeForTimeZone(TimeZone,[TmpDate,_]).
  207
  208getCurrentTime([TmpTime]) :-
  209	currentTimeZone(TimeZone),
  210	getCurrentDateTimeForTimeZone(TimeZone,[_,TmpTime]).
  214hasUTCOffset(utc,0).
  215hasUTCOffset(centralDaylightTime,5).
  216hasUTCOffset(centralStandardTime,6).
  217
  218convertUTCDateTimeToTimeZoneDateTime(UTCDateTime,TimeZone,[Y-M-D,H:Mi:S]) :-
  219	hasUTCOffset(TimeZone,Offset),
  220	DTs is Offset * 60 * 60,
  221	delta_time([Y-M-D,H:Mi:S], s(DTs), UTCDateTime).
  222
  223getCurrentDateTimeForTimeZone(TimeZone,[Y-M-D,H:Mi:S]) :-
  224	getCurrentUTCDateTime(UTCDateTime),
  225	convertUTCDateTimeToTimeZoneDateTime(UTCDateTime,TimeZone,[Y-M-D,H:Mi:S]).
  226
  227getCurrentUTCDateTime([Y-M-D,H:Mi:S]) :-
  228	julian:form_time([now,[Y-M-D,H:Mi:S]]).
  229
  230render(auroraIllinois,'Aurora').
  231render(stCharlesIllinois,'St. Charles').
  232render(napervilleIllinois,'Naperville').
  233
  234renderObject(Object,Output) :-
  235	Object = addressFn(StreetAddress,City,State,ZipCode),
  236	render(City,CityTmp),
  237	atomic_list_concat([CityTmp,','],'',CityRendered),
  238	capitalize(State,StateRendered),
  239	((StreetAddress = houseNumberFn(Number,Street)) ->
  240	 (atomic_list_concat([Number,Street,CityRendered,StateRendered,ZipCode],' ',Output)) ;
  241	 (atomic_list_concat([StreetAddress,CityRendered,StateRendered,ZipCode],' ',Output))).
  242
  243meetingAgenda(TaskID,MeetingParticipants,MeetingAgenda) :-
  244	eventParticipants(TaskID,Participants),
  245	Participants =.. [groupFn|[MeetingParticipants]],
  246	findall(Point,(hasMeetingAgenda(TaskID,Agenda),member(Point,Agenda)),MeetingAgenda).
  260non_empty_list(List) :-
  261	length(List,Length),
  262	Length > 0.
  263
  264meetingLocations(TaskID,MeetingLocations) :-
  265	setof([Term,Location],
  266	      TaskID^Description^Address^(description(TaskID,Description),
  267					  term_contains_subterm(Term,Description),
  268					  hasAddress(Term,Address),
  269					  renderObject(Address,Location)),
  270	      MeetingLocations) ->
  271	true ;
  272	MeetingLocations = [].
  273
  274meetingPhoneNumbers(TaskID,MeetingParticipants,MeetingPhoneNumbers) :-
  275	setof([Term,MeetingPhoneNumber],
  276		TaskID^Description^Term^MeetingParticipants^(((description(TaskID,Description),term_contains_subterm(Term,Description)) ;
  277		  term_contains_subterm(Term,MeetingParticipants)),
  278		 hasPhoneNumberSequence(Term,MeetingPhoneNumber)),
  279		MeetingPhoneNumbers).
  280
  281
  282meetingPhoneNumbersHuh(TaskID,MeetingParticipants,MeetingPhoneNumbers) :-
  283	findall(MeetingPhoneNumber,
  284		(((description(TaskID,Description),
  285		  term_contains_subterm(Term,Description)) ;
  286		  term_contains_subterm(Term,MeetingParticipants)),
  287		 hasPhoneNumberSequence(Term,MeetingPhoneNumber)),
  288		MeetingPhoneNumbers).
  289
  290listFactsAboutTask(TaskID,Facts) :-
  291	description(TaskID,Desc),
  292	meetingAgenda(TaskID,MeetingParticipants,MeetingAgenda),
  293	meetingLocations(TaskID,MeetingLocations),
  294	meetingPhoneNumbers(TaskID,MeetingParticipants,MeetingPhoneNumbers),
  295	Facts = [MeetingParticipants,MeetingAgenda,MeetingPhoneNumbers].
  296
  297createNewEvent([DateArg,SpecificationArg,ParticipantsArg,AgendaArg],Results) :-
  298	newId(AppointmentID),
  299
  300	parseForm(date,DateArg,Date),
  301	parseForm(specification,SpecificationArg,Specification),
  302	parseForm(participants,ParticipantsArg,Participants),
  303	parseForm(agenda,AgendaArg,Agenda),
  304
  305	assertz(appointment(AppointmentID,Participants,Specification)),
  306	assertz(deadline(AppointmentID,Date)),
  307	assertz(hasMeetingAgenda(TaskID,Agenda)).
  308
  309parseForm(date,DateArg,Date) :-
  310	Dates = ['next monday','tomorrow','yesterday','this tuesday','easter'],
  311	Times = ['in 3 hours','15 minutes from now','tonight','first thing in the morning'],
  312	true.
  313parseForm(specification,SpecificationArg,Specification) :-
  314	true.
  315parseForm(participants,ParticipantsArg,Participants) :-
  316	split_string(ParticipantsArg, ",", "", Items),
  317	true.
  318parseForm(agenda,AgendaArg,Agenda) :-
  319	true.
  320
  321dateTimeP([Y-M-D,H:Mi:S]) :-
  322	true