| 12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151115211531154115511561157115811591160116111621163116411651166116711681169117011711172117311741175117611771178117911801181118211831184118511861187118811891190119111921193119411951196119711981199120012011202120312041205120612071208120912101211121212131214121512161217121812191220122112221223122412251226122712281229123012311232123312341235123612371238123912401241124212431244124512461247124812491250125112521253125412551256125712581259126012611262126312641265126612671268126912701271127212731274127512761277127812791280128112821283128412851286128712881289129012911292129312941295129612971298129913001301130213031304130513061307130813091310131113121313131413151316131713181319132013211322132313241325132613271328132913301331133213331334133513361337133813391340134113421343134413451346134713481349135013511352135313541355135613571358135913601361136213631364136513661367136813691370137113721373137413751376137713781379138013811382138313841385138613871388138913901391139213931394139513961397139813991400140114021403140414051406140714081409141014111412141314141415141614171418141914201421142214231424142514261427142814291430143114321433143414351436143714381439144014411442144314441445144614471448144914501451145214531454145514561457145814591460146114621463146414651466146714681469147014711472147314741475147614771478147914801481148214831484148514861487148814891490149114921493149414951496149714981499150015011502150315041505150615071508150915101511151215131514151515161517151815191520152115221523152415251526152715281529153015311532153315341535153615371538153915401541154215431544154515461547154815491550155115521553155415551556155715581559156015611562156315641565156615671568156915701571157215731574157515761577157815791580158115821583158415851586158715881589159015911592159315941595159615971598159916001601160216031604160516061607160816091610161116121613161416151616161716181619 | {    *********************************************************************    Copyright (C) 1997, 1998 Gertjan Schouten    See the file COPYING.FPC, included in this distribution,    for details about the copyright.    This program is distributed in the hope that it will be useful,    but WITHOUT ANY WARRANTY; without even the implied warranty of    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. **********************************************************************    System Utilities For Free Pascal}{==============================================================================}{   internal functions                                                         }{==============================================================================}Function DoEncodeDate(Year, Month, Day: Word): longint;Var  D : TDateTime;begin  If TryEncodeDate(Year,Month,Day,D) then    Result:=Trunc(D)  else    Result:=0;end;function DoEncodeTime(Hour, Minute, Second, MilliSecond: word): TDateTime;begin  If not TryEncodeTime(Hour,Minute,Second,MilliSecond,Result) then    Result:=0;end;{==============================================================================}{   Public functions                                                           }{==============================================================================}{   ComposeDateTime converts a Date and a Time into one TDateTime   }function ComposeDateTime(Date,Time : TDateTime) : TDateTime;begin  if Date < 0 then Result := trunc(Date) - Abs(frac(Time))  else Result := trunc(Date) + Abs(frac(Time));end;{   DateTimeToTimeStamp converts DateTime to a TTimeStamp   }function DateTimeToTimeStamp(DateTime: TDateTime): TTimeStamp;Var  D : Double;begin  D:=DateTime * Single(MSecsPerDay);  if D<0 then    D:=D-0.5  else    D:=D+0.5;  result.Time := Abs(Trunc(D)) Mod MSecsPerDay;  result.Date := DateDelta + Trunc(D) div MSecsPerDay;end;{   TimeStampToDateTime converts TimeStamp to a TDateTime value   }function TimeStampToDateTime(const TimeStamp: TTimeStamp): TDateTime;begin  Result := ComposeDateTime(TimeStamp.Date - DateDelta,TimeStamp.Time / MSecsPerDay)end;{   MSecsToTimeStamp   }function MSecsToTimeStamp(MSecs: comp): TTimeStamp;var  D1:Int64;begin  D1:=Trunc(msecs);  result.Date := D1 div msecsperday;  result.Time := D1 - result.date * msecsperday;end;{   TimeStampToMSecs   }function TimeStampToMSecs(const TimeStamp: TTimeStamp): comp;begin  result := TimeStamp.Time + comp(timestamp.date)*msecsperday;end;Function TryEncodeDate(Year,Month,Day : Word; Out Date : TDateTime) : Boolean;var  c, ya: cardinal;begin  Result:=(Year>0) and (Year<10000) and          (Month in [1..12]) and          (Day>0) and (Day<=MonthDays[IsleapYear(Year),Month]); If Result then   begin     if month > 2 then      Dec(Month,3)     else      begin        Inc(Month,9);        Dec(Year);      end;     c:= Year DIV 100;     ya:= Year - 100*c;     Date := (146097*c) SHR 2 + (1461*ya) SHR 2 + (153*cardinal(Month)+2) DIV 5 + cardinal(Day);     // Note that this line can't be part of the line above, since TDateTime is     // signed and c and ya are not     Date := Date - 693900;   endend;function TryEncodeTime(Hour, Min, Sec, MSec:word; Out Time : TDateTime) : boolean;begin  Result:=((Hour<24) and (Min<60) and (Sec<60) and (MSec<1000)) or    { allow leap second }    ((Hour=23) and (Min=59) and (Sec=60) and (MSec<1000));  If Result then    Time:=TDateTime(cardinal(Hour)*3600000+cardinal(Min)*60000+cardinal(Sec)*1000+MSec)/MSecsPerDay;end;{   EncodeDate packs three variables Year, Month and Day into a    TDateTime value the result is the number of days since 12/30/1899   }function EncodeDate(Year, Month, Day: word): TDateTime;begin  If Not TryEncodeDate(Year,Month,Day,Result) then    Raise EConvertError.CreateFmt('%d-%d-%d is not a valid date specification',                              [Year,Month,Day]);end;{   EncodeTime packs four variables Hour, Minute, Second and MilliSecond into    a TDateTime value     }function EncodeTime(Hour, Minute, Second, MilliSecond:word):TDateTime;begin  If not TryEncodeTime(Hour,Minute,Second,MilliSecond,Result) then    Raise EConvertError.CreateFmt('%d:%d:%d.%d is not a valid time specification',                              [Hour,Minute,Second,MilliSecond]);end;{   DecodeDate unpacks the value Date into three values:    Year, Month and Day   }procedure DecodeDate(Date: TDateTime; out Year, Month, Day: word);var  ly,ld,lm,j : cardinal;begin  if Date <= -datedelta then  // If Date is before 1-1-1 then return 0-0-0    begin    Year := 0;    Month := 0;    Day := 0;    end  else    begin    if Date>0 then      Date:=Date+1/(msecsperday*2)    else        Date:=Date-1/(msecsperday*2);    if Date>MaxDateTime then      Date:=MaxDateTime;//       Raise EConvertError.CreateFmt('%f is not a valid TDatetime encoding, maximum value is %f.',[Date,MaxDateTime]);    j := pred((longint(Trunc(System.Int(Date))) + 693900) SHL 2);    ly:= j DIV 146097;    j:= j - 146097 * cardinal(ly);    ld := j SHR 2;    j:=(ld SHL 2 + 3) DIV 1461;    ld:= (cardinal(ld) SHL 2 + 7 - 1461*j) SHR 2;    lm:=(5 * ld-3) DIV 153;    ld:= (5 * ld +2 - 153*lm) DIV 5;    ly:= 100 * cardinal(ly) + j;    if lm < 10 then     inc(lm,3)    else      begin        dec(lm,9);        inc(ly);      end;    year:=ly;    month:=lm;    day:=ld;    end;end;function DecodeDateFully(const DateTime: TDateTime; out Year, Month, Day, DOW: Word): Boolean;begin  DecodeDate(DateTime,Year,Month,Day);  DOW:=DayOfWeek(DateTime);  Result:=IsLeapYear(Year);end;{   DecodeTime unpacks Time into four values:    Hour, Minute, Second and MilliSecond    }procedure DecodeTime(Time: TDateTime; out Hour, Minute, Second, MilliSecond: word);Var  l : cardinal;begin l := DateTimeToTimeStamp(Time).Time; Hour   := l div 3600000; l := l mod 3600000; Minute := l div 60000; l := l mod 60000; Second := l div 1000; l := l mod 1000; MilliSecond := l;end;{   DateTimeToSystemTime converts DateTime value to SystemTime   }procedure DateTimeToSystemTime(DateTime: TDateTime; out SystemTime: TSystemTime);begin  DecodeDateFully(DateTime, SystemTime.Year, SystemTime.Month, SystemTime.Day,SystemTime.DayOfWeek);  DecodeTime(DateTime, SystemTime.Hour, SystemTime.Minute, SystemTime.Second, SystemTime.MilliSecond);  Dec(SystemTime.DayOfWeek);end ;{   SystemTimeToDateTime converts SystemTime to a TDateTime value   }function SystemTimeToDateTime(const SystemTime: TSystemTime): TDateTime;begin  result := ComposeDateTime(DoEncodeDate(SystemTime.Year, SystemTime.Month, SystemTime.Day),                            DoEncodeTime(SystemTime.Hour, SystemTime.Minute, SystemTime.Second, SystemTime.MilliSecond));end ;{   DayOfWeek returns the Day of the week (sunday is day 1)  }function DayOfWeek(DateTime: TDateTime): integer;begin  Result := 1 + ((Trunc(DateTime) - 1) mod 7);  If (Result<=0) then    Inc(Result,7);end;{   Date returns the current Date   }function Date: TDateTime;var  SystemTime: TSystemTime;begin  GetLocalTime(SystemTime);  result := DoEncodeDate(SystemTime.Year, SystemTime.Month, SystemTime.Day);end ;{   Time returns the current Time   }function Time: TDateTime;var  SystemTime: TSystemTime;begin  GetLocalTime(SystemTime);  Result := DoEncodeTime(SystemTime.Hour,SystemTime.Minute,SystemTime.Second,SystemTime.MilliSecond);end ;{   Now returns the current Date and Time    }function Now: TDateTime;var  SystemTime: TSystemTime;begin  GetLocalTime(SystemTime);  result := systemTimeToDateTime(SystemTime);end;{   NowUTC returns the current UTC Date and Time if available on the OS. If not, local date is returned   }function NowUTC: TDateTime;var  SystemTime: TSystemTime;begin  if not GetUniversalTime(SystemTime) then    GetLocalTime(SystemTime);  result := systemTimeToDateTime(SystemTime);end;{   IncMonth increments DateTime with NumberOfMonths months,    NumberOfMonths can be less than zero   }function IncMonth(const DateTime: TDateTime; NumberOfMonths: integer = 1 ): TDateTime;var  Year, Month, Day : word;begin  DecodeDate(DateTime, Year, Month, Day);  IncAMonth(Year, Month, Day, NumberOfMonths);  result := ComposeDateTime(DoEncodeDate(Year, Month, Day), DateTime);end ;{   IncAMonth is the same as IncMonth, but operates on decoded date  }procedure IncAMonth(var Year, Month, Day: Word; NumberOfMonths: Integer = 1);var  TempMonth, S: Integer;begin  If NumberOfMonths>=0 then    s:=1  else    s:=-1;  inc(Year,(NumberOfMonths div 12));  TempMonth:=Month+(NumberOfMonths mod 12)-1;  if (TempMonth>11) or     (TempMonth<0) then   begin     Dec(TempMonth, S*12);     Inc(Year, S);   end;  Month:=TempMonth+1;          {   Months from 1 to 12   }  If (Day>MonthDays[IsLeapYear(Year)][Month]) then    Day:=MonthDays[IsLeapYear(Year)][Month];end;{  IsLeapYear returns true if Year is a leap year   }function IsLeapYear(Year: Word): boolean;begin  Result := (Year mod 4 = 0) and ((Year mod 100 <> 0) or (Year mod 400 = 0));end;{  DateToStr returns a string representation of Date using ShortDateFormat   }function DateToStr(Date: TDateTime): string;begin  DateTimeToString(Result, 'ddddd', Date);end ;function DateToStr(Date: TDateTime; const FormatSettings: TFormatSettings): string;begin  DateTimeToString(result, FormatSettings.ShortDateFormat, Date, FormatSettings);end;{  TimeToStr returns a string representation of Time using LongTimeFormat   }function TimeToStr(Time: TDateTime): string;begin  DateTimeToString(Result, 'tt', Time);end ;function TimeToStr(Time: TDateTime; const FormatSettings: TFormatSettings): string;begin  DateTimeToString(Result, FormatSettings.LongTimeFormat, Time, FormatSettings);end;{   DateTimeToStr returns a string representation of DateTime using ShortDateFormat and LongTimeFormat   }Const  DateTimeToStrFormat : Array[Boolean] of string = ('c','f');function DateTimeToStr(DateTime: TDateTime; ForceTimeIfZero : Boolean = False): string;begin  DateTimeToString(Result, DateTimeToStrFormat[ForceTimeIfZero], DateTime)end ;function DateTimeToStr(DateTime: TDateTime; const FormatSettings: TFormatSettings; ForceTimeIfZero : Boolean = False): string;begin  DateTimeToString(Result,  DateTimeToStrFormat[ForceTimeIfZero], DateTime ,FormatSettings);end;{   StrToDate converts the string S to a TDateTime value    if S does not represent a valid date value    an EConvertError will be raised   }function IntStrToDate(Out ErrorMsg : AnsiString; const S: PAnsiChar; Len : integer; const useformat : string; const defs:TFormatSettings; separator : AnsiChar = #0): TDateTime;const SInvalidDateFormat = '"%s" is not a valid date format';procedure FixErrorMsg(const errm :ansistring;const errmarg : ansistring);begin  errormsg:=format(errm,[errmarg]);end;var   df:string;   d,m,y,ly:integer;   n,i:longint;   c:word;   dp,mp,yp,which : Byte;   s1:string;   values:array[0..3] of longint;   LocalTime:tsystemtime;   YearMoreThenTwoDigits : boolean;begin  ErrorMsg:='';   Result:=0;  While (Len>0) and (S[Len-1] in [' ',#8,#9,#10,#12,#13]) do    Dec(len);  if (Len=0) then    begin      FixErrorMsg(SInvalidDateFormat,'');      exit;    end;  YearMoreThenTwoDigits := False;  if separator = #0 then    separator := defs.DateSeparator;  df := UpperCase(useFormat);  { Determine order of D,M,Y }  yp:=0;  mp:=0;  dp:=0;  Which:=0;  i:=0;  while (i<Length(df)) and (Which<3) do   begin     inc(i);     Case df[i] of       'Y' :         if yp=0 then          begin            Inc(Which);            yp:=which;          end;       'M' :         if mp=0 then          begin            Inc(Which);            mp:=which;          end;       'D' :         if dp=0 then          begin            Inc(Which);            dp:=which;          end;     end;   end;  for i := 1 to 3 do    values[i] := 0;  s1 := '';  n := 0;  dec(len);  for i := 0 to len do   begin     if s[i] in ['0'..'9'] then      s1 := s1 + s[i];     { space can be part of the shortdateformat, and is defaultly in slovak       windows, therefor it shouldn't be taken as separator (unless so specified)       and ignored }     if (Separator <> ' ') and (s[i] = ' ') then       Continue;     if (s[i] = separator) or ((i = len) and (s[i] in ['0'..'9'])) then      begin        inc(n);        if n>3 then          begin            FixErrorMsg(SInvalidDateFormat,s);            exit;          end;         // Check if the year has more then two digits (if n=yp, then we are evaluating the year.)        if (n=yp) and (length(s1)>2) then YearMoreThenTwoDigits := True;        val(s1, values[n], c);//        Writeln(s1,'->',values[n]);        if c<>0 then          begin            FixErrorMsg(SInvalidDateFormat,s);            Exit;          end;        s1 := '';      end     else if not (s[i] in ['0'..'9']) then       begin         FixErrorMsg(SInvalidDateFormat,s);         Exit;       end;   end ;   if (Which<3) and (N>Which) then    begin    FixErrorMsg(SInvalidDateFormat,s);    Exit;    end;   // Fill in values.  getLocalTime(LocalTime);  ly := LocalTime.Year;  for I:=1 to 3 do    if values[i]>high(Word) then      begin      errormsg:='Invalid date';      exit;      end;  If N=3 then   begin     y:=values[yp];     m:=values[mp];     d:=values[dp];   end  Else  begin    Y:=ly;    If n<2 then     begin       d:=values[1];       m := LocalTime.Month;     end    else     If dp<mp then      begin        d:=values[1];        m:=values[2];      end    else      begin        d:=values[2];        m:=values[1];      end;  end;  if (y >= 0) and (y < 100) and not YearMoreThenTwoDigits then    begin    ly := ly - defs.TwoDigitYearCenturyWindow;    Inc(Y, ly div 100 * 100);    if (defs.TwoDigitYearCenturyWindow > 0) and (Y < ly) then      Inc(Y, 100);    end;  if not TryEncodeDate(y, m, d, result) then    errormsg:='Invalid date';end;function StrToDate(const S: PAnsiChar; Len : integer; const useformat : string; separator : AnsiChar = #0): TDateTime;Var  MSg : AnsiString;begin  Result:=IntStrToDate(Msg,S,Len,useFormat,DefaultFormatSettings,Separator);  If (Msg<>'') then    Raise EConvertError.Create(Msg);end;function StrToDate(const S: string; FormatSettings: TFormatSettings): TDateTime;var  Msg: AnsiString;begin  Result:=IntStrToDate(Msg,PAnsiChar(S),Length(S),FormatSettings.ShortDateFormat,FormatSettings);  if Msg<>'' then    raise EConvertError.Create(Msg);end;function StrToDate(const S: ShortString; const useformat : string; separator : AnsiChar = #0): TDateTime;begin  // S[1] always exists for shortstring. Length 0 will trigger an error.  result := StrToDate(@S[1],Length(s),UseFormat,separator);end;function StrToDate(const S: AnsiString; const useformat : string; separator : AnsiChar = #0): TDateTime;begin  result := StrToDate(PAnsiChar(S),Length(s),UseFormat,separator);end;function StrToDate(const S: ShortString; separator : AnsiChar): TDateTime;begin  // S[1] always exists for shortstring. Length 0 will trigger an error.  result := StrToDate(@S[1],Length(s),DefaultFormatSettings.ShortDateFormat,separator)end;function StrToDate(const S: ShortString): TDateTime;begin  // S[1] always exists for shortstring. Length 0 will trigger an error.  result := StrToDate(@S[1],Length(s),DefaultFormatSettings.ShortDateFormat,#0);end;function StrToDate(const S: AnsiString; separator : AnsiChar): TDateTime;begin    result := StrToDate(PAnsiChar(S),Length(s),DefaultFormatSettings.ShortDateFormat,separator)end;function StrToDate(const S: AnsiString): TDateTime;begin  result := StrToDate(PAnsiChar(S),Length(s),DefaultFormatSettings.ShortDateFormat,#0);end;{   StrToTime converts the string S to a TDateTime value    if S does not represent a valid time value an    EConvertError will be raised   }function IntStrToTime(Out ErrorMsg : AnsiString; const S: PAnsiChar; Len : integer;const defs:TFormatSettings; separator : AnsiChar = #0): TDateTime;const  AMPM_None = 0;  AMPM_AM = 1;  AMPM_PM = 2;  tiHour = 0;  tiMin = 1;  tiSec = 2;  tiMSec = 3;type  TTimeValues = array[tiHour..tiMSec] of Word;var   AmPm: integer;   TimeValues: TTimeValues;    function StrPas(Src : PAnsiChar; len: integer = 0) : ShortString;    begin        //this is unsafe for len > 255, it will trash memory (I tested this)        //reducing it is safe, since whenever we use this a string > 255 is invalid anyway        if len > 255 then len := 255;        SetLength(Result, len);        move(src[0],result[1],len);    end;   function SplitElements(out TimeValues: TTimeValues; out AmPm: Integer): Boolean;   //Strict version. It does not allow #32 as Separator, it will treat it as whitespace always   const     Digits = ['0'..'9'];   var      Cur, Offset, ElemLen, Err, TimeIndex, FirstSignificantDigit: Integer;      Value: Word;      DigitPending, MSecPending: Boolean;      AmPmStr: ShortString;      CurChar: AnsiChar;   begin     Result := False;     AmPm := AMPM_None; //No Am or PM in string found yet     MSecPending := False;     TimeIndex := 0; //indicating which TTimeValue must be filled next     FillChar(TimeValues, SizeOf(TTimeValues), 0);     Cur := 0;     //skip leading blanks     While (Cur < Len) and (S[Cur] =#32) do Inc(Cur);     Offset := Cur;     //First non-blank cannot be Separator or DecimalSeparator     if (Cur > Len - 1) or (S[Cur] = Separator) or (S[Cur] = defs.Decimalseparator) then Exit;     DigitPending := (S[Cur] in Digits);     While (Cur < Len) do     begin       //writeln;       //writeln('Main While loop:  Cur = ',Cur,' S[Cur] = "',S[Cur],'" Len = ',Len);       CurChar := S[Cur];       if CurChar in Digits then       begin//Digits         //HH, MM, SS, or Msec?         //writeln('Digit');         //Digits are only allowed after starting Am/PM or at beginning of string or after Separator         //and TimeIndex must be <= tiMSec         //Uncomment "or (#32 = Separator)" and it will allllow #32 as separator         if (not (DigitPending {or (#32 = Separator)})) or (TimeIndex > tiMSec) then Exit;         OffSet := Cur;         if (CurChar <> '0') then FirstSignificantDigit := OffSet else FirstSignificantDigit := -1;         while (Cur < Len -1) and (S[Cur + 1] in Digits) do         begin           //Mark first Digit that is not '0'           if (FirstSignificantDigit = -1) and (S[Cur] <> '0') then FirstSignificantDigit := Cur;           Inc(Cur);         end;         if (FirstSignificantDigit = -1) then FirstSignificantDigit := Cur;         ElemLen := 1 + Cur - FirstSignificantDigit;         //writeln('  S[FirstSignificantDigit] = ',S[FirstSignificantDigit], ' S[Cur] = ',S[Cur],' ElemLen = ',ElemLen,' -> ', StrPas(S + Offset, ElemLen));         //writeln('  Cur = ',Cur);         //this way we know that Val() will never overflow Value !         if (ElemLen <= 2) or ((ElemLen <= 3) and (TimeIndex = tiMSec) ) then         begin           Val(StrPas(S + FirstSignificantDigit, ElemLen), Value, Err);           //writeln('  Value = ',Value,' HH = ',TimeValues[0],' MM = ',TimeValues[1],' SS = ',TimeValues[2],' MSec = ',Timevalues[3]);           //This is safe now, because we know Value < High(Word)           TimeValues[TimeIndex] := Value;           Inc(TimeIndex);           DigitPending := False;         end         else  Exit; //Value to big, so it must be a wrong timestring       end//Digits       else if (CurChar = #32) then       begin         //writeln('#32');         //just skip, but we must adress this, or it will be parsed by either AM/PM or Separator       end       else if (CurChar = Separator) then       begin         //writeln('Separator');         if DigitPending or (TimeIndex > tiSec) then Exit;         DigitPending := True;         MSecPending := False;       end       else if (CurChar = defs.DecimalSeparator) then       begin         //writeln('DecimalSeparator');         if DigitPending or MSecPending or (TimeIndex <> tiMSec) then Exit;         DigitPending := True;         MSecPending := True;       end       else       begin//AM/PM?         //None of the above, so this AnsiChar _must_ be the start of AM/PM string         //If we already have found AM/PM or we expect a digit then then timestring must be wrong at this point         //writeln('AM/PM?');         if (AmPm <> AMPM_None) or DigitPending then Exit;         OffSet := Cur;         while (Cur < Len -1) and (not (S[Cur + 1] in [Separator, #32, defs.DecimalSeparator]))           and not (S[Cur + 1] in Digits) do Inc(Cur);         ElemLen := 1 + Cur - OffSet;         //writeln('  S[Offset] = ',S[Offset], ' S[Cur] = ',S[Cur],' ElemLen = ',ElemLen,' -> ', StrPas(S + Offset, ElemLen));         //writeln('  Cur = ',Cur);         AmPmStr := StrPas(S + OffSet, ElemLen);         //writeln('AmPmStr = ',ampmstr,' (',length(ampmstr),')');         //We must compare to TimeAMString before hardcoded 'AM' for delphi compatibility         //Also it is perfectly legal, though insane to have TimeAMString = 'PM' and vice versa         if (AnsiCompareText(AmPmStr, defs.TimeAMString) = 0) then AmPm := AMPM_AM         else if (AnsiCompareText(AmPmStr, defs.TimePMString) = 0) then AmPm := AMPM_PM         else if (CompareText(AmPmStr, 'AM') = 0) then AmPm := AMPM_AM         else if (CompareText(AmPmStr, 'PM') = 0) then AmPm := AMPM_PM         else Exit; //If text does not match any of these, timestring must be wrong;         //if AM/PM is at beginning of string, then a digit is mandatory after it         if (TimeIndex = tiHour) then         begin           DigitPending := True;         end         //otherwise, no more TimeValues allowed after this         else         begin           TimeIndex := tiMSec + 1;           DigitPending := False;         end;       end;//AM/PM       Inc(Cur)     end;//while     //If we arrive here, parsing the elements has been successfull     //if not at least Hours specified then input is not valid     //when am/pm is specified Hour must be <= 12 and not 0     if (TimeIndex = tiHour) or ((AmPm <> AMPM_None) and ((TimeValues[tiHour] > 12) or (TimeValues[tiHour] = 0))) or DigitPending then Exit;     Result := True;   end;begin  if separator = #0 then        separator := defs.TimeSeparator;  AmPm := AMPM_None;  if not SplitElements(TimeValues, AmPm) then  begin    ErrorMsg:=Format(SErrInvalidTimeFormat,[StrPas(S, Len)]);    Exit;  end;  if (AmPm=AMPM_PM) and (TimeValues[tiHour]<>12) then Inc(TimeValues[tiHour], 12)  else if (AmPm=AMPM_AM) and (TimeValues[tiHour]=12) then TimeValues[tiHour]:=0;  if not TryEncodeTime(TimeValues[tiHour], TimeValues[tiMin], TimeValues[tiSec], TimeValues[tiMSec], result) Then    //errormsg:='Invalid time.';    ErrorMsg:=Format(SErrInvalidTimeFormat,[StrPas(S, Len)]);end ;function StrToTime(const S: PAnsiChar; Len : integer; separator : AnsiChar = #0): TDateTime;Var  Msg : AnsiString;begin  Result:=IntStrToTime(Msg,S,Len,DefaultFormatSettings,Separator);  If (Msg<>'') then    Raise EConvertError.Create(Msg);end;function StrToTime(const S: string; FormatSettings : TFormatSettings): TDateTime;Var  Msg : AnsiString;begin  Result:=IntStrToTime(Msg, PAnsiChar(S), length(S), FormatSettings, #0);  If (Msg<>'') then    Raise EConvertError.Create(Msg);end;function StrToTime(const s: ShortString; separator : AnsiChar): TDateTime;begin  // S[1] always exists for shortstring. Length 0 will trigger an error.  result := StrToTime(@s[1], length(s), separator);end;function StrToTime(const s: AnsiString; separator : AnsiChar): TDateTime;begin   result := StrToTime(PAnsiChar(S), length(s), separator);end;function StrToTime(const s: ShortString): TDateTime;begin  // S[1] always exists for shortstring. Length 0 will trigger an error.   result := StrToTime(@s[1], length(s), #0);end;function StrToTime(const s: AnsiString): TDateTime;begin   result:= StrToTime(PAnsiChar(s), length(s), #0);end;{   StrToDateTime converts the string S to a TDateTime value    if S does not represent a valid date and/or time value    an EConvertError will be raised   }function SplitDateTimeStr(DateTimeStr: AnsiString; const FS: TFormatSettings; out DateStr, TimeStr: AnsiString): Integer;{ Helper function for StrToDateTime  Pre-condition    Date is before Time    If either Date or Time is omitted then see what fits best, a time or a date (issue #0020522)    Date and Time are separated by whitespace (space Tab, Linefeed or carriage return)    FS.DateSeparator can be the same as FS.TimeSeparator (issue #0020522)    If they are both #32 and TrimWhite(DateTimeStr) contains a #32 a date is assumed.  Post-condition    DateStr holds date as string or is empty    TimeStr holds time as string or is empty    Result = number of strings returned, 0 = error}const  WhiteSpace = [#9,#10,#13,#32];  Space : String = #32; // String, to avoid error 'Cannot decide what overload to call'var  p: Integer;  DummyDT: TDateTime;begin  Result := 0;  DateStr := '';  TimeStr := '';  DateTimeStr := Trim(DateTimeStr);  if Length(DateTimeStr) = 0 then exit;  if (FS.DateSeparator = #32) and (FS.TimeSeparator = #32) and (Pos(#32, DateTimeStr) > 0) then     begin    DateStr:=DateTimeStr;    {      Assume a date: dd [mm [yy]].       Really fancy would be counting the number of whitespace occurrences and decide       and split accordingly    }    Exit(1);     end;  p:=1;  //find separator  if Pos(Space,FS.DateSeparator)=0 then    begin      while (p<Length(DateTimeStr)) and (not (DateTimeStr[p+1] in WhiteSpace)) do       Inc(p);    end  else    begin    p:=Pos(FS.TimeSeparator, DateTimeStr);    if (p<>0) then       repeat        Dec(p);      until (p=0) or (DateTimeStr[p] in WhiteSpace);    end;  //Always fill DateStr, it eases the algorithm later  if (p=0) then     p:=Length(DateTimeStr);  DateStr:=Copy(DateTimeStr,1,p);  TimeStr:=Trim(Copy(DateTimeStr,p+1,MaxInt));  if (Length(TimeStr)<>0) then    Result:=2  else    begin    Result:=1; //found 1 string    // 2 cases when DateTimeStr only contains a time:    // Date/time separator differ, and string contains a timeseparator    // Date/time separators are equal, but transformation to date fails.    if ((FS.DateSeparator<>FS.TimeSeparator) and (Pos(FS.TimeSeparator,DateStr) > 0))       or ((FS.DateSeparator=FS.TimeSeparator) and (not TryStrToDate(DateStr, DummyDT, FS)))  then      begin      TimeStr := DateStr;      DateStr := '';      end;    end;end; function StrToDateTime(const s: AnsiString; const FormatSettings : TFormatSettings): TDateTime;var  TimeStr, DateStr: AnsiString;  PartsFound: Integer;begin  PartsFound := SplitDateTimeStr(S, FormatSettings, DateStr, TimeStr);  case PartsFound of      0: Result:=StrToDate('');    1: if (Length(DateStr) > 0) then         Result := StrToDate(DateStr, FormatSettings.ShortDateFormat,FormatSettings.DateSeparator)       else         Result := StrToTime(TimeStr, FormatSettings);    2: Result := ComposeDateTime(StrTodate(DateStr,FormatSettings.ShortDateFormat,FormatSettings.DateSeparator),                                  StrToTime(TimeStr,FormatSettings));  end;end;function StrToDateTime(const s: AnsiString): TDateTime;begin  Result:=StrToDateTime(S,DefaultFormatSettings);end;function StrToDateTime(const s: ShortString; const FormatSettings : TFormatSettings): TDateTime;var  A : AnsiString;begin  A:=S;  Result:=StrToDateTime(A,FormatSettings);end;{   FormatDateTime formats DateTime to the given format string FormatStr   }function FormatDateTime(const FormatStr: string; DateTime: TDateTime; Options : TFormatDateTimeOptions = []): string;begin  DateTimeToString(Result, FormatStr, DateTime, DefaultFormatSettings,Options);end;function FormatDateTime(const FormatStr: string; DateTime: TDateTime; const FormatSettings: TFormatSettings; Options : TFormatDateTimeOptions = []): string;begin  DateTimeToString(Result, FormatStr, DateTime, FormatSettings,Options);end;{   DateTimeToString formats DateTime to the given format in FormatStr   }procedure DateTimeToString(out Result: string; const FormatStr: string;   const DateTime: TDateTime; Options : TFormatDateTimeOptions = []);begin  DateTimeToString(Result, FormatStr, DateTime, DefaultFormatSettings, Options);end;procedure DateTimeToString(out Result: string; const FormatStr: string; const DateTime: TDateTime;   const FormatSettings: TFormatSettings; Options : TFormatDateTimeOptions = []);var  ResultLen: integer;  ResultBuffer: array[0..255] of AnsiChar;  ResultCurrent: PAnsiChar;{$if defined(win32) or defined(win64)}  isEnable_E_Format : Boolean;  isEnable_G_Format : Boolean;  eastasiainited : boolean;  procedure InitEastAsia;  var     ALCID : LCID;         PriLangID , SubLangID : Word;  begin    ALCID := GetThreadLocale;    PriLangID := ALCID and $3FF;    if (PriLangID>0) then       SubLangID := (ALCID and $FFFF) shr 10      else        begin          PriLangID := SysLocale.PriLangID;          SubLangID := SysLocale.SubLangID;        end;    isEnable_E_Format := (PriLangID = LANG_JAPANESE)                  or                  (PriLangID = LANG_KOREAN)                  or                  ((PriLangID = LANG_CHINESE)                   and                   (SubLangID = SUBLANG_CHINESE_TRADITIONAL)                  );    isEnable_G_Format := (PriLangID = LANG_JAPANESE)                  or                  ((PriLangID = LANG_CHINESE)                   and                   (SubLangID = SUBLANG_CHINESE_TRADITIONAL)                  );    eastasiainited :=true;  end;{$endif win32 or win64}  procedure StoreStr(Str: PAnsiChar; Len: Integer);  begin    if ResultLen + Len < SizeOf(ResultBuffer) then    begin      StrMove(ResultCurrent, Str, Len);      ResultCurrent := ResultCurrent + Len;      ResultLen := ResultLen + Len;    end;  end;  procedure StoreString(const Str: string);  var Len: integer;  begin   Len := Length(Str);   if ResultLen + Len < SizeOf(ResultBuffer) then     begin       StrMove(ResultCurrent, PAnsiChar(Str), Len);       ResultCurrent := ResultCurrent + Len;       ResultLen := ResultLen + Len;     end;  end;  procedure StoreInt(Value, Digits: Integer);  var    S: string[16];    Len: integer;  begin    System.Str(Value:Digits, S);    for Len := 1 to Length(S) do    begin      if S[Len] = ' ' then        S[Len] := '0'      else        Break;    end;    StoreStr(PAnsiChar(@S[1]), Length(S));  end ;var  Year, Month, Day, DayOfWeek, Hour, Minute, Second, MilliSecond: word;  function FullDays(ADateTime: TDateTime): Integer;  begin    if ADateTime < 0 then ADateTime := -ADateTime;    Result := trunc(ADateTime);    if (frac(ADateTime) > 0.9) and (Hour = 0) and (Minute = 0) and (Second = 0) and (Millisecond = 0) then      inc(Result);  end;  procedure StoreFormat(const FormatStr: string; Nesting: Integer; TimeFlag: Boolean);  var    Token, lastformattoken, prevlasttoken: AnsiChar;    FormatCurrent: PAnsiChar;    FormatEnd: PAnsiChar;    Count: integer;    Clock12: boolean;    P: PAnsiChar;    tmp: integer;    isInterval: Boolean;  begin    if Nesting > 1 then  // 0 is original string, 1 is included FormatString      Exit;    FormatCurrent := PAnsiChar(FormatStr);    FormatEnd := FormatCurrent + Length(FormatStr);    Clock12 := false;    isInterval := false;    P := FormatCurrent;    // look for unquoted 12-hour clock token    while P < FormatEnd do    begin      Token := P^;      case Token of        '''', '"':        begin          Inc(P);          while (P < FormatEnd) and (P^ <> Token) do            Inc(P);        end;        'A', 'a':        begin          if (StrLIComp(P, 'A/P', 3) = 0) or             (StrLIComp(P, 'AMPM', 4) = 0) or             (StrLIComp(P, 'AM/PM', 5) = 0) then          begin            Clock12 := true;            break;          end;        end;      end;  // case      Inc(P);    end ;    token := #255;    lastformattoken := ' ';    prevlasttoken := 'H';    while FormatCurrent < FormatEnd do    begin      Token := UpCase(FormatCurrent^);      Count := 1;      P := FormatCurrent + 1;      case Token of        '''', '"':        begin          while (P < FormatEnd) and (p^ <> Token) do            Inc(P);          Inc(P);          Count := P - FormatCurrent;          StoreStr(FormatCurrent + 1, Count - 2);        end ;        'A':        begin          if StrLIComp(FormatCurrent, 'AMPM', 4) = 0 then          begin            Count := 4;            if Hour < 12 then              StoreString(FormatSettings.TimeAMString)            else              StoreString(FormatSettings.TimePMString);          end          else if StrLIComp(FormatCurrent, 'AM/PM', 5) = 0 then          begin            Count := 5;            if Hour < 12 then StoreStr(FormatCurrent, 2)                         else StoreStr(FormatCurrent+3, 2);          end          else if StrLIComp(FormatCurrent, 'A/P', 3) = 0 then          begin            Count := 3;            if Hour < 12 then StoreStr(FormatCurrent, 1)                         else StoreStr(FormatCurrent+2, 1);          end          else            raise EConvertError.Create('Illegal character in format string');        end ;        '/': if FormatSettings.DateSeparator<>#0 then StoreStr(@FormatSettings.DateSeparator, 1);        ':': if FormatSettings.TimeSeparator<>#0 then StoreStr(@FormatSettings.TimeSeparator, 1);        '[': if (fdoInterval in Options) then isInterval := true else StoreStr(FormatCurrent, 1);        ']': if (fdoInterval in Options) then isInterval := false else StoreStr(FormatCurrent, 1);        ' ', 'C', 'D', 'H', 'M', 'N', 'S', 'T', 'Y', 'Z', 'F' {$IFDEF MSWindows}, 'G', 'E'{$ENDIF MSWindows} :        begin          while (P < FormatEnd) and (UpCase(P^) = Token) do            Inc(P);          Count := P - FormatCurrent;          case Token of            ' ': StoreStr(FormatCurrent, Count);            'Y': begin              if Count > 2 then                StoreInt(Year, 4)              else                StoreInt(Year mod 100, 2);            end;            'M': begin              if isInterval and ((prevlasttoken = 'H') or TimeFlag) then                StoreInt(Minute + (Hour + FullDays(DateTime)*24)*60, 0)              else              if (lastformattoken = 'H') or TimeFlag then              begin                if Count = 1 then                  StoreInt(Minute, 0)                else                  StoreInt(Minute, 2);              end              else              begin                case Count of                  1: StoreInt(Month, 0);                  2: StoreInt(Month, 2);                  3: StoreString(FormatSettings.ShortMonthNames[Month]);                else                  StoreString(FormatSettings.LongMonthNames[Month]);                end;              end;            end;            'D': begin              case Count of                1: StoreInt(Day, 0);                2: StoreInt(Day, 2);                3: StoreString(FormatSettings.ShortDayNames[DayOfWeek]);                4: StoreString(FormatSettings.LongDayNames[DayOfWeek]);                5: StoreFormat(FormatSettings.ShortDateFormat, Nesting+1, False);              else                StoreFormat(FormatSettings.LongDateFormat, Nesting+1, False);              end ;            end ;            'H':              if isInterval then                StoreInt(Hour + FullDays(DateTime)*24, Count)              else              if Clock12 then              begin                tmp := hour mod 12;                if tmp=0 then tmp:=12;                if Count = 1 then                  StoreInt(tmp, 0)                else                  StoreInt(tmp, 2);              end              else begin                if Count = 1 then                  StoreInt(Hour, 0)                else                  StoreInt(Hour, 2);              end;            'N': if isInterval then                   StoreInt(Minute + (Hour + FullDays(DateTime)*24)*60, Count)                 else                 if Count = 1 then                   StoreInt(Minute, 0)                 else                   StoreInt(Minute, 2);            'S': if isInterval then                   StoreInt(Second + (Minute + (Hour + FullDays(DateTime)*24)*60)*60, Count)                 else                 if Count = 1 then                   StoreInt(Second, 0)                 else                   StoreInt(Second, 2);            'Z': if Count = 1 then                   StoreInt(MilliSecond, 0)                 else                   StoreInt(MilliSecond, 3);            'T': if Count = 1 then                   StoreFormat(FormatSettings.ShortTimeFormat, Nesting+1, True)                 else                   StoreFormat(FormatSettings.LongTimeFormat, Nesting+1, True);            'C': begin                   StoreFormat(FormatSettings.ShortDateFormat, Nesting+1, False);                   if (Hour<>0) or (Minute<>0) or (Second<>0) then                     begin                      StoreString(' ');                      StoreFormat(FormatSettings.LongTimeFormat, Nesting+1, True);                     end;                 end;            'F': begin                   StoreFormat(FormatSettings.ShortDateFormat, Nesting+1, False);                   StoreString(' ');                   StoreFormat(FormatSettings.LongTimeFormat, Nesting+1, True);                 end;{$if defined(win32) or defined(win64)}            'E':               begin                 if not Eastasiainited then InitEastAsia;                 if Not(isEnable_E_Format) then StoreStr(FormatCurrent, 1)                  else                   begin                     while (P < FormatEnd) and (UpCase(P^) = Token) do                     P := P + 1;                     Count := P - FormatCurrent;                     StoreString(ConvertEraYearString(Count,Year,Month,Day));                   end;                 prevlasttoken := lastformattoken;                   lastformattoken:=token;               end;             'G':               begin                 if not Eastasiainited then InitEastAsia;                 if Not(isEnable_G_Format) then StoreStr(FormatCurrent, 1)                  else                   begin                     while (P < FormatEnd) and (UpCase(P^) = Token) do                     P := P + 1;                     Count := P - FormatCurrent;                     StoreString(ConvertEraString(Count,Year,Month,Day));                   end;                 prevlasttoken := lastformattoken;                 lastformattoken:=token;               end;{$endif win32 or win64}          end;          prevlasttoken := lastformattoken;          lastformattoken := token;        end;        else          StoreStr(@Token, 1);      end ;      Inc(FormatCurrent, Count);    end;  end;begin{$if defined(win32) or defined(win64)}  eastasiainited:=false;{$endif win32 or win64}  DecodeDateFully(DateTime, Year, Month, Day, DayOfWeek);  DecodeTime(DateTime, Hour, Minute, Second, MilliSecond);  ResultLen := 0;  ResultCurrent := @ResultBuffer[0];  if FormatStr <> '' then    StoreFormat(FormatStr, 0, False)  else    StoreFormat('C', 0, False);  ResultBuffer[ResultLen] := #0;  result := StrPas(@ResultBuffer[0]);  if (DateTime < 0) and (fdoInterval in Options) then    result := '-' + result;end ;Function DateTimeToFileDate(DateTime : TDateTime) : Int64;Var YY,MM,DD,H,m,s,msec : Word;begin  Decodedate (DateTime,YY,MM,DD);  DecodeTime (DateTime,h,m,s,msec);{$if not defined(unix) and not defined(wasi)}  If (YY<1980) or (YY>2099) then    Result:=0  else    begin    Result:=(s shr 1) or (m shl 5) or (h shl 11);    Result:=Result or longint(DD shl 16 or (MM shl 21) or (word(YY-1980) shl 25));    end;{$else unix or wasi}  Result:=LocalToEpoch(yy,mm,dd,h,m,s);{$endif unix or wasi}end;Function UniversalToFileDate(DateTime : TDateTime) : int64;{$if not defined(unix) and not defined(wasi)}begin  Result := DateTimeToFileDate(UniversalTimeToLocal(DateTime));end;{$else unix or wasi}Var YY,MM,DD,H,m,s,msec : Word;begin  Decodedate (DateTime,YY,MM,DD);  DecodeTime (DateTime,h,m,s,msec);  Result:=UniversalToEpoch(yy,mm,dd,h,m,s);end;{$endif unix or wasi}function CurrentYear: Word;var  SysTime: TSystemTime;begin  GetLocalTime(SysTime);  Result := SysTime.Year;end;Function FileDateToDateTime (Filedate : Int64) : TDateTime;{$if not defined(unix) and not defined(wasi)}Var Date,Time : Word;begin  Date:=FileDate shr 16;  Time:=FileDate and $ffff;  Result:=ComposeDateTime(EncodeDate((Date shr 9) + 1980,(Date shr 5) and 15, Date and 31),          EncodeTime(Time shr 11, (Time shr 5) and 63, (Time and 31) shl 1,0));end;{$else unix or wasi}var  y, mon, d, h, min, s: word;begin  EpochToLocal(FileDate,y,mon,d,h,min,s);  Result:=ComposeDateTime(EncodeDate(y,mon,d),EncodeTime(h,min,s,0));end;{$endif unix or wasi}Function FileDateToUniversal (Filedate : Int64) : TDateTime;{$if not defined(unix) and not defined(wasi)}begin  Result := LocalTimeToUniversal(FileDateToDateTime(Filedate));end;{$else unix or wasi}var  y, mon, d, h, min, s: word;begin  EpochToUniversal(FileDate,y,mon,d,h,min,s);  Result:=ComposeDateTime(EncodeDate(y,mon,d),EncodeTime(h,min,s,0));end;{$endif unix or wasi}function TryStrToDate(const S: ShortString; out Value: TDateTime): Boolean;begin    result := TryStrToDate(S, Value, #0);end;function TryStrToDate(const S: ShortString; out Value: TDateTime;                    const useformat : string; separator : AnsiChar = #0): Boolean;Var  Msg : Ansistring;begin  // S[1] always exists for shortstring. Length 0 will trigger an error.  Value:=IntStrToDate(Msg,@S[1],Length(S),useformat,defaultformatsettings,separator);  Result:=(Msg='');end;function TryStrToDate(const S: AnsiString; out Value: TDateTime;                    const useformat : string; separator : AnsiChar = #0): Boolean;Var  Msg : Ansistring;begin  Result:=Length(S)<>0;  If Result then    begin    Value:=IntStrToDate(Msg,PAnsiChar(S),Length(S),useformat,DefaultFormatSettings,Separator);    Result:=(Msg='');    end;end;function TryStrToDate(const S: ShortString; out Value: TDateTime; separator : AnsiChar): Boolean;begin  Result:=TryStrToDate(S,Value,DefaultFormatSettings.ShortDateFormat,Separator);end;function TryStrToDate(const S: AnsiString; out Value: TDateTime): Boolean;begin  Result:=TryStrToDate(S,Value,DefaultFormatSettings.ShortDateFormat,#0);end;function TryStrToDate(const S: AnsiString; out Value: TDateTime; separator : AnsiChar): Boolean;begin  Result:=TryStrToDate(S,Value,DefaultFormatSettings.ShortDateFormat,Separator);end;function TryStrToDate(const S: string; out Value: TDateTime; const FormatSettings: TFormatSettings): Boolean;Var  Msg : Ansistring;begin  Result:=Length(S)<>0;  If Result then    begin      Value:=IntStrToDate(Msg,PAnsiChar(S),Length(S),FormatSettings.ShortDateFormat,FormatSettings,#0);      Result:=(Msg='');    end;end;function TryStrToTime(const S: ShortString; out Value: TDateTime; separator : AnsiChar): Boolean;Var  Msg : AnsiString;begin  // S[1] always exists for shortstring. Length 0 will trigger an error.  Value:=IntStrToTime(Msg,@S[1],Length(S),DefaultFormatSettings,Separator);  result:=(Msg='');end;function TryStrToTime(const S: ShortString; out Value: TDateTime): Boolean;begin  Result := TryStrToTime(S,Value,#0);end;function TryStrToTime(const S: AnsiString; out Value: TDateTime; separator : AnsiChar): Boolean;Var  Msg : AnsiString;begin  Result:=Length(S)<>0;  If Result then    begin      Value:=IntStrToTime(Msg,PAnsiChar(S),Length(S),DefaultFormatSettings,Separator);      Result:=(Msg='');    end;end;function TryStrToTime(const S: AnsiString; out Value: TDateTime): Boolean;begin    result := TryStrToTime(S,Value,#0);end;function TryStrToTime(const S: string; out Value: TDateTime; const FormatSettings: TFormatSettings): Boolean;Var msg : AnsiString;begin  Result:=Length(S)<>0;  If Result then    begin      Value:=IntStrToTime(Msg,PAnsiChar(S),Length(S),FormatSettings,#0);      Result:=(Msg='');    end;end;function TryStrToDateTime(const S: ShortString; out Value: TDateTime): Boolean;  begin    result := TryStrToDateTime(S, Value, DefaultFormatSettings);  end;function TryStrToDateTime(const S: AnsiString; out Value: TDateTime): Boolean;  begin    result := TryStrToDateTime(S, Value, DefaultFormatSettings);  end;function TryStrToDateTime(const S: string; out Value: TDateTime; const FormatSettings: TFormatSettings): Boolean;var  I: integer;  dtdate, dttime :TDateTime;begin  result:=false;  I:=Pos(FormatSettings.TimeSeparator,S);  If (I>0) then    begin      While (I>0) and (S[I]<>' ') do        Dec(I);      If I>0 then        begin          if not TryStrToDate(Copy(S,1,I-1),dtdate,Formatsettings) then            exit;          if not TryStrToTime(Copy(S,i+1, Length(S)-i),dttime,Formatsettings) then            exit;          Value:=ComposeDateTime(dtdate,dttime);          result:=true;        end      else         result:=TryStrToTime(s,Value,Formatsettings);    end  else    result:=TryStrToDate(s,Value,Formatsettings);end;function StrToDateDef(const S: ShortString; const Defvalue : TDateTime): TDateTime;begin   result := StrToDateDef(S,DefValue,#0);end;function StrToTimeDef(const S: ShortString; const Defvalue : TDateTime): TDateTime;begin   result := StrToTimeDef(S,DefValue,#0);end;function StrToDateTimeDef(const S: ShortString; const Defvalue : TDateTime): TDateTime;begin  Result:=StrToDateTimeDef(S,DefValue,DefaultFormatSettings);end;function StrToDateTimeDef(const S: AnsiString; const Defvalue : TDateTime; const FormatSettings: TFormatSettings): TDateTime;begin  if not TryStrToDateTime(s,Result,FormatSettings) Then    result:=defvalue;end;function StrToDateDef(const S: ShortString; const Defvalue : TDateTime; separator : AnsiChar): TDateTime;begin  if not TryStrToDate(s,Result, separator) Then    result:=defvalue;end;function StrToTimeDef(const S: ShortString; const Defvalue : TDateTime; separator : AnsiChar): TDateTime;begin  if not TryStrToTime(s,Result, separator) Then    result:=defvalue;end;function StrToDateDef(const S: AnsiString; const Defvalue : TDateTime): TDateTime;begin   result := StrToDateDef(S,DefValue,#0);end;function StrToTimeDef(const S: AnsiString; const Defvalue : TDateTime): TDateTime;begin   result := StrToTimeDef(S,DefValue,#0);end;function StrToDateTimeDef(const S: AnsiString; const Defvalue : TDateTime): TDateTime;begin  if not TryStrToDateTime(s,Result) Then    result:=defvalue;end;function StrToDateDef(const S: AnsiString; const Defvalue : TDateTime; separator : AnsiChar): TDateTime;begin  if not TryStrToDate(s,Result, separator) Then    result:=defvalue;end;function StrToTimeDef(const S: AnsiString; const Defvalue : TDateTime; separator : AnsiChar): TDateTime;begin  if not TryStrToTime(s,Result, separator) Then    result:=defvalue;end;procedure ReplaceTime(var dati:TDateTime; NewTime : TDateTime);inline;begin  dati:= ComposeDateTime(dati, newtime);end;procedure ReplaceDate(var DateTime: TDateTime; const NewDate: TDateTime); inline;var  tmp : TDateTime;begin  tmp:=NewDate;  ReplaceTime(tmp,DateTime);  DateTime:=tmp;end;{$IFNDEF HAS_LOCALTIMEZONEOFFSET}Function GetLocalTimeOffset : Integer;begin  Result:=0;end;function GetLocalTimeOffset(const DateTime: TDateTime; const InputIsUTC: Boolean; out Offset: Integer): Boolean;begin  Result:=False;end;function GetUniversalTime(var SystemTime: TSystemTime): Boolean;begin  Result:=False;end;{$ENDIF}function GetLocalTimeOffset(const DateTime: TDateTime; const InputIsUTC: Boolean): Integer;begin  if not GetLocalTimeOffset(DateTime, InputIsUTC, Result) then    Result:=GetLocalTimeOffset();end;{ Conversion of UTC to local time and vice versa }function UniversalTimeToLocal(UT: TDateTime): TDateTime;begin  Result:=UniversalTimeToLocal(UT,-GetLocalTimeOffset(UT, True));end;function UniversalTimeToLocal(UT: TDateTime; TZOffset : Integer): TDateTime;begin  if (TZOffset > 0) then    Result := UT + EncodeTime(TZOffset div 60, TZOffset mod 60, 0, 0)  else if (TZOffset < 0) then    Result := UT - EncodeTime(Abs(TZOffset) div 60, Abs(TZOffset) mod 60, 0, 0)  else    Result := UT;end;Function LocalTimeToUniversal(LT: TDateTime): TDateTime;begin  Result:=LocalTimeToUniversal(LT,-GetLocalTimeOffset(LT, False));end;Function LocalTimeToUniversal(LT: TDateTime;TZOffset: Integer): TDateTime;begin  if (TZOffset > 0) then    Result := LT - EncodeTime(TZOffset div 60, TZOffset mod 60, 0, 0)  else if (TZOffset < 0) then    Result := LT + EncodeTime(Abs(TZOffset) div 60, Abs(TZOffset) mod 60, 0, 0)  else    Result := LT;end;
 |