Ignore:
Timestamp:
Jul 24, 2024, 1:17:08 PM (6 months ago)
Author:
abarral
Message:

Rename modules in misc from *_mod > lmdz_*
Put cbrt.f90, ch*.f90, pch*.f90 in new lmdz_libmath_pch.f90

Location:
LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/lmdz_1dutils.f90

    r5112 r5113  
    12461246    !   avec w=omega * dt
    12471247    !---------------------------------------------------------------
    1248     implicit none
     1248    IMPLICIT NONE
    12491249    ! arguments
    12501250    integer llm
     
    12821282    !   sans WTG rajouter une advection horizontale
    12831283    !----------------------------------------------------------------------
    1284     implicit none
     1284    IMPLICIT NONE
    12851285    include "YOMCST.h"
    12861286    !        argument
     
    13541354    !   sans WTG rajouter une advection horizontale
    13551355    !----------------------------------------------------------------------
    1356     implicit none
     1356    IMPLICIT NONE
    13571357    include "YOMCST.h"
    13581358    !        argument
     
    14291429    USE dimphy
    14301430
    1431     implicit none
     1431    IMPLICIT NONE
    14321432
    14331433    ! ========================================================
     
    14771477    USE dimphy
    14781478
    1479     implicit none
     1479    IMPLICIT NONE
    14801480
    14811481    ! ========================================================
     
    15101510    USE dimphy
    15111511
    1512     implicit none
     1512    IMPLICIT NONE
    15131513
    15141514    ! ========================================================
     
    15991599    USE dimphy
    16001600
    1601     implicit none
     1601    IMPLICIT NONE
    16021602
    16031603    ! ========================================================
     
    16641664          &, dth_mod_cas, hth_mod_cas, vth_mod_cas, mxcalc)
    16651665
    1666     implicit none
     1666    IMPLICIT NONE
    16671667
    16681668    include "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/lmdz_old_1dconv.f90

    r5104 r5113  
    88          &       Ts, imp_fcg, ts_fcg, Tp_fcg, Turb_fcg)
    99
    10     implicit none
     10    IMPLICIT NONE
    1111
    1212    !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     
    458458          &, d_t_adv, d_q_adv)
    459459    use dimphy
    460     implicit none
     460    IMPLICIT NONE
    461461
    462462    INCLUDE "dimensions.h"
     
    490490
    491491  SUBROUTINE copie(klevgcm, playgcm, psolgcm, file_forctl)
    492     implicit none
     492    IMPLICIT NONE
    493493
    494494    !cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     
    703703
    704704  SUBROUTINE corresbis(psol)
    705     implicit none
     705    IMPLICIT NONE
    706706
    707707    !cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/mod_1D_amma_read.F90

    r5105 r5113  
    5757
    5858SUBROUTINE read_1D_cases
    59       implicit none
     59      IMPLICIT NONE
    6060
    6161      INTEGER nid,rid,ierr
     
    176176
    177177!program reading forcings of the AMMA case study
    178       implicit none
     178      IMPLICIT NONE
    179179
    180180      integer ntime,nlevel
     
    348348           ,vitw_amma,ht_amma,hq_amma,lat_amma,sens_amma               &
    349349           ,vitw_prof,ht_prof,hq_prof,lat_prof,sens_prof)
    350         implicit none
     350        IMPLICIT NONE
    351351
    352352!---------------------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/mod_1D_cases_read.F90

    r5105 r5113  
    819819
    820820
    821         implicit none
     821        IMPLICIT NONE
    822822
    823823!---------------------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/mod_1D_cases_read2.F90

    r5105 r5113  
    8080
    8181  SUBROUTINE read_1D_cas
    82     implicit none
     82    IMPLICIT NONE
    8383
    8484    INTEGER nid,rid,ierr
     
    189189  !**********************************************************************************************
    190190  SUBROUTINE read2_1D_cas
    191     implicit none
     191    IMPLICIT NONE
    192192
    193193    INTEGER nid,rid,ierr
     
    314314  !**********************************************************************************************
    315315  SUBROUTINE old_read_SCM_cas
    316     implicit none
     316    IMPLICIT NONE
    317317
    318318    INCLUDE "date_cas.h"
     
    535535
    536536  !program reading forcing of the case study
    537   implicit none
     537  IMPLICIT NONE
    538538
    539539  integer ntime,nlevel
     
    650650
    651651  !program reading forcing of the case study
    652   implicit none
     652  IMPLICIT NONE
    653653
    654654  integer ntime,nlevel
     
    819819
    820820  !program reading forcing of the case study
    821   implicit none
     821  IMPLICIT NONE
    822822
    823823  integer ntime,nlevel,k,t
     
    10381038
    10391039
    1040   implicit none
     1040  IMPLICIT NONE
    10411041
    10421042  !---------------------------------------------------------------------------------------
     
    12471247
    12481248
    1249   implicit none
     1249  IMPLICIT NONE
    12501250
    12511251  !---------------------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/mod_1D_cases_read_std.F90

    r5105 r5113  
    8989  !**********************************************************************************************
    9090  SUBROUTINE read_SCM_cas
    91     implicit none
     91    IMPLICIT NONE
    9292
    9393    INCLUDE "date_cas.h"
     
    329329
    330330    !program reading forcing of the case study
    331     implicit none
     331    IMPLICIT NONE
    332332    INCLUDE "compar1d.h"
    333333
     
    658658
    659659
    660     implicit none
     660    IMPLICIT NONE
    661661
    662662    !---------------------------------------------------------------------------------------
     
    930930       ,dth_mod_cas,hth_mod_cas,vth_mod_cas,mxcalc)
    931931
    932     implicit none
     932    IMPLICIT NONE
    933933
    934934    INCLUDE "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/old_1DUTILS_read_interp.h

    r5105 r5113  
    33     &             ,ts_toga,plev_toga,t_toga,q_toga,u_toga,v_toga,w_toga        &
    44     &             ,ht_toga,vt_toga,hq_toga,vq_toga)
    5       implicit none
     5      IMPLICIT NONE
    66
    77!-------------------------------------------------------------------------
     
    6565!-------------------------------------------------------------------------
    6666      SUBROUTINE read_sandu(fich_sandu,nlev_sandu,nt_sandu,ts_sandu)
    67       implicit none
     67      IMPLICIT NONE
    6868
    6969!-------------------------------------------------------------------------
     
    102102      SUBROUTINE read_astex(fich_astex,nlev_astex,nt_astex,div_astex,      &
    103103     & ts_astex,ug_astex,vg_astex,ufa_astex,vfa_astex)
    104       implicit none
     104      IMPLICIT NONE
    105105
    106106!-------------------------------------------------------------------------
     
    150150
    151151
    152       implicit none
     152      IMPLICIT NONE
    153153
    154154      integer ntime,nlevel
     
    495495            nf90_inq_dimid,nf90_inquire_dimension
    496496
    497          implicit none
     497         IMPLICIT NONE
    498498         integer nid,ttm,llm
    499499         real*8 time(ttm)
     
    543543     &         ,omega_mod,o3mmr_mod,mxcalc)
    544544
    545        implicit none
     545       IMPLICIT NONE
    546546
    547547      INCLUDE "dimensions.h"
     
    657657     &         ,tke_mod,o3mmr_mod,mxcalc)
    658658
    659        implicit none
     659       IMPLICIT NONE
    660660
    661661      INCLUDE "dimensions.h"
     
    776776     &             ,ts_rico,t_rico,q_rico,u_rico,v_rico,w_rico             &
    777777     &             ,dth_dyn,dqh_dyn)
    778       implicit none
     778      IMPLICIT NONE
    779779
    780780!-------------------------------------------------------------------------
     
    939939     &             ,year_ini_sandu,day_ini_sandu,nt_sandu,dt_sandu         &
    940940     &             ,nlev_sandu,ts_sandu,ts_prof)
    941         implicit none
     941        IMPLICIT NONE
    942942
    943943!---------------------------------------------------------------------------------------
     
    10141014      SUBROUTINE read_armcu(fich_armcu,nlev_armcu,nt_armcu,                &
    10151015     & sens,flat,adv_theta,rad_theta,adv_qt)
    1016       implicit none
     1016      IMPLICIT NONE
    10171017
    10181018!-------------------------------------------------------------------------
     
    10551055     &         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
    10561056 
    1057        implicit none
     1057       IMPLICIT NONE
    10581058 
    10591059      INCLUDE "dimensions.h"
     
    11771177     &         ,dt_mod_cas,ht_mod_cas,vt_mod_cas,dtrad_mod_cas,dq_mod_cas,hq_mod_cas,vq_mod_cas,mxcalc)
    11781178 
    1179        implicit none
     1179       IMPLICIT NONE
    11801180 
    11811181       INCLUDE "dimensions.h"
     
    13361336     &         ,ht_mod,hq_mod,hu_mod,hv_mod,w_mod,omega_mod,mxcalc)
    13371337 
    1338        implicit none
     1338       IMPLICIT NONE
    13391339 
    13401340       INCLUDE "dimensions.h"
     
    14581458     &             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof   &
    14591459     &             ,ufa_prof,vfa_prof)
    1460         implicit none
     1460        IMPLICIT NONE
    14611461
    14621462!---------------------------------------------------------------------------------------
     
    15501550     &             ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof   &
    15511551     &             ,ht_prof,vt_prof,hq_prof,vq_prof)
    1552         implicit none
     1552        IMPLICIT NONE
    15531553
    15541554!---------------------------------------------------------------------------------------
     
    16921692     &             ,ustar_prof,psurf_prof,ug_prof,vg_prof                 &
    16931693     &             ,ht_prof,hq_prof,hu_prof,hv_prof,w_prof,omega_prof)
    1694         implicit none
     1694        IMPLICIT NONE
    16951695
    16961696!---------------------------------------------------------------------------------------
     
    18051805     &             ,ug_gabls4,vg_gabls4,ht_gabls4,hq_gabls4,tg_gabls4                          &
    18061806     &             ,ug_prof,vg_prof,ht_prof,hq_prof,tg_prof)
    1807         implicit none
     1807        IMPLICIT NONE
    18081808
    18091809!---------------------------------------------------------------------------------------
     
    18921892     &             ,nlev_armcu,fs_armcu,fl_armcu,at_armcu,rt_armcu         &
    18931893     &             ,aqt_armcu,fs_prof,fl_prof,at_prof,rt_prof,aqt_prof)
    1894         implicit none
     1894        IMPLICIT NONE
    18951895
    18961896!---------------------------------------------------------------------------------------
     
    19721972     &           wfls,dqtdxls,dqtdyls,dqtdtls,                             &
    19731973     &           thlpcar,tracer,nt1,nt2)
    1974       implicit none
     1974      IMPLICIT NONE
    19751975
    19761976        integer nlev_max,kmax,kmax2,ntrac
     
    20452045     &       thlprof,qprof,uprof,vprof,wprof,omega,o3mmr)
    20462046!======================================================================
    2047       implicit none
     2047      IMPLICIT NONE
    20482048
    20492049        integer nlev_max,kmax
     
    20772077     &    thlprof,qvprof,qlprof,qtprof,uprof,vprof,wprof,tkeprof,o3mmr)
    20782078!======================================================================
    2079       implicit none
     2079      IMPLICIT NONE
    20802080
    20812081        integer nlev_max,kmax
     
    21112111     &       vprof,thetaprof,tprof,qvprof,rvprof,aprof,bprof)
    21122112!======================================================================
    2113       implicit none
     2113      IMPLICIT NONE
    21142114
    21152115        integer nlev_max,kmax
     
    21722172      use netcdf, ONLY: nf90_open,nf90_nowrite,nf90_noerr,nf90_strerror,nf90_inq_varid,nf90_get_var,&
    21732173            nf90_inq_dimid,nf90_inquire_dimension
    2174       implicit none
     2174      IMPLICIT NONE
    21752175
    21762176      integer ntime,nlevel
     
    23832383            nf90_inq_dimid,nf90_inquire_dimension
    23842384
    2385       implicit none
     2385      IMPLICIT NONE
    23862386
    23872387      INCLUDE "YOMCST.h"
     
    27172717            nf90_inq_dimid,nf90_inquire_dimension
    27182718
    2719       implicit none
     2719      IMPLICIT NONE
    27202720
    27212721      integer ntime,nlevel,nsol
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/replay1d.F90

    r5103 r5113  
    1010
    1111
    12       implicit none
     12      IMPLICIT NONE
    1313      INCLUDE "dimensions.h"
    1414
Note: See TracChangeset for help on using the changeset viewer.