source: LMDZ6/trunk/libf/phylmd/iotd_mod_h.f90 @ 5301

Last change on this file since 5301 was 5291, checked in by abarral, 4 days ago

Move thermcell_old.h iotd.h to module

File size: 775 bytes
Line 
1MODULE iotd_mod_h
2  IMPLICIT NONE; PRIVATE
3  PUBLIC imax, jmax, lmax, nid, dim_coord, iotd_ts, iotd_t0, n_names_iotd_def, names_iotd_def, &
4          un_nom
5  !=======================================================================
6  !
7  !   Auteur:  F. Hourdin
8  !   -------
9  !
10  !   Objet:
11  !   ------
12  !   Light interface for netcdf outputs. can be used outside LMDZ
13  !
14  !=======================================================================
15
16  integer imax, jmax, lmax, nid
17  INTEGER dim_coord(4)
18  real iotd_ts, iotd_t0
19  integer :: n_names_iotd_def
20  character*20, dimension(200) :: names_iotd_def
21  character*20 :: un_nom
22
23  !$OMP THREADPRIVATE(imax,jmax,lmax,nid,dim_coord,iotd_ts,iotd_t0,n_names_iotd_def,names_iotd_def,&
24  !$OMP un_nom)
25END MODULE iotd_mod_h
Note: See TracBrowser for help on using the repository browser.