Changeset 5291


Ignore:
Timestamp:
Oct 28, 2024, 4:44:39 PM (3 hours ago)
Author:
abarral
Message:

Move thermcell_old.h iotd.h to module

Location:
LMDZ6/trunk/libf
Files:
6 edited
4 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phy_common/mod_phys_lmdz_omp_data.F90

    r3435 r5291  
    109109  USE print_control_mod, ONLY: lunout
    110110  IMPLICIT NONE
    111 !  INCLUDE "iniprint.h"
    112111
    113112!$OMP CRITICAL 
  • LMDZ6/trunk/libf/phylmd/calltherm.F90

    r5282 r5291  
    4141#endif
    4242      USE clesphys_mod_h
     43      USE thermcell_old_mod_h, ONLY: r_aspect_thermals, l_mix_thermals, w2di_thermals
    4344      implicit none
    44       include "thermcell_old.h"
    4545
    4646
  • LMDZ6/trunk/libf/phylmd/iophys.F90

    r5285 r5291  
    216216
    217217      SUBROUTINE iotd_ecrit_seq(nom,lllm,titre,unite,px)
     218        USE iotd_mod_h
    218219
    219220      IMPLICIT NONE
    220 
    221 ! px arrive
    222 
    223       INCLUDE "iotd.h"
    224221
    225222
  • LMDZ6/trunk/libf/phylmd/iotd_ecrit.f90

    r5270 r5291  
    2424      USE netcdf, ONLY: nf90_put_var, nf90_inq_varid, nf90_enddef, nf90_redef, nf90_sync, nf90_noerr, &
    2525            nf90_float, nf90_def_var
     26      USE iotd_mod_h
    2627      implicit none
    27 
    28 ! Commons
    29       INCLUDE "iotd.h"
    3028
    3129
  • LMDZ6/trunk/libf/phylmd/iotd_fin.f90

    r5270 r5291  
    1       SUBROUTINE iotd_fin
    2       USE netcdf, ONLY: nf90_close
    3       IMPLICIT NONE
     1SUBROUTINE iotd_fin
     2  USE iotd_mod_h, ONLY: nid
     3  USE netcdf, ONLY: nf90_close
     4  IMPLICIT NONE
    45
    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       INCLUDE "iotd.h"
    16       integer ierr
     6  !=======================================================================
     7  !
     8  !   Auteur:  F. Hourdin
     9  !   -------
     10  !
     11  !   Objet:
     12  !   ------
     13  !   Light interface for netcdf outputs. can be used outside LMDZ
     14  !
     15  !=======================================================================
     16  integer ierr
    1717
    18 !   Arguments:
    19 !   ----------
     18  !   Arguments:
     19  !   ----------
    2020
    21       ierr=nf90_close(nid)
    22 
    23       END
     21  ierr = nf90_close(nid)
     22END
  • LMDZ6/trunk/libf/phylmd/iotd_ini.f90

    r5270 r5291  
    22      USE netcdf, ONLY: nf90_enddef, nf90_put_att, nf90_float, nf90_def_var, nf90_redef, &
    33            nf90_global, nf90_def_dim, nf90_create, nf90_clobber, nf90_unlimited, nf90_put_var
     4      USE iotd_mod_h
    45      IMPLICIT NONE
    56
     
    1516!=======================================================================
    1617!-----------------------------------------------------------------------
    17 !   Declarations:
    18 !   -------------
    19       INCLUDE "iotd.h"
    2018
    2119!   Arguments:
  • LMDZ6/trunk/libf/phylmd/iotd_mod_h.f90

    r5290 r5291  
    1 !=======================================================================
    2 !
    3 !   Auteur:  F. Hourdin
    4 !   -------
    5 !
    6 !   Objet:
    7 !   ------
    8 !   Light interface for netcdf outputs. can be used outside LMDZ
    9 !
    10 !=======================================================================
     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  !=======================================================================
    1115
    12       integer imax,jmax,lmax,nid
    13       INTEGER dim_coord(4)
    14       real iotd_ts,iotd_t0
    15       integer :: n_names_iotd_def
    16       character*20, dimension(200) :: names_iotd_def
    17       character*20 :: un_nom
     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
    1822
    19       common/iotd_ca/imax,jmax,lmax,nid,dim_coord,iotd_t0,iotd_ts
    20       common/iotd_cb/n_names_iotd_def,names_iotd_def
    21 !$OMP THREADPRIVATE(/iotd_ca/)
    22 !$OMP THREADPRIVATE(/iotd_cb/)
     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
  • LMDZ6/trunk/libf/phylmd/thermcell_old_mod_h.f90

    r5290 r5291  
    1 
    2       real,parameter     :: r_aspect_thermals=2.
    3       real,parameter     :: l_mix_thermals=30.
    4       integer,parameter  :: w2di_thermals=0
     1MODULE thermcell_old_mod_h
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC r_aspect_thermals, l_mix_thermals, w2di_thermals
     4  real, parameter :: r_aspect_thermals = 2.
     5  real, parameter :: l_mix_thermals = 30.
     6  integer, parameter :: w2di_thermals = 0
     7END MODULE thermcell_old_mod_h
  • LMDZ6/trunk/libf/phylmdiso/iotd_mod_h.f90

    r5290 r5291  
    1 link ../phylmd/iotd.h
     1link ../phylmd/iotd_mod_h.f90
  • LMDZ6/trunk/libf/phylmdiso/thermcell_old_mod_h.f90

    r5290 r5291  
    1 link ../phylmd/thermcell_old.h
     1link ../phylmd/thermcell_old_mod_h.f90
Note: See TracChangeset for help on using the changeset viewer.