1/*   vcard_values
    2     Author: poo.
    3
    4     Copyright (C) 2018 poo
    5
    6     This program is free software: you can redistribute it and/or modify
    7     it under the terms of the GNU General Public License as published by
    8     the Free Software Foundation, either version 3 of the License, or
    9     at your option) any later version.
   10
   11     This program is distributed in the hope that it will be useful,
   12     but WITHOUT ANY WARRANTY; without even the implied warranty of
   13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14     GNU General Public License for more details.
   15
   16     You should have received a copy of the GNU General Public License
   17     along with this program.  If not, see <http://www.gnu.org/licenses/>.
   18
   19     09 jun 2018
   20*/
   21
   22
   23:- module(vcard_values, [
   24	      integer_list//1,
   25	      float_list//1,
   26	      date_list//1	      
   27	  ]).

vcard_values: VCard Values Interpretation

Predicates for parsing and intepreting VCard values. */

   33:- ensure_loaded(library(dcg/basics)).   34
   35
   36sign(`-`) --> "-", !.
   37sign(`+`) --> "+".
 integer_value(-Value:codes)//
integer = [sign] 1*DIGIT

*/

   46integer_value(Value) --> sign(Sign), !, digits(Digits),
   47			 { append(Sign, Digits, Value1),
   48			   number_codes(Value, Value1) }.
   49integer_value(Value) --> digits(Value1),
   50			 {number_codes(Value, Value1)}.
 integer_list(Values)//
integer-list = integer *("," integer)
Arguments:
Values- a list of integer. */
   61integer_list([Value|Rest]) --> integer_value(Value), ",", !, 
   62			      integer_list(Rest).
   63integer_list([Value]) --> integer_value(Value).
   64
   65
   66
   67
   68/*
   69   value(-Value: list)//
   70
   71```
   72     value = text
   73           / text-list
   74           / date-list
   75           / time-list
   76           / date-time-list
   77           / date-and-or-time-list
   78           / timestamp-list
   79           / boolean
   80           / integer-list
   81           / float-list
   82           / URI               ; from Section 3 of [RFC3986]
   83           / utc-offset
   84           / Language-Tag
   85           / iana-valuespec
   86       ; Actual value type depends on property name and VALUE parameter.
   87```
   88*/
 text_value(-Value:code)//
Return the text value. We use folded_string//1 for text folding support.
text = *TEXT-CHAR
TEXT-CHAR = "\\" / "\," / "\n" / WSP / NON-ASCII
               / %x21-2B / %x2D-5B / %x5D-7E
        ; Backslashes, commas, and newlines must be encoded.

*/

  117text_value(Value) --> folded_string(Value).
 boolean_value(-Value:code)//
boolean = "TRUE" / "FALSE"

*/

  126boolean_value(true) --> "TRUE", !.
  127boolean_value(false) --> "FALSE".
 float_value(-Value:float)//
float   = [sign] 1*DIGIT ["." 1*DIGIT]

*/

  136float_value(Value) --> ( sign(Sign) | {Sign = []}), !,
  137		       digits(Digits),
  138		       (".", !, digits(Digits2) | {Digits2 = `0`} ),
  139		       { append([Sign, Digits, `.`, Digits2], Value1),
  140			 number_codes(Value, Value1) }.		
  141
  142float_list([Value|Rest]) --> float(Value), ",", !,
  143			    float_list(Rest).
  144float_list([Value]) --> float(Value).
 date_value(-Value:pred)//
Parse a date value. If year, month or day is not provided, then it will be assigned a zero value.

No number range checks is performed on Month an Day values.

date = year [month  day]
     / year "-" month
     / "--"     month [day]
     / "--"      "-"   day
Arguments:
Value- a date/3 predicate date(Year: int, Month: int, Day: int). */
  163date_value(date(0,0,D2)) --> "---", !, 
  164			     day_value(D), {number_codes(D2, D)}.
  165date_value(date(0,M2,D2)) --> "--", !, 
  166			      month_value(M), (day_value(D),! | {D = `0`}),
  167			      {number_codes(M2,M), number_codes(D2, D)}.
  168date_value(date(Y2,M2,0)) --> year_value(Y), "-", !, 
  169			      month_value(M),
  170			    {number_codes(Y2, Y), number_codes(M2, M)}.
  171date_value(date(Y2,M2,D2)) --> year_value(Y),
  172			       ( month_value(M) , day_value(D) |
  173				 {M = `0`, D = `0`} ), !,
  174			       {number_codes(Y2, Y), number_codes(M2, M),
  175				number_codes(D2, D)}.
 year_value(-Year:codes)//
year   = 4DIGIT  ; 0000-9999

*/

  185year_value([C1, C2, C3, C4]) --> digit(C1), digit(C2), digit(C3), digit(C4).
 month_value(-Month:codes)//
No range check is performed.
month  = 2DIGIT  ; 01-12

*/

  195month_value([C1, C2]) --> digit(C1), digit(C2).
 day_value(-Day:codes)//
No range check is performed.
day = 2DIGIT  ; 01-28/29/30/31 depending on month and leap year

*/

  205day_value([C1, C2]) --> digit(C1), digit(C2).
  206
  207
  208date_list([Value|Rest]) --> date_value(Value), ",", !,
  209			   date_list(Rest).
  210date_list([Value]) --> date_value(Value)