source: XIOS/trunk/src/interface/fortran/timer_interface.f90 @ 1849

Last change on this file since 1849 was 1849, checked in by ymipsl, 4 years ago

Export xios timers throw the fortran interface

YM

File size: 1.6 KB
Line 
1MODULE TIMER_INTERFACE
2   USE, INTRINSIC :: ISO_C_BINDING
3       
4   INTERFACE ! Ne pas appeler directement/Interface FORTRAN 2003 <-> C99
5 
6      SUBROUTINE cxios_timer_resume(timer_id, len_timer_id, trace) BIND(C)
7         USE ISO_C_BINDING
8         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: timer_id
9         INTEGER(kind = C_INT)       , VALUE        :: len_timer_id
10         LOGICAL  (kind = C_BOOL)    , VALUE        :: trace
11         
12      END SUBROUTINE cxios_timer_resume
13   
14      SUBROUTINE cxios_timer_suspend(timer_id, len_timer_id, trace) BIND(C)
15         USE ISO_C_BINDING
16         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: timer_id
17         INTEGER(kind = C_INT)       , VALUE        :: len_timer_id
18         LOGICAL  (kind = C_BOOL)    , VALUE        :: trace
19      END SUBROUTINE cxios_timer_suspend
20
21
22      SUBROUTINE cxios_timer_reset(timer_id, len_timer_id) BIND(C)
23         USE ISO_C_BINDING
24         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: timer_id
25         INTEGER(kind = C_INT)       , VALUE        :: len_timer_id
26      END SUBROUTINE cxios_timer_reset
27
28      SUBROUTINE cxios_timer_get_time(time) BIND(C)
29         USE ISO_C_BINDING
30         REAL  (kind = C_DOUBLE)                   :: time
31      END SUBROUTINE cxios_timer_get_time
32 
33      SUBROUTINE cxios_timer_get_cumulated_time(timer_id, len_timer_id, time) BIND(C)
34         USE ISO_C_BINDING
35         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: timer_id
36         INTEGER(kind = C_INT)       , VALUE        :: len_timer_id
37         REAL  (kind = C_DOUBLE)                    :: time
38       END SUBROUTINE cxios_timer_get_cumulated_time
39
40   END INTERFACE
41       
42END MODULE TIMER_INTERFACE
Note: See TracBrowser for help on using the repository browser.