Changeset 5302 for LMDZ6


Ignore:
Timestamp:
Oct 30, 2024, 6:19:06 PM (4 weeks ago)
Author:
abarral
Message:

Turn compar1d.h date_cas.h into module
Move fcg_racmo.h to obsolete

Location:
LMDZ6/trunk/libf
Files:
1 deleted
8 edited
3 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/dyn1d/1DUTILS.h

    r5301 r5302  
    1 #include "conf_gcm.f90"
    2 
    3 !
    4 ! $Id$
    5 !
    6 !
    7 !
     1
    82      SUBROUTINE conf_unicol
    93!
     
    148      USE fcg_gcssold_mod_h
    159      USE flux_arp_mod_h
     10      USE compar1d_mod_h
    1611      IMPLICIT NONE
    1712!-----------------------------------------------------------------------
     
    2116!   --------------
    2217
    23 #include "compar1d.h"
    24 #include "fcg_racmo.h"
     18
    2519!
    2620!
  • LMDZ6/trunk/libf/phylmd/dyn1d/compar1d_mod_h.f90

    r5301 r5302  
    1 !
    2 ! $Id: compar1d.h 2010-08-04 17:02:56Z lahellec $
    3 !
    4       integer :: forcing_type
    5       integer :: tend_u,tend_v,tend_w,tend_t,tend_q,tend_rayo
    6       real :: nudge_u,nudge_v,nudge_w,nudge_t,nudge_q
    7       integer :: iflag_nudge
    8       real :: nat_surf
    9       real :: tsurf
    10       real :: beta_surf
    11       real :: rugos
    12       real :: rugosh
    13       real :: xqsol(1:2)
    14       real :: qsurf
    15       real :: psurf
    16       real :: zsurf
    17       real :: albedo
    18       real :: snowmass
     1MODULE compar1d_mod_h
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC  nat_surf, tsurf, beta_surf, rugos, rugosh, &
     4          xqsol, qsurf, psurf, zsurf, albedo, time, time_ini, xlat, xlon, airefi, &
     5          wtsurf, wqsurf, restart_runoff, xagesno, qsolinp, zpicinp, &
     6          forcing_type, tend_u, tend_v, tend_w, tend_t, tend_q, tend_rayo, &
     7          nudge_u, nudge_v, nudge_w, nudge_t, nudge_q, &
     8          iflag_nudge, snowmass, &
     9          restart, ok_old_disvert, &
     10          tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh, &
     11          trad, forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar, &
     12          nudging_u, nudging_v, nudging_t, nudging_qv, nudging_w, &
     13          p_nudging_u, p_nudging_v, p_nudging_t, p_nudging_qv, p_nudging_w
    1914
    20       real :: time
    21       real :: time_ini
    22       real :: xlat
    23       real :: xlon
    24       real :: airefi
    25       real :: wtsurf
    26       real :: wqsurf
    27       real :: restart_runoff
    28       real :: xagesno
    29       real :: qsolinp
    30       real :: zpicinp
     15  INTEGER :: forcing_type
     16  INTEGER :: tend_u, tend_v, tend_w, tend_t, tend_q, tend_rayo
     17  REAL :: nudge_u, nudge_v, nudge_w, nudge_t, nudge_q
     18  INTEGER :: iflag_nudge
     19  REAL :: nat_surf
     20  REAL :: tsurf
     21  REAL :: beta_surf
     22  REAL :: rugos
     23  REAL :: rugosh
     24  REAL :: xqsol(1:2)
     25  REAL :: qsurf
     26  REAL :: psurf
     27  REAL :: zsurf
     28  REAL :: albedo
     29  REAL :: snowmass
    3130
    32       logical :: restart
    33       logical :: ok_old_disvert
     31  REAL :: time
     32  REAL :: time_ini
     33  REAL :: xlat
     34  REAL :: xlon
     35  REAL :: airefi
     36  REAL :: wtsurf
     37  REAL :: wqsurf
     38  REAL :: restart_runoff
     39  REAL :: xagesno
     40  REAL :: qsolinp
     41  REAL :: zpicinp
    3442
    35 ! Pour les forcages communs: ces entiers valent 0 ou 1
    36 ! tadv= advection tempe, tadvv= adv tempe verticale, tadvh= adv tempe horizontale
    37 ! idem pour l advection en theta
    38 ! qadv= advection q, qadvv= adv q verticale, qadvh= adv q horizontale
    39 ! trad= 0 (rayonnement actif) ou 1 (prescrit par tend_rad) ou adv (prescir et contenu dans les tadv)
    40 ! forcages en omega, w, vent geostrophique ou ustar
    41 ! Parametres de nudging en u,v,t,q valent 0 ou 1 ou le temps de nudging
     43  LOGICAL :: restart
     44  LOGICAL :: ok_old_disvert
    4245
    43       integer :: tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh, trad
    44       integer :: forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar
    45       real    :: nudging_u, nudging_v, nudging_w, nudging_t, nudging_qv
    46       real    :: p_nudging_u, p_nudging_v, p_nudging_w, p_nudging_t, p_nudging_qv
    47       common/com_par1d/                                                 &
    48      & nat_surf,tsurf,beta_surf,rugos,rugosh,                           &
    49      & xqsol,qsurf,psurf,zsurf,albedo,time,time_ini,xlat,xlon,airefi,   &
    50      & wtsurf,wqsurf,restart_runoff,xagesno,qsolinp,zpicinp,            &
    51      & forcing_type,tend_u,tend_v,tend_w,tend_t,tend_q,tend_rayo,       &
    52      & nudge_u,nudge_v,nudge_w,nudge_t,nudge_q,                         &
    53      & iflag_nudge,snowmass,                                            &
    54      & restart,ok_old_disvert,                                          &
    55      & tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh,   &
    56      & trad, forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar,  &
    57      & nudging_u, nudging_v, nudging_t, nudging_qv, nudging_w,          &
    58      & p_nudging_u, p_nudging_v, p_nudging_t, p_nudging_qv, p_nudging_w
     46  ! Pour les forcages communs: ces entiers valent 0 ou 1
     47  ! tadv= advection tempe, tadvv= adv tempe verticale, tadvh= adv tempe horizontale
     48  ! idem pour l advection en theta
     49  ! qadv= advection q, qadvv= adv q verticale, qadvh= adv q horizontale
     50  ! trad= 0 (rayonnement actif) ou 1 (prescrit par tend_rad) ou adv (prescir et contenu dans les tadv)
     51  ! forcages en omega, w, vent geostrophique ou ustar
     52  ! Parametres de nudging en u,v,t,q valent 0 ou 1 ou le temps de nudging
    5953
    60 !$OMP THREADPRIVATE(/com_par1d/)
     54  INTEGER :: tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh, trad
     55  INTEGER :: forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar
     56  REAL :: nudging_u, nudging_v, nudging_w, nudging_t, nudging_qv
     57  REAL :: p_nudging_u, p_nudging_v, p_nudging_w, p_nudging_t, p_nudging_qv
    6158
    6259
     60  !$OMP THREADPRIVATE(nat_surf, tsurf, beta_surf, rugos, rugosh, &
     61  !$OMP      xqsol, qsurf, psurf, zsurf, albedo, time, time_ini, xlat, xlon, airefi, &
     62  !$OMP      wtsurf, wqsurf, restart_runoff, xagesno, qsolinp, zpicinp, &
     63  !$OMP      forcing_type, tend_u, tend_v, tend_w, tend_t, tend_q, tend_rayo, &
     64  !$OMP      nudge_u, nudge_v, nudge_w, nudge_t, nudge_q, &
     65  !$OMP      iflag_nudge, snowmass, &
     66  !$OMP      restart, ok_old_disvert, &
     67  !$OMP      tadv, tadvv, tadvh, qadv, qadvv, qadvh, thadv, thadvv, thadvh, &
     68  !$OMP      trad, forc_omega, forc_u, forc_v, forc_w, forc_geo, forc_ustar, &
     69  !$OMP      nudging_u, nudging_v, nudging_t, nudging_qv, nudging_w, &
     70  !$OMP      p_nudging_u, p_nudging_v, p_nudging_t, p_nudging_qv, p_nudging_w)
    6371
    64 
    65 
    66 
    67 
    68 
    69 
    70 
    71 
     72END MODULE compar1d_mod_h
  • LMDZ6/trunk/libf/phylmd/dyn1d/date_cas_mod_h.f90

    r5301 r5302  
    1       integer :: year_ini_cas    ! initial year of the case
    2       integer :: mth_ini_cas     ! initial month of the case
    3       integer :: day_deb         ! initial day of the case
    4       real :: heure_ini_cas      ! start time of the case
    5       real :: pdt_cas            ! forcing_frequency
    6       real :: day_ju_ini_cas     ! julian day of initial day of the case
     1MODULE date_cas_mod_h
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC year_ini_cas, mth_ini_cas, day_deb, heure_ini_cas, pdt_cas, day_ju_ini_cas
    74
    8       common /date_cas/year_ini_cas,mth_ini_cas,day_deb,heure_ini_cas,pdt_cas,day_ju_ini_cas
     5  INTEGER :: year_ini_cas    ! initial year of the case
     6  INTEGER :: mth_ini_cas     ! initial month of the case
     7  INTEGER :: day_deb         ! initial day of the case
     8  REAL :: heure_ini_cas      ! start time of the case
     9  REAL :: pdt_cas            ! forcing_frequency
     10  REAL :: day_ju_ini_cas     ! julian day of initial day of the case
     11END MODULE date_cas_mod_h
    912
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_amma_read.f90

    r5270 r5302  
    352352     &         ,vitw_amma,ht_amma,hq_amma,lat_amma,sens_amma               &
    353353     &         ,vitw_prof,ht_prof,hq_prof,lat_prof,sens_prof)
     354          USE compar1d_mod_h
    354355        implicit none
    355356
     
    362363! dt_amma: total time interval (in sec) between 2 forcing data (e.g. 30min for AMMA)
    363364!---------------------------------------------------------------------------------------
    364 
    365         INCLUDE "compar1d.h"
    366365
    367366! inputs:
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read.f90

    r5270 r5302  
    828828     &         ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas)
    829829         
    830 
     830        USE compar1d_mod_h
     831        USE date_cas_mod_h
    831832        implicit none
    832833
     
    839840! pdt_cas: total time interval (in sec) between 2 forcing data
    840841!---------------------------------------------------------------------------------------
    841 
    842         INCLUDE "compar1d.h"
    843         INCLUDE "date_cas.h"
    844842
    845843! inputs:
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read2.f90

    r5270 r5302  
    315315  SUBROUTINE old_read_SCM_cas
    316316    use netcdf, only: nf90_get_var
     317    USE date_cas_mod_h
    317318    implicit none
    318     INCLUDE "date_cas.h"
    319319
    320320    INTEGER nid,rid,ierr
     
    10431043     ,hq_prof_cas,vq_prof_cas,lat_prof_cas,sens_prof_cas    &
    10441044     ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas)
    1045 
    1046 
     1045  USE compar1d_mod_h
     1046  USE date_cas_mod_h
    10471047  implicit none
    10481048
     
    10551055  ! pdt_cas: total time interval (in sec) between 2 forcing data
    10561056  !---------------------------------------------------------------------------------------
    1057 
    1058   INCLUDE "compar1d.h"
    1059   INCLUDE "date_cas.h"
    10601057
    10611058  ! inputs:
     
    12531250     ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas,tke_prof_cas)
    12541251
    1255 
     1252  USE compar1d_mod_h
     1253  USE date_cas_mod_h
    12561254  implicit none
    12571255
     
    12641262  ! pdt_cas: total time interval (in sec) between 2 forcing data
    12651263  !---------------------------------------------------------------------------------------
    1266 
    1267   INCLUDE "compar1d.h"
    1268   INCLUDE "date_cas.h"
    12691264
    12701265  ! inputs:
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read_std.f90

    r5285 r5302  
    9090  SUBROUTINE read_SCM_cas
    9191    use netcdf, only: nf90_get_var
     92    USE date_cas_mod_h
    9293    implicit none
    93     INCLUDE "date_cas.h"
    9494
    9595    INTEGER nid,rid,ierr
     
    330330    !program reading forcing of the case study
    331331    use netcdf, only: nf90_get_var
     332    USE compar1d_mod_h
    332333    implicit none
    333     INCLUDE "compar1d.h"
    334334
    335335    integer ntime,nlevel,k,t
     
    653653       ,lat_prof_cas,sens_prof_cas                                        &
    654654       ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas,tkes_prof_cas)
    655 
    656 
    657 
    658 
    659 
    660 
     655    USE compar1d_mod_h
     656    USE date_cas_mod_h
    661657    implicit none
    662658
     
    669665    ! pdt_cas: total time interval (in sec) between 2 forcing data
    670666    !---------------------------------------------------------------------------------------
    671 
    672     INCLUDE "compar1d.h"
    673     INCLUDE "date_cas.h"
    674667
    675668    ! inputs:
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_1DUTILS_read_interp.h

    r5285 r5302  
    15561556     &             ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof   &
    15571557     &             ,ht_prof,vt_prof,hq_prof,vq_prof)
     1558     USE compar1d_mod_h
    15581559        implicit none
    15591560
     
    15661567! dt_toga: total time interval (in sec) between 2 forcing data (e.g. 6h for TOGA-COARE)
    15671568!---------------------------------------------------------------------------------------
    1568 
    1569         INCLUDE "compar1d.h"
    15701569
    15711570! inputs:
     
    16981697     &             ,ustar_prof,psurf_prof,ug_prof,vg_prof                 &
    16991698     &             ,ht_prof,hq_prof,hu_prof,hv_prof,w_prof,omega_prof)
     1699     USE compar1d_mod_h
    17001700        implicit none
    17011701
     
    17081708! dt_dice: total time interval (in sec) between 2 forcing data (e.g. 30min. for Dice)
    17091709!---------------------------------------------------------------------------------------
    1710 
    1711         INCLUDE "compar1d.h"
    17121710
    17131711! inputs:
     
    18111809     &             ,ug_gabls4,vg_gabls4,ht_gabls4,hq_gabls4,tg_gabls4                          &
    18121810     &             ,ug_prof,vg_prof,ht_prof,hq_prof,tg_prof)
     1811     USE compar1d_mod_h
    18131812        implicit none
    18141813
     
    18211820! dt_gabls4: total time interval (in sec) between 2 forcing data (e.g. 60min. for gabls4)
    18221821!---------------------------------------------------------------------------------------
    1823 
    1824         INCLUDE "compar1d.h"
    18251822
    18261823! inputs:
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_lmdz1d.f90

    r5301 r5302  
    5656  USE tsoilnudge_mod_h
    5757  USE fcg_gcssold_mod_h
     58        USE compar1d_mod_h
     59        USE date_cas_mod_h
    5860implicit none
    5961
    60       INCLUDE "compar1d.h"
    61       INCLUDE "date_cas.h"
    6262!!!      INCLUDE "fbforcing.h"
    6363
  • LMDZ6/trunk/libf/phylmd/dyn1d/scm.f90

    r5301 r5302  
    5252  USE tsoilnudge_mod_h
    5353  USE fcg_gcssold_mod_h
     54  USE compar1d_mod_h
     55  USE date_cas_mod_h
    5456implicit none
    55       INCLUDE "compar1d.h"
    56       INCLUDE "date_cas.h"
    5757
    5858!=====================================================================
Note: See TracChangeset for help on using the changeset viewer.