source: XIOS/dev/dev_rv/src/xmlio/fortran/idate.f90 @ 1512

Last change on this file since 1512 was 270, checked in by hozdoba, 13 years ago

Début nouvelle interface fortran

File size: 1.5 KB
Line 
1MODULE IDATE
2   USE, INTRINSIC :: ISO_C_BINDING
3
4   ! enum XCalendarType
5   INTEGER(kind = C_INT), PARAMETER :: D360 = 0 , ALLLEAP = 1 , NOLEAP = 2 , JULIAN = 3 , GREGORIAN = 4
6
7   TYPE XDate
8      INTEGER :: year, month, day, hour, minute, second
9   END TYPE XDate
10
11   TYPE XDuration
12      REAL(kind = 8) :: year, month, day, hour, minute, second
13   END TYPE XDuration
14   
15   INTERFACE ! Ne pas appeler directement/Interface FORTRAN 2003 <-> C99
16   
17      SUBROUTINE xios_set_timestep(ts_year, ts_month, ts_day, ts_hour, ts_minute, ts_second) BIND(C)
18         IMPORT C_DOUBLE
19         REAL (kind = C_DOUBLE), VALUE :: ts_year, ts_month , ts_day   , &
20                                          ts_hour, ts_minute, ts_second
21      END SUBROUTINE xios_set_timestep
22
23      SUBROUTINE xios_update_calendar(step) BIND(C)
24         IMPORT C_INT
25         INTEGER (kind = C_INT), VALUE :: step
26      END SUBROUTINE xios_update_calendar
27     
28   END INTERFACE
29   
30   CONTAINS ! Fonctions disponibles pour les utilisateurs.
31   
32   SUBROUTINE set_timestep(timestep)
33      TYPE(XDuration), INTENT(IN):: timestep
34      CALL xios_set_timestep(timestep%year, timestep%month , timestep%day, &
35                             timestep%hour, timestep%minute, timestep%second)
36   END SUBROUTINE set_timestep
37   
38   SUBROUTINE update_calendar(step)
39      INTEGER, INTENT(IN):: step
40      IF (step < 1) THEN
41         PRINT *, "L'argument 'step' ne peut être négatif ou nul"
42         STOP
43      END IF
44      CALL xios_update_calendar(step)
45   END SUBROUTINE update_calendar
46   
47END MODULE IDATE
Note: See TracBrowser for help on using the repository browser.