1 {*********************[ TIME UNIT ]************************}
2 {                                                          }
3 {             System independent TIME unit                 }
4 {                                                          }
5 {   Copyright (c) 1996, 1997, 1998, 1999 by Leon de Boer   }
6 {   ldeboer@attglobal.net  - primary e-mail address        }
7 {   ldeboer@starwon.com.au - backup e-mail address         }
8 {                                                          }
9 {****************[ THIS CODE IS FREEWARE ]*****************}
10 {                                                          }
11 {     This sourcecode is released for the purpose to       }
12 {   promote the pascal language on all platforms. You may  }
13 {   redistribute it and/or modify with the following       }
14 {   DISCLAIMER.                                            }
15 {                                                          }
16 {     This SOURCE CODE is distributed "AS IS" WITHOUT      }
17 {   WARRANTIES AS TO PERFORMANCE OF MERCHANTABILITY OR     }
18 {   ANY OTHER WARRANTIES WHETHER EXPRESSED OR IMPLIED.     }
19 {                                                          }
20 {*****************[ SUPPORTED PLATFORMS ]******************}
21 {     16 and 32 Bit compilers                              }
22 {        DOS      - Turbo Pascal 7.0 +      (16 Bit)       }
23 {        DPMI     - Turbo Pascal 7.0 +      (16 Bit)       }
24 {                 - FPC 0.9912+ (GO32V2)    (32 Bit)       }
25 {        WINDOWS  - Turbo Pascal 7.0 +      (16 Bit)       }
26 {                 - Delphi 1.0+             (16 Bit)       }
27 {        WIN95/NT - Delphi 2.0+             (32 Bit)       }
28 {                 - Virtual Pascal 2.0+     (32 Bit)       }
29 {                 - Speedsoft Sybil 2.0+    (32 Bit)       }
30 {                 - FPC 0.9912+             (32 Bit)       }
31 {        OS2      - Virtual Pascal 1.0+     (32 Bit)       }
32 {                 - Speed Pascal 1.0+       (32 Bit)       }
33 {                 - C'T patch to BP         (16 Bit)       }
34 {                                                          }
35 {******************[ REVISION HISTORY ]********************}
36 {  Version  Date        Fix                                }
37 {  -------  ---------   ---------------------------------  }
38 {  1.00     06 Dec 96   First multi platform release.      }
39 {  1.10     06 Jul 97   New functiions added.              }
40 {  1.20     22 Jul 97   FPC pascal compiler added.         }
41 {  1.30     29 Aug 97   Platform.inc sort added.           }
42 {  1.40     13 Oct 97   Delphi 2/3 32 bit code added.      }
43 {  1.50     06 Nov 97   Speed pascal code added.           }
44 {  1.60     05 May 98   Virtual pascal 2.0 compiler added. }
45 {  1.61     07 Jul 99   Speedsoft SYBIL 2.0 code added.    }
46 {**********************************************************}
47 
48 UNIT Time;
49 
50 {<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>}
51                                   INTERFACE
52 {<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>}
53 
54 {====Include file to sort compiler platform out =====================}
55 {$I platform.inc}
56 {====================================================================}
57 
58 {==== Compiler directives ===========================================}
59 
60 {$IFNDEF PPC_FPC} { FPC doesn't support these switches }
61    {$F-} { Short calls are okay }
62    {$A+} { Word Align Data }
63    {$B-} { Allow short circuit boolean evaluations }
64    {$O+} { This unit may be overlaid }
65    {$G+} { 286 Code optimization - if you're on an 8088 get a real computer }
66    {$E+} {  Emulation is on }
67    {$N-} {  No 80x87 code generation }
68 {$ENDIF}
69 
70 {$X+} { Extended syntax is ok }
71 {$R-} { Disable range checking }
72 {$S-} { Disable Stack Checking }
73 {$I-} { Disable IO Checking }
74 {$Q-} { Disable Overflow Checking }
75 {$V-} { Turn off strict VAR strings }
76 {====================================================================}
77 
78 {***************************************************************************}
79 {                            INTERFACE ROUTINES                             }
80 {***************************************************************************}
81 
82 {-CurrentMinuteOfDay-------------------------------------------------
83 Returns the number of minutes since midnight of a current system time.
84 19Jun97 LdB               (Range: 0 - 1439)
85 ---------------------------------------------------------------------}
CurrentMinuteOfDaynull86 FUNCTION CurrentMinuteOfDay: Word;
87 
88 {-CurrentSecondOfDay-------------------------------------------------
89 Returns the number of seconds since midnight of current system time.
90 24Jun97 LdB               (Range: 0 - 86399)
91 ---------------------------------------------------------------------}
CurrentSecondOfDaynull92 FUNCTION CurrentSecondOfDay: LongInt;
93 
94 {-CurrentSec100OfDay-------------------------------------------------
95 Returns the 1/100ths of a second since midnight of current system time.
96 24Jun97 LdB               (Range: 0 - 8639999)
97 ---------------------------------------------------------------------}
CurrentSec100OfDaynull98 FUNCTION CurrentSec100OfDay: LongInt;
99 
100 {-MinuteOfDay--------------------------------------------------------
101 Returns the number of minutes since midnight of a valid given time.
102 19Jun97 LdB               (Range: 0 - 1439)
103 ---------------------------------------------------------------------}
MinuteOfDaynull104 FUNCTION MinuteOfDay (Hour24, Minute: Word): Word;
105 
106 {-SecondOfDay--------------------------------------------------------
107 Returns the number of seconds since midnight of a valid given time.
108 19Jun97 LdB               (Range: 0 - 86399)
109 ---------------------------------------------------------------------}
SecondOfDaynull110 FUNCTION SecondOfDay (Hour24, Minute, Second: Word): LongInt;
111 
112 {-SetTime------------------------------------------------------------
113 Set the operating systems time clock to the given values. If values
114 are invalid this function will fail without notification.
115 06Nov97 LdB
116 ---------------------------------------------------------------------}
117 PROCEDURE SetTime (Hour, Minute, Second, Sec100: Word);
118 
119 {-GetTime------------------------------------------------------------
120 Returns the current time settings of the operating system.
121 06Nov97 LdB
122 ---------------------------------------------------------------------}
123 PROCEDURE GetTime (Var Hour, Minute, Second, Sec100: Word);
124 
125 {-MinutesToTime------------------------------------------------------
126 Returns the time in hours and minutes of a given number of minutes.
127 19Jun97 LdB
128 ---------------------------------------------------------------------}
129 PROCEDURE MinutesToTime (Md: LongInt; Var Hour24, Minute: Word);
130 
131 {-SecondsToTime------------------------------------------------------
132 Returns the time in hours, mins and secs of a given number of seconds.
133 19Jun97 LdB
134 ---------------------------------------------------------------------}
135 PROCEDURE SecondsToTime (Sd: LongInt; Var Hour24, Minute, Second: Word);
136 
137 {<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>}
138                                 IMPLEMENTATION
139 {<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>}
140 {$IFDEF OS_WINDOWS}                                   { WIN/NT CODE }
141 
142   {$IFNDEF PPC_SPEED}                                 { NON SPEED COMPILER }
143     {$IFDEF PPC_FPC}                                  { FPC WINDOWS COMPILER }
144     USEs Windows;                                     { Standard unit }
145     {$ELSE}                                           { OTHER COMPILERS }
146     USES WinTypes, WinProcs;                          { Standard units }
147     {$ENDIF}
148   {$ELSE}                                             { SPEEDSOFT COMPILER }
149   USES WinBase;                                       { Standard unit }
150   TYPE TSystemTime = SystemTime;                      { Type fix up }
151   {$ENDIF}
152 
153 {$ENDIF}
154 
155 {$IFDEF OS_OS2}                                       { OS2 COMPILERS }
156 
157   {$IFDEF PPC_VIRTUAL}                                { VIRTUAL PASCAL }
158   USES OS2Base;                                       { Standard unit }
159   {$ENDIF}
160 
161   {$IFDEF PPC_SPEED}                                  { SPEED PASCAL }
162   USES BseDos, Os2Def;                                { Standard unit }
163   {$ENDIF}
164 
165   {$IFDEF PPC_FPC}                                    { FPC }
166   USES Dos, DosCalls;                                 { Standard unit }
167 
168   TYPE DateTime = TDateTime;                          { Type correction }
169   {$ENDIF}
170 
171   {$IFDEF PPC_BPOS2}                                  { C'T PATCH TO BP CODE }
172   USES DosTypes, DosProcs;                            { Standard unit }
173 
174   TYPE DateTime = TDateTime;                          { Type correction }
175   {$ENDIF}
176 
177 {$ENDIF}
178 
179 {$ifdef OS_UNIX}
180   USES Dos;
181 {$endif OS_UNIX}
182 
183 {$ifdef OS_GO32}
184   USES Dos;
185 {$endif OS_GO32}
186 
187 {$ifdef OS_NETWARE}
188   USES Dos;
189 {$endif OS_NETWARE}
190 
191 {$ifdef OS_AMIGA}
192   USES Dos;
193 {$endif OS_AMIGA}
194 
195 {***************************************************************************}
196 {                            INTERFACE ROUTINES                             }
197 {***************************************************************************}
198 
199 {---------------------------------------------------------------------------}
200 {  CurrentMinuteOfDay -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 24Jun97 LdB}
201 {---------------------------------------------------------------------------}
CurrentMinuteOfDaynull202 FUNCTION CurrentMinuteOfDay: Word;
203 VAR Hour, Minute, Second, Sec100: Word;
204 BEGIN
205    GetTime(Hour, Minute, Second, Sec100);             { Get current time }
206    CurrentMinuteOfDay := (Hour * 60) + Minute;        { Minute from midnight }
207 END;
208 
209 {---------------------------------------------------------------------------}
210 {  CurrentSecondOfDay -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 24Jun97 LdB}
211 {---------------------------------------------------------------------------}
CurrentSecondOfDaynull212 FUNCTION CurrentSecondOfDay: LongInt;
213 VAR Hour, Minute, Second, Sec100: Word;
214 BEGIN
215    GetTime(Hour, Minute, Second, Sec100);             { Get current time }
216    CurrentSecondOfDay := (LongInt(Hour) * 3600) +
217      (Minute * 60) + Second;                          { Second from midnight }
218 END;
219 
220 {---------------------------------------------------------------------------}
221 {  CurrentSec100OfDay -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 24Jun97 LdB}
222 {---------------------------------------------------------------------------}
CurrentSec100OfDaynull223 FUNCTION CurrentSec100OfDay: LongInt;
224 VAR Hour, Minute, Second, Sec100: Word;
225 BEGIN
226    GetTime(Hour, Minute, Second, Sec100);             { Get current time }
227    CurrentSec100OfDay := (LongInt(Hour) * 360000) +
228      (LongInt(Minute) * 6000) + (Second*100)+ Sec100; { Sec100 from midnight }
229 END;
230 
231 {---------------------------------------------------------------------------}
232 {  MinuteOfDay -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 19Jun97 LdB       }
233 {---------------------------------------------------------------------------}
MinuteOfDaynull234 FUNCTION MinuteOfDay (Hour24, Minute: Word): Word;
235 BEGIN
236    MinuteOfDay := (Hour24 * 60) + Minute;             { Minute from midnight }
237 END;
238 
239 {---------------------------------------------------------------------------}
240 {  SecondOfDay -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 19Jun97 LdB       }
241 {---------------------------------------------------------------------------}
SecondOfDaynull242 FUNCTION SecondOfDay (Hour24, Minute, Second: Word): LongInt;
243 BEGIN
244    SecondOfDay := (LongInt(Hour24) * 3600) +
245      (Minute * 60) + Second;                          { Second from midnight }
246 END;
247 
248 {---------------------------------------------------------------------------}
249 {  SetTime -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 06Nov97 LdB           }
250 {---------------------------------------------------------------------------}
251 PROCEDURE SetTime (Hour, Minute, Second, Sec100: Word);
252 {$IFDEF OS_DOS}                                       { DOS/DPMI CODE }
253    {$IFDEF ASM_BP}                                    { BP COMPATABLE ASM }
254    ASSEMBLER;
255    ASM
256      MOV CH, BYTE PTR Hour;                           { Fetch hour }
257      MOV CL, BYTE PTR Minute;                         { Fetch minute }
258      MOV DH, BYTE PTR Second;                         { Fetch second }
259      MOV DL, BYTE PTR Sec100;                         { Fetch hundredths }
260      MOV AX, $2D00;                                   { Set function id }
261      PUSH BP;                                         { Safety save register }
262      INT $21;                                         { Set the time }
263      POP BP;                                          { Restore register }
264    END;
265    {$ENDIF}
266    {$IFDEF ASM_FPC}                                   { FPC COMPATABLE ASM }
267      {$IFDEF BIT_16}
268      ASSEMBLER;
269      ASM
270        MOV CH, BYTE PTR Hour;                           { Fetch hour }
271        MOV CL, BYTE PTR Minute;                         { Fetch minute }
272        MOV DH, BYTE PTR Second;                         { Fetch second }
273        MOV DL, BYTE PTR Sec100;                         { Fetch hundredths }
274        MOV AX, $2D00;                                   { Set function id }
275        PUSH BP;                                         { Safety save register }
276        INT $21;                                         { Set the time }
277        POP BP;                                          { Restore register }
278      END;
279      {$ELSE}
280      BEGIN
281      ASM
282        MOVB Hour, %CH;                                  { Fetch hour }
283        MOVB Minute, %CL;                                { Fetch minute }
284        MOVB Second, %DH;                                { Fetch second }
285        MOVB Sec100, %DL;                                { Fetch hundredths }
286        MOVW $0x2D00, %AX;                               { Set function id }
287        PUSHL %EBP;                                      { Save register }
288        INT $0x21;                                       { BIOS set time }
289        POPL %EBP;                                       { Restore register }
290      END;
291      END;
292      {$ENDIF}
293    {$ENDIF}
294 {$ENDIF}
295 {$IFDEF OS_WIN16}                                     { 16 BIT WINDOWS CODE }
296    ASSEMBLER;
297    ASM
298      MOV CH, BYTE PTR Hour;                           { Fetch hour }
299      MOV CL, BYTE PTR Minute;                         { Fetch minute }
300      MOV DH, BYTE PTR Second;                         { Fetch second }
301      MOV DL, BYTE PTR Sec100;                         { Fetch hundredths }
302      MOV AX, $2D00;                                   { Set function id }
303      PUSH BP;                                         { Safety save register }
304      INT $21;                                         { Set the time }
305      POP BP;                                          { Restore register }
306    END;
307 {$ENDIF}
308 {$IFDEF OS_WINDOWS}                                   { WIN/NT CODE }
309    {$IFDEF BIT_16}                                    { 16 BIT WINDOWS CODE }
310    ASSEMBLER;
311    ASM
312      MOV CH, BYTE PTR Hour;                           { Fetch hour }
313      MOV CL, BYTE PTR Minute;                         { Fetch minute }
314      MOV DH, BYTE PTR Second;                         { Fetch second }
315      MOV DL, BYTE PTR Sec100;                         { Fetch hundredths }
316      MOV AX, $2D00;                                   { Set function id }
317      PUSH BP;                                         { Safety save register }
318      INT $21;                                         { Set the time }
319      POP BP;                                          { Restore register }
320    END;
321    {$ENDIF}
322    {$IFDEF BIT_32_OR_MORE}                            { 32 BIT WINDOWS CODE }
323    VAR DT: TSystemTime;
324    BEGIN
325      {$IFDEF PPC_FPC}                                 { FPC WINDOWS COMPILER }
326      GetLocalTime(@DT);                               { Get the date/time }
327      {$ELSE}                                          { OTHER COMPILERS }
328      GetLocalTime(DT);                                { Get the date/time }
329      {$ENDIF}
330      DT.wHour := Hour;                                { Transfer hour }
331      DT.wMinute := Minute;                            { Transfer minute }
332      DT.wSecond := Second;                            { Transfer seconds }
333      DT.wMilliseconds := Sec100 * 10;                 { Transfer millisecs }
334      SetLocalTime(DT);                               { Set the date/time }
335    END;
336    {$ENDIF}
337 {$ENDIF}
338 {$IFDEF OS_OS2}                                       { OS2 CODE }
339 VAR DT: DateTime;
340 BEGIN
341    DosGetDateTime(DT);                                { Get the date/time }
342    DT.Hours := Hour;                                  { Transfer hour }
343    DT.Minutes := Minute;                              { Transfer minute }
344    DT.Seconds := Second;                              { Transfer seconds }
345    DT.Hundredths := Sec100;                           { Transfer hundredths }
346    DosSetDateTime(DT);                                { Set the time }
347 END;
348 {$ENDIF}
349 {$ifdef OS_UNIX}
350 BEGIN
351  {settime is dummy in Linux}
352 END;
353 {$endif OS_UNIX}
354 {$IFDEF OS_NETWARE}
355 BEGIN
356  {settime is dummy in Netware (Libc and Clib) }
357 END;
358 {$ENDIF OS_NETWARE}
359 {$IFDEF OS_AMIGA}
360 BEGIN
361  { settime is dummy on Amiga }
362  { probably could be implemented, but it's low pri... (KB) }
363 END;
364 {$ENDIF OS_AMIGA}
365 
366 {---------------------------------------------------------------------------}
367 {  GetTime -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 06Nov97 LdB           }
368 {---------------------------------------------------------------------------}
369 PROCEDURE GetTime (Var Hour, Minute, Second, Sec100: Word);
370 {$IFDEF OS_DOS}                                       { DOS/DPMI CODE }
371    {$IFDEF ASM_BP}                                    { BP COMPATABLE ASM }
372    ASSEMBLER;
373    ASM
374      MOV AX, $2C00;                                   { Set function id }
375      PUSH BP;                                         { Safety save register }
376      INT $21;                                         { System get time }
377      POP BP;                                          { Restore register }
378      XOR AH, AH;                                      { Clear register }
379      CLD;                                             { Strings go forward }
380      MOV AL, DL;                                      { Transfer register }
381      LES DI, Sec100;                                  { ES:DI -> hundredths }
382      STOSW;                                           { Return hundredths }
383      MOV AL, DH;                                      { Transfer register }
384      LES DI, Second;                                  { ES:DI -> seconds }
385      STOSW;                                           { Return seconds }
386      MOV AL, CL;                                      { Transfer register }
387      LES DI, Minute;                                  { ES:DI -> minutes }
388      STOSW;                                           { Return minutes }
389      MOV AL, CH;                                      { Transfer register }
390      LES DI, Hour;                                    { ES:DI -> hours }
391      STOSW;                                           { Return hours }
392    END;
393    {$ENDIF}
394    {$IFDEF ASM_FPC}                                   { FPC COMPATABLE ASM }
395      {$IFDEF BIT_16}
396        {$IFDEF FPC_X86_DATA_NEAR}
397        ASSEMBLER;
398        ASM
399          MOV AX, $2C00;                                   { Set function id }
400          PUSH BP;                                         { Safety save register }
401          INT $21;                                         { System get time }
402          POP BP;                                          { Restore register }
403          XOR AH, AH;                                      { Clear register }
404          CLD;                                             { Strings go forward }
405          MOV AL, DL;                                      { Transfer register }
406          PUSH DS
407          POP ES
408          MOV DI, Sec100;                                  { ES:DI -> hundredths }
409          STOSW;                                           { Return hundredths }
410          MOV AL, DH;                                      { Transfer register }
411          MOV DI, Second;                                  { ES:DI -> seconds }
412          STOSW;                                           { Return seconds }
413          MOV AL, CL;                                      { Transfer register }
414          MOV DI, Minute;                                  { ES:DI -> minutes }
415          STOSW;                                           { Return minutes }
416          MOV AL, CH;                                      { Transfer register }
417          MOV DI, Hour;                                    { ES:DI -> hours }
418          STOSW;                                           { Return hours }
419        END;
420        {$ELSE FPC_X86_DATA_NEAR}
421        ASSEMBLER;
422        ASM
423          MOV AX, $2C00;                                   { Set function id }
424          PUSH BP;                                         { Safety save register }
425          INT $21;                                         { System get time }
426          POP BP;                                          { Restore register }
427          XOR AH, AH;                                      { Clear register }
428          CLD;                                             { Strings go forward }
429          MOV AL, DL;                                      { Transfer register }
430          LES DI, Sec100;                                  { ES:DI -> hundredths }
431          STOSW;                                           { Return hundredths }
432          MOV AL, DH;                                      { Transfer register }
433          LES DI, Second;                                  { ES:DI -> seconds }
434          STOSW;                                           { Return seconds }
435          MOV AL, CL;                                      { Transfer register }
436          LES DI, Minute;                                  { ES:DI -> minutes }
437          STOSW;                                           { Return minutes }
438          MOV AL, CH;                                      { Transfer register }
439          LES DI, Hour;                                    { ES:DI -> hours }
440          STOSW;                                           { Return hours }
441        END;
442        {$ENDIF}
443      {$ELSE}
444      BEGIN
445      (* ASM
446        MOVW $0x2C00, %AX;                               { Set function id }
447        PUSHL %EBP;                                      { Save register }
448        INT $0x21;                                       { System get time }
449        POPL %EBP;                                       { Restore register }
450        XORB %AH, %AH;                                   { Clear register }
451        MOVB %DL, %AL;                                   { Transfer register }
452        MOVL Sec100, %EDI;                               { EDI -> Sec100 }
453        MOVW %AX, (%EDI);                                { Return Sec100 }
454        MOVB %DH, %AL;                                   { Transfer register }
455        MOVL Second, %EDI;                               { EDI -> Second }
456        MOVW %AX, (%EDI);                                { Return Second }
457        MOVB %CL, %AL;                                   { Transfer register }
458        MOVL Minute, %EDI;                               { EDI -> Minute }
459        MOVW %AX, (%EDI);                                { Return minute }
460        MOVB %CH, %AL;                                   { Transfer register }
461        MOVL Hour, %EDI;                                 { EDI -> Hour }
462        MOVW %AX, (%EDI);                                { Return hour }
463      END; *)
464      { direct call of real interrupt seems to render the system
465        unstable on Win2000 because some registers are not properly
466        restored if a mouse interrupt is generated while the Dos
467        interrupt is called... PM }
468        Dos.GetTime(Hour,Minute,Second,Sec100);
469      END;
470      {$ENDIF}
471    {$ENDIF}
472 {$ENDIF}
473 {$IFDEF OS_WIN16}                                     { 16 BIT WINDOWS CODE }
474    {$IFDEF FPC_X86_DATA_NEAR}
475    ASSEMBLER;
476    ASM
477      MOV AX, $2C00;                                   { Set function id }
478      PUSH BP;                                         { Safety save register }
479      INT $21;                                         { System get time }
480      POP BP;                                          { Restore register }
481      XOR AH, AH;                                      { Clear register }
482      CLD;                                             { Strings go forward }
483      MOV AL, DL;                                      { Transfer register }
484      PUSH DS
485      POP ES
486      MOV DI, Sec100;                                  { ES:DI -> hundredths }
487      STOSW;                                           { Return hundredths }
488      MOV AL, DH;                                      { Transfer register }
489      MOV DI, Second;                                  { ES:DI -> seconds }
490      STOSW;                                           { Return seconds }
491      MOV AL, CL;                                      { Transfer register }
492      MOV DI, Minute;                                  { ES:DI -> minutes }
493      STOSW;                                           { Return minutes }
494      MOV AL, CH;                                      { Transfer register }
495      MOV DI, Hour;                                    { ES:DI -> hours }
496      STOSW;                                           { Return hours }
497    END;
498    {$ELSE FPC_X86_DATA_NEAR}
499    ASSEMBLER;
500    ASM
501      MOV AX, $2C00;                                   { Set function id }
502      PUSH BP;                                         { Safety save register }
503      INT $21;                                         { System get time }
504      POP BP;                                          { Restore register }
505      XOR AH, AH;                                      { Clear register }
506      CLD;                                             { Strings go forward }
507      MOV AL, DL;                                      { Transfer register }
508      LES DI, Sec100;                                  { ES:DI -> hundredths }
509      STOSW;                                           { Return hundredths }
510      MOV AL, DH;                                      { Transfer register }
511      LES DI, Second;                                  { ES:DI -> seconds }
512      STOSW;                                           { Return seconds }
513      MOV AL, CL;                                      { Transfer register }
514      LES DI, Minute;                                  { ES:DI -> minutes }
515      STOSW;                                           { Return minutes }
516      MOV AL, CH;                                      { Transfer register }
517      LES DI, Hour;                                    { ES:DI -> hours }
518      STOSW;                                           { Return hours }
519    END;
520    {$ENDIF}
521 {$ENDIF}
522 {$IFDEF OS_WINDOWS}                                   { WIN/NT CODE }
523    {$IFDEF BIT_16}                                    { 16 BIT WINDOWS CODE }
524    ASSEMBLER;
525    ASM
526      MOV AX, $2C00;                                   { Set function id }
527      PUSH BP;                                         { Safety save register }
528      INT $21;                                         { System get time }
529      POP BP;                                          { Restore register }
530      XOR AH, AH;                                      { Clear register }
531      CLD;                                             { Strings go forward }
532      MOV AL, DL;                                      { Transfer register }
533      LES DI, Sec100;                                  { ES:DI -> hundredths }
534      STOSW;                                           { Return hundredths }
535      MOV AL, DH;                                      { Transfer register }
536      LES DI, Second;                                  { ES:DI -> seconds }
537      STOSW;                                           { Return seconds }
538      MOV AL, CL;                                      { Transfer register }
539      LES DI, Minute;                                  { ES:DI -> minutes }
540      STOSW;                                           { Return minutes }
541      MOV AL, CH;                                      { Transfer register }
542      LES DI, Hour;                                    { ES:DI -> hours }
543      STOSW;                                           { Return hours }
544    END;
545    {$ENDIF}
546    {$IFDEF BIT_32_OR_MORE}                            { 32 BIT WINDOWS CODE }
547    VAR DT: TSystemTime;
548    BEGIN
549      {$IFDEF PPC_FPC}                                 { FPC WINDOWS COMPILER }
550      GetLocalTime(@DT);                              { Get the date/time }
551      {$ELSE}                                          { OTHER COMPILERS }
552      GetLocalTime(DT);                               { Get the date/time }
553      {$ENDIF}
554      Hour := DT.wHour;                                { Transfer hour }
555      Minute := DT.wMinute;                            { Transfer minute }
556      Second := DT.wSecond;                            { Transfer seconds }
557      Sec100 := DT.wMilliseconds DIV 10;               { Transfer hundredths }
558    END;
559    {$ENDIF}
560 {$ENDIF}
561 {$IFDEF OS_OS2}                                       { OS2 CODE }
562 VAR DT: DateTime;
563 BEGIN
564    DosGetDateTime(DT);                                { Get the date/time }
565    Hour   := DT.Hours;                                { Transfer hour }
566    Minute := DT.Minutes;                              { Transfer minute }
567    Second := DT.Seconds;                              { Transfer seconds }
568    Sec100 := DT.Hundredths;                           { Transfer hundredths }
569 END;
570 {$ENDIF}
571 {$ifdef OS_UNIX}
572 BEGIN
573   Dos.GetTime(Hour,Minute,Second,Sec100);
574 END;
575 {$endif OS_UNIX}
576 {$IFDEF OS_NETWARE}
577 BEGIN
578   Dos.GetTime(Hour,Minute,Second,Sec100);
579 END;
580 {$ENDIF OS_NETWARE}
581 {$IFDEF OS_AMIGA}
582 BEGIN
583   Dos.GetTime(Hour,Minute,Second,Sec100);
584 END;
585 {$ENDIF OS_AMIGA}
586 
587 {---------------------------------------------------------------------------}
588 {  MinutesToTime -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 19Jun97 LdB     }
589 {---------------------------------------------------------------------------}
590 PROCEDURE MinutesToTime (Md: LongInt; Var Hour24, Minute: Word);
591 BEGIN
592    Hour24 := Md DIV 60;                               { Hours of time }
593    Minute := Md MOD 60;                               { Minutes of time }
594 END;
595 
596 {---------------------------------------------------------------------------}
597 {  SecondsToTime -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 19Jun97 LdB     }
598 {---------------------------------------------------------------------------}
599 PROCEDURE SecondsToTime (Sd: LongInt; Var Hour24, Minute, Second: Word);
600 BEGIN
601    Hour24 := Sd DIV 3600;                             { Hours of time }
602    Minute := Sd MOD 3600 DIV 60;                      { Minutes of time }
603    Second := Sd MOD 60;                               { Seconds of time }
604 END;
605 
606 END.
607