Changeset 5368


Ignore:
Timestamp:
Dec 3, 2024, 12:40:26 PM (29 hours ago)
Author:
abarral
Message:

(WIP) Turn implicit into explicit declarations
Turn 1dconv.h into a module to that end

Location:
LMDZ6/trunk/libf/phylmd/dyn1d
Files:
3 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/dyn1d/lmdz1d.F90

    r5272 r5368  
    1 !
    2 ! $Id$
    3 !
     1
    42!#ifdef CPP_1D
    53!INCLUDE "../dyn3d/mod_const_mpi.F90"
     
    2725
    2826#include "1DUTILS.h"
    29 #include "1Dconv.h"
    3027
    3128!#endif
  • LMDZ6/trunk/libf/phylmd/dyn1d/m_1dconv_mod_h.f90

    r5367 r5368  
    1 !
    2 ! $Id$
    3 !
     1MODULE m_1dconv_mod_h
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC get_uvd, copie, get_uvd2
     4
     5  REAL play(100)  !pression en Pa au milieu de chaque couche GCM
     6  INTEGER JM(100) !pression en Pa au milieu de chaque couche GCM
     7  REAL coef1(100) !coefficient d interpolation
     8  REAL coef2(100) !coefficient d interpolation
     9  INTEGER klev
     10
     11  INTEGER nblvlm !nombre de niveau de pression du mesoNH
     12  REAL playm(100)  !pression en Pa au milieu de chaque couche Meso-NH
     13  REAL hplaym(100) !pression en hPa milieux des couches Meso-NH
     14
     15CONTAINS
     16
    417        subroutine get_uvd(itap,dtime,file_forctl,file_fordat,                  &
    518     &       ht,hq,hw,hu,hv,hthturb,hqturb,                                     &
     
    1326! pouvoir calculer la convergence et le cisaillement dans la physiq
    1427!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    15 
    16 
    17 
    18       INTEGER klev
    19       REAL play(100)  !pression en Pa au milieu de chaque couche GCM
    20       INTEGER JM(100) !pression en Pa au milieu de chaque couche GCM
    21       REAL coef1(100) !coefficient d interpolation
    22       REAL coef2(100) !coefficient d interpolation
    23 
    24       INTEGER nblvlm !nombre de niveau de pression du mesoNH
    25       REAL playm(100)  !pression en Pa au milieu de chaque couche Meso-NH
    26       REAL hplaym(100) !pression en hPa milieux des couches Meso-NH
    27 
    2828      integer i,j,k,ll,in
    2929
    3030      CHARACTER*80 file_forctl,file_fordat
    31 
    32       COMMON/com1_phys_gcss/play,coef1,coef2,JM,klev
    33       COMMON/com2_phys_gcss/playm,hplaym,nblvlm
    3431
    3532!======================================================================
     
    6663        integer itap
    6764        real dtime
    68         real ht(100)
    69         real hq(100)
    70         real hu(100)
    71         real hv(100)
    72         real hw(100)
    73         real hthturb(100)
    74         real hqturb(100)
     65        real ht(:)
     66        real hq(:)
     67        real hu(:)
     68        real hv(:)
     69        real hw(:)
     70        real hthturb(:)
     71        real hqturb(:)
    7572        real Ts, Ts_subr
    7673        logical imp_fcg
     
    141138! variables destinees a la lecture du pas de temps du fichier de donnees
    142139!---------------------------------------------------------------------
    143        character*80 aaa,atemps,spaces,apasmax
     140       character*80 aaa,atemps,apasmax
    144141       integer nch,imn,ipa
    145 !---------------------------------------------------------------------
    146 !  procedures appelees
    147         external rdgrads    !lire en iterant dans forcing.dat
    148142!---------------------------------------------------------------------
    149143               print*,'le pas itap est:',itap
     
    496490
    497491!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    498 ! cette routine remplit les COMMON com1_phys_gcss et com2_phys_gcss.h
     492! cette routine remplit les variables du module
    499493!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    500 
    501       INTEGER klev !nombre de niveau de pression du GCM
    502       REAL play(100)  !pression en Pa au milieu de chaque couche GCM
    503       INTEGER JM(100)
    504       REAL coef1(100)   !coefficient d interpolation
    505       REAL coef2(100)   !coefficient d interpolation
    506 
    507       INTEGER nblvlm !nombre de niveau de pression du mesoNH
    508       REAL playm(100) !pression en Pa au milieu de chaque couche Meso-NH
    509       REAL hplaym(100)!pression en hecto-Pa des milieux de couche Meso-NH
    510 
    511       COMMON/com1_phys_gcss/play,coef1,coef2,JM,klev
    512       COMMON/com2_phys_gcss/playm,hplaym,nblvlm
    513494
    514495      integer k,klevgcm
     
    578559!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    579560!
    580       INTEGER nblvlm !nombre de niveau de pression du mesoNH
    581       REAL playm(100)  !pression en Pa milieu de chaque couche Meso-NH
    582       REAL hplaym(100) !pression en hPa des milieux de couche Meso-NH
    583       COMMON/com2_phys_gcss/playm,hplaym,nblvlm
    584561
    585562      INTEGER i,lu,mlz,mlzh
     
    588565
    589566      character*4 a
    590       character*80 aaa,anblvl,spaces
     567      character*80 aaa,anblvl
    591568      integer nch
    592569
     
    718695! meme.
    719696!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    720 
    721       INTEGER klev    !nombre de niveau de pression du GCM
    722       REAL play(100)  !pression en Pa au milieu de chaque couche GCM
    723       INTEGER JM(100)
    724       REAL coef1(100) !coefficient d interpolation
    725       REAL coef2(100) !coefficient d interpolation
    726 
    727       INTEGER nblvlm !nombre de niveau de pression du mesoNH
    728       REAL playm(100) !pression en Pa milieu de chaque couche Meso-NH
    729       REAL hplaym(100)!pression en hPa des milieux de couche Meso-NH
    730 
    731       COMMON/com1_phys_gcss/play,coef1,coef2,JM,klev
    732       COMMON/com2_phys_gcss/playm,hplaym,nblvlm
    733697
    734698      REAL psol
     
    823787      END
    824788
    825       CHARACTER*(*) FUNCTION SPACES(STR,NSPACE)
     789      CHARACTER*(80) FUNCTION SPACES(STR,NSPACE)
    826790!
    827791! CERN PROGLIB# M433    SPACES          .VERSION KERNFOR  4.14  860211
     
    832796!-    replaced by NSPACE blanks inside the string STR
    833797!
    834       CHARACTER*(*), INTENT(OUT) :: str
    835       INTEGER, INTENT(INOUT) :: nspace
     798      CHARACTER*(80), INTENT(OUT) :: str
     799      INTEGER :: nspace
    836800      INTEGER :: iblank, inonbl, ispace, lenspa, i, lens
    837801!
     
    881845!
    882846  999 END
     847
     848END MODULE m_1dconv_mod_h
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_1DUTILS_read_interp.h

    r5302 r5368  
    29602960      SUBROUTINE read_circ(nlev_circ,cf,lwp,iwp,reliq,reice,t,z,p,pm,h2o,o3,sza)
    29612961
     2962      USE yomcst_mod_h, ONLY: rpi
     2963
     2964      INTEGER :: ncm_1, nlev_circ, ilev, iskip, icm_1, il
    29622965      parameter (ncm_1=49180)
    29632966
    2964       real albsfc(ncm_1), albsfc_w(ncm_1)
     2967      REAL :: albsfc(ncm_1), albsfc_w(ncm_1), aer_alpha, sw_dn_toa, tsfc
    29652968      real cf(nlev_circ), icefra(nlev_circ), deice(nlev_circ), &
    29662969           reliq(nlev_circ), reice(nlev_circ), lwp(nlev_circ), iwp(nlev_circ)
     
    30643067      SUBROUTINE read_rtmip(nlev_rtmip,play,plev,t,h2o,o3)
    30653068
    3066 
     3069      INTEGER nlev_rtmip, il
    30673070      real t(nlev_rtmip), pt(nlev_rtmip),pb(nlev_rtmip),h2o(nlev_rtmip), o3(nlev_rtmip)
    30683071      real temp(nlev_rtmip), play(nlev_rtmip),ovap(nlev_rtmip), oz(nlev_rtmip),plev(nlev_rtmip+1)
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_lmdz1d.f90

    r5302 r5368  
    5353   USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    5454   USE dimsoil_mod_h, ONLY: nsoilmx
    55   USE yomcst_mod_h
    56   USE tsoilnudge_mod_h
    57   USE fcg_gcssold_mod_h
    58         USE compar1d_mod_h
    59         USE date_cas_mod_h
     55   USE yomcst_mod_h
     56   USE tsoilnudge_mod_h
     57   USE fcg_gcssold_mod_h
     58   USE compar1d_mod_h
     59   USE date_cas_mod_h
     60   USE m_1dconv_mod_h, ONLY: get_uvd, get_uvd2, copie
    6061implicit none
    6162
Note: See TracChangeset for help on using the changeset viewer.