1:- module(julian_lang_en, [english_form//1]).    2
    3:- use_module(library(clpfd)).    4:- use_module(library(dcg/basics), [ integer//1
    5                                   , string//1
    6                                   ]).    7:- use_module(library(lambda)).    8:- use_module(library(julian/util), [dow_number/2]).    9:- use_module(library(julian/calendar/gregorian), [month_number/2]).   10
   11
   12:- multifile julian:form_time/2.   13julian:form_time(english(English), Dt) :-
   14    once(phrase(julian_lang_en:english_form(Form), English)),
   15    !,
   16    form_time(Form, Dt).
   17
   18% TODO implement the module
   19% TODO make string//1 an argument like Separator
   20% TODO so that I can call phrase(split(comma, day_of_week, Parts), Xs)
   21:- meta_predicate split(//,*,*,*).   22split(Separator, [Part|Parts]) -->
   23    string(Part),
   24    Separator,
   25    split(Separator, Parts).
   26split(_, [Part], Part, []).
   27
   28
   29end_of_content([],[]).
   30
   31
   32comma --> " and ".
   33comma --> " or ".
   34comma --> ", ".
   35comma --> ",".
   36
   37
   38within --> " during ".
   39within --> " in ".
   40within --> " of ".
   41
   42ordinal(N) -->
   43    ordinal_short(N).
   44ordinal(N) -->
   45    ordinal_long(N).
   46
   47ordinal_long(1) --> "first".
   48ordinal_long(2) --> "second".
   49ordinal_long(3) --> "third".
   50ordinal_long(4) --> "fourth".
   51ordinal_long(5) --> "fifth".
   52
   53ordinal_short(N) -->
   54    integer(N),
   55    ( "th"; "st"; "nd"; "rd" ).
   56
   57
   58parity(X) -->
   59    "even",
   60    !,
   61    { X mod 2 #= 0 }.
   62parity(X) -->
   63    "odd",
   64    !,
   65    { X mod 2 #= 1 }.
   66
   67
   68% True if Day is an atom representing the day of week named in Codes
   69codes_dow(Codes, Day) :-
   70    atom_codes(Atom, Codes),
   71    downcase_atom(Atom, Day),
   72    dow_number(Day, _).
   73
   74
   75% True if Month is an atom representing the month named in Codes
   76codes_month(Codes, Month) :-
   77    atom_codes(Atom, Codes),
   78    downcase_atom(Atom, Month),
   79    month_number(Month, _).
 english_form(-Form)//
Parse an English language date or time phrase into a library(julian) form. One usually interacts with library(julian/lang/en) by calling Julian's form_time/2 predicate using the english/1 form. For example, form_time(english("tuesday or thursday in April"), Dt). However, it's sometimes convenient to separate the parsing and constraining steps. In that case, call english_form//1 directly:
?- phrase(english_form(Form), "tuesday or thursday in April").
Form = [month(april), dow([tuesday, thursday])].

This predicate is declared multifile so that you can add additional English phrases to suit your needs. Perhaps defining what "summer" means to you:

julian_lang_en:english_form(month([june,july,august])) -->
    "summer".
  100:- multifile english_form//1.  101english_form(true) -->
  102    "each day",
  103    end_of_content,
  104    !.
  105english_form(weekday) -->
  106    "weekday",
  107    end_of_content,
  108    !.
  109english_form(dow(Day)) -->
  110    string(Word),
  111    end_of_content,
  112    { codes_dow(Word, Day) },
  113    !.
  114english_form(dow(Days)) -->
  115    split(comma, Words),
  116    { maplist(codes_dow, Words, Days) },
  117    !.
  118english_form(month(Month)) -->
  119    string(Word),
  120    end_of_content,
  121    { codes_month(Word, Month) },
  122    !.
  123english_form(month(Months)) -->
  124    split(comma, Words),
  125    { maplist(codes_month, Words, Months) },
  126    !.
  127english_form(gregorian(Y,M,_)) -->
  128    string(Word),
  129    { codes_month(Word, Month) },
  130    { month_number(Month, M) },
  131    " ",
  132    integer(Y),
  133    end_of_content,
  134    { Y > 999 },
  135    !.
  136english_form(gregorian(_,M,D)) -->
  137    string(Word),
  138    { codes_month(Word, Month) },
  139    { month_number(Month, M) },
  140    " ",
  141    ordinal(D),
  142    end_of_content,
  143    !.
  144english_form(gregorian(Y,_,_)) -->
  145    parity(Y),
  146    " years",
  147    end_of_content,
  148    !.
  149english_form([A,B|T]) -->  % list of at least two elements (indexable)
  150    { Forms = [A,B|T] },
  151    split(within, Parts),
  152    { length(Parts, N), N > 1 },
  153    { maplist(\Part^Form^once(phrase(english_form(Form),Part)), Parts, Fs) },
  154    !,
  155    % optimization: constraints on the end are usually more concrete
  156    { reverse(Fs, Forms) }.
  157english_form(nth(-1,Form)) -->
  158    "final ",
  159    english_form(Form),
  160    !.
  161english_form(nth([N0,N1],Form)) -->
  162    ordinal(N0),
  163    comma,
  164    ordinal(N1),
  165    " ",
  166    english_form(Form),
  167    !.
  168english_form(nth(N,Form)) -->
  169    ordinal(N),
  170    " ",
  171    english_form(Form),
  172    !