Changeset 3816 for dynamico_lmdz/aquaplanet/LMDZ5
- Timestamp:
- Apr 17, 2015, 9:51:15 AM (10 years ago)
- Location:
- dynamico_lmdz/aquaplanet/LMDZ5/libf
- Files:
-
- 1 deleted
- 34 edited
- 5 moved
Legend:
- Unmodified
- Added
- Removed
-
dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3d/gcm.F90
r3809 r3816 417 417 #ifdef CPP_PHYS 418 418 CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, & 419 rlatu,rl onv,aire,cu,cv,rad,g,r,cpp, &419 rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, & 420 420 iflag_phys) 421 421 #endif -
dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3dmem/gcm.F
r3809 r3816 406 406 #ifdef CPP_PHYS 407 407 CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, 408 & rlatu,rl onv,aire,cu,cv,rad,g,r,cpp,408 & rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, 409 409 & iflag_phys) 410 410 #endif -
dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3dpar/gcm.F
r3809 r3816 407 407 #ifdef CPP_PHYS 408 408 CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, 409 & rlatu,rl onv,aire,cu,cv,rad,g,r,cpp,409 & rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, 410 410 & iflag_phys) 411 411 #endif -
dynamico_lmdz/aquaplanet/LMDZ5/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90
r3809 r3816 3 3 4 4 5 SUBROUTINE iniphysiq(ii m,jjm,nlayer,punjours, pdayref,ptimestep, &6 rlatu,rl onv,aire,cu,cv,&5 SUBROUTINE iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep, & 6 rlatu,rlatv,rlonu,rlonv,aire,cu,cv, & 7 7 prad,pg,pr,pcpp,iflag_phys) 8 8 USE dimphy, ONLY: klev ! number of atmospheric levels … … 14 14 klon_mpi_begin ! start indes of columns (on local mpi grid) 15 15 USE comgeomphy, ONLY: initcomgeomphy, & 16 initcomgeomphy_vert, & 17 initcomgeomphy_horiz,& 16 18 airephy, & ! physics grid area (m2) 17 19 cuphy, & ! cu coeff. (u_covariant = cu * u) … … 19 21 rlond, & ! longitudes 20 22 rlatd ! latitudes 23 USE misc_mod, ONLY: debug 24 USE infotrac, ONLY: nqtot,nqo,nbtr,tname,ttext,type_trac,& 25 niadv,conv_flg,pbl_flg,solsym 26 USE phytrac_mod, ONLY: ini_phytrac_mod 27 USE control_mod, ONLY: dayref,anneeref,day_step,iphysiq,nday,& 28 config_inca,raz_date,offline 29 USE inifis_mod, ONLY: inifis 30 USE infotrac_phy, ONLY: init_infotrac_phy 21 31 USE phyaqua_mod, ONLY: iniaqua 22 32 IMPLICIT NONE … … 27 37 ! ======================================================================= 28 38 29 include "YOMCST.h" 39 ! include "YOMCST.h" 40 include "dimensions.h" 41 include "comvert.h" 42 include "comconst.h" 30 43 include "iniprint.h" 44 include "temps.h" 31 45 32 46 REAL, INTENT (IN) :: prad ! radius of the planet (m) … … 36 50 REAL, INTENT (IN) :: punjours ! length (in s) of a standard day 37 51 INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers 38 INTEGER, INTENT (IN) :: iim ! number of atmospheric columns along longitudes 39 INTEGER, INTENT (IN) :: jjm ! number of atompsheric columns along latitudes 40 REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid 41 REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid 42 REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2) 43 REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u) 44 REAL, INTENT (IN) :: cv((iim+1)*jjm) ! cv coeff. (v_covariant = cv * v) 52 INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes 53 INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes 54 REAL, INTENT (IN) :: rlatu(jj+1) ! latitudes of the physics grid 55 REAL, INTENT (IN) :: rlatv(jj) ! latitude boundaries of the physics grid 56 REAL, INTENT (IN) :: rlonv(ii+1) ! longitudes of the physics grid 57 REAL, INTENT (IN) :: rlonu(ii+1) ! longitude boundaries of the physics grid 58 REAL, INTENT (IN) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2) 59 REAL, INTENT (IN) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u) 60 REAL, INTENT (IN) :: cv((ii+1)*jj) ! cv coeff. (v_covariant = cv * v) 45 61 INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation 46 62 REAL, INTENT (IN) :: ptimestep !physics time step (s) … … 70 86 END IF 71 87 72 !call init_phys_lmdz(ii m,jjm+1,llm,1,(/(jjm-1)*iim+2/))88 !call init_phys_lmdz(ii,jj+1,llm,1,(/(jj-1)*ii+2/)) 73 89 74 90 ! Generate global arrays on full physics grid … … 82 98 cufi(1) = cu(1) 83 99 cvfi(1) = cv(1) 84 DO j=2,jj m85 DO i=1,ii m86 latfi((j-2)*ii m+1+i)= rlatu(j)87 lonfi((j-2)*ii m+1+i)= rlonv(i)88 cufi((j-2)*ii m+1+i) = cu((j-1)*iim+1+i)89 cvfi((j-2)*ii m+1+i) = cv((j-1)*iim+1+i)100 DO j=2,jj 101 DO i=1,ii 102 latfi((j-2)*ii+1+i)= rlatu(j) 103 lonfi((j-2)*ii+1+i)= rlonv(i) 104 cufi((j-2)*ii+1+i) = cu((j-1)*ii+1+i) 105 cvfi((j-2)*ii+1+i) = cv((j-1)*ii+1+i) 90 106 ENDDO 91 107 ENDDO 92 108 ! South pole 93 latfi(klon_glo)= rlatu(jj m+1)109 latfi(klon_glo)= rlatu(jj+1) 94 110 lonfi(klon_glo)= 0. 95 cufi(klon_glo) = cu((ii m+1)*jjm+1)96 cvfi(klon_glo) = cv((ii m+1)*jjm-iim)111 cufi(klon_glo) = cu((ii+1)*jj+1) 112 cvfi(klon_glo) = cv((ii+1)*jj-ii) 97 113 98 114 ! build airefi(), mesh area on physics grid 99 CALL gr_dyn_fi(1,ii m+1,jjm+1,klon_glo,aire,airefi)115 CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,aire,airefi) 100 116 ! Poles are single points on physics grid 101 airefi(1)=sum(aire(1:ii m,1))102 airefi(klon_glo)=sum(aire(1:ii m,jjm+1))117 airefi(1)=sum(aire(1:ii,1)) 118 airefi(klon_glo)=sum(aire(1:ii,jj+1)) 103 119 104 120 ! Sanity check: do total planet area match between physics and dynamics? 105 total_area_dyn=sum(aire(1:ii m,1:jjm+1))121 total_area_dyn=sum(aire(1:ii,1:jj+1)) 106 122 total_area_phy=sum(airefi(1:klon_glo)) 107 123 IF (total_area_dyn/=total_area_phy) THEN … … 126 142 !$OMP PARALLEL 127 143 ! Now generate local lon/lat/cu/cv/area arrays 128 CALL initcomgeomphy 144 CALL initcomgeomphy(klon_omp) 129 145 130 146 offset = klon_mpi_begin - 1 … … 135 151 rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end) 136 152 137 ! suphel => initialize some physical constants (orbital parameters, 138 ! geoid, gravity, thermodynamical constants, etc.) in the 139 ! physics 140 CALL suphel 153 ! copy over global grid longitudes and latitudes 154 CALL initcomgeomphy_horiz(iim,jjm,rlonu,rlonv,rlatu,rlatv) 155 156 ! copy over preff , ap(), bp(), etc 157 CALL initcomgeomphy_vert(nlayer,preff,ap,bp,presnivs,pseudoalt) 141 158 142 !$OMP END PARALLEL 159 ! ! suphel => initialize some physical constants (orbital parameters, 160 ! ! geoid, gravity, thermodynamical constants, etc.) in the 161 ! ! physics 162 ! CALL suphel 143 163 144 ! check that physical constants set in 'suphel' are coherent 145 ! with values set in the dynamics: 146 IF (rday/=punjours) THEN 147 WRITE (lunout, *) 'iniphysiq: length of day discrepancy!!!' 148 WRITE (lunout, *) ' in the dynamics punjours=', punjours 149 WRITE (lunout, *) ' but in the physics RDAY=', rday 150 IF (abs(rday-punjours)>0.01*punjours) THEN 151 ! stop here if the relative difference is more than 1% 152 abort_message = 'length of day discrepancy' 153 CALL abort_gcm(modname, abort_message, 1) 154 END IF 155 END IF 156 IF (rg/=pg) THEN 157 WRITE (lunout, *) 'iniphysiq: gravity discrepancy !!!' 158 WRITE (lunout, *) ' in the dynamics pg=', pg 159 WRITE (lunout, *) ' but in the physics RG=', rg 160 IF (abs(rg-pg)>0.01*pg) THEN 161 ! stop here if the relative difference is more than 1% 162 abort_message = 'gravity discrepancy' 163 CALL abort_gcm(modname, abort_message, 1) 164 END IF 165 END IF 166 IF (ra/=prad) THEN 167 WRITE (lunout, *) 'iniphysiq: planet radius discrepancy !!!' 168 WRITE (lunout, *) ' in the dynamics prad=', prad 169 WRITE (lunout, *) ' but in the physics RA=', ra 170 IF (abs(ra-prad)>0.01*prad) THEN 171 ! stop here if the relative difference is more than 1% 172 abort_message = 'planet radius discrepancy' 173 CALL abort_gcm(modname, abort_message, 1) 174 END IF 175 END IF 176 IF (rd/=pr) THEN 177 WRITE (lunout, *) 'iniphysiq: reduced gas constant discrepancy !!!' 178 WRITE (lunout, *) ' in the dynamics pr=', pr 179 WRITE (lunout, *) ' but in the physics RD=', rd 180 IF (abs(rd-pr)>0.01*pr) THEN 181 ! stop here if the relative difference is more than 1% 182 abort_message = 'reduced gas constant discrepancy' 183 CALL abort_gcm(modname, abort_message, 1) 184 END IF 185 END IF 186 IF (rcpd/=pcpp) THEN 187 WRITE (lunout, *) 'iniphysiq: specific heat discrepancy !!!' 188 WRITE (lunout, *) ' in the dynamics pcpp=', pcpp 189 WRITE (lunout, *) ' but in the physics RCPD=', rcpd 190 IF (abs(rcpd-pcpp)>0.01*pcpp) THEN 191 ! stop here if the relative difference is more than 1% 192 abort_message = 'specific heat discrepancy' 193 CALL abort_gcm(modname, abort_message, 1) 194 END IF 195 END IF 164 ! Initialize tracer names, numbers, etc. for physics 165 CALL ini_phytrac_phy(nqtot,nqo,nbtr,tname,ttext,type_trac,& 166 niadv,conv_flg,pbl_flg,solsym) 167 168 ! transfer some flags/infos from dynamics to physics 169 call inifis(punjours,prad,pg,pr,pcpp,ptimestep,& 170 day_step,iphysiq,dayref,anneeref,nday,& 171 annee_ref,day_ini,day_end,& 172 itau_phy,itaufin,& 173 start_time,day_ref,jD_ref, & 174 offline,raz_date,config_inca, & 175 lunout,prt_level,debug) 176 177 !!$OMP END PARALLEL 196 178 197 179 ! Additional initializations for aquaplanets 198 ! $OMP PARALLEL180 !!$OMP PARALLEL 199 181 IF (iflag_phys>=100) THEN 200 182 CALL iniaqua(klon_omp, rlatd, rlond, iflag_phys) -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/comconst_phy_mod.f90
r3814 r3816 1 1 MODULE comconst_phy_mod 2 2 3 REAL,PARAMETER :: pi=3.1415926535897932384626433832795 ! something like 3.14159.... 3 ! REAL,PARAMETER :: pi=3.1415926535897932384626433832795 ! something like 3.14159.... 4 ! => pi is in misc/nrtype 4 5 5 REAL, SAVE :: daysec !length (in s) of a standard day 6 ! $OMP THREADPRIVATE(daysec)6 ! REAL, SAVE :: daysec !length (in s) of a standard day => inifis_mod 7 !!$OMP THREADPRIVATE(daysec) 7 8 8 REAL, SAVE :: dtvr ! dynamical time step (in s) 9 !$OMP THREADPRIVATE(dtvr) 9 ! REAL, SAVE :: dtvr ! dynamical time step (in s) 10 ! => removed; was only used in phyaqua and could be replaced 11 !!$OMP THREADPRIVATE(dtvr) 10 12 11 13 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/comgeom2_phy_mod.f90
r3814 r3816 1 1 MODULE comgeom2_phy_mod 2 2 3 REAL,ALLOCATABLE,SAVE :: rlatu(:) 4 ! $OMP THREADPRIVATE(rlatu)3 ! REAL,ALLOCATABLE,SAVE :: rlatu(:) => comgeomphy 4 !!$OMP THREADPRIVATE(rlatu) 5 5 6 REAL,ALLOCATABLE,SAVE :: rlatv(:) 7 ! $OMP THREADPRIVATE(rlatv)6 ! REAL,ALLOCATABLE,SAVE :: rlatv(:) => comgeomphy 7 !!$OMP THREADPRIVATE(rlatv) 8 8 9 9 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/comgeomphy.F90
r3809 r3816 6 6 real,save,allocatable :: rlond(:) 7 7 !$OMP THREADPRIVATE(airephy,cuphy,cvphy,rlatd,rlond) 8 ! general (over global grid) latitudes and longitudes: 9 ! useful for outputs 10 real,save,allocatable :: rlonv(:) ! longitudes (rad) 11 real,save,allocatable :: rlonu(:) ! longitude boundaries (rad) 12 real,save,allocatable :: rlatu(:) ! latitudes (rad) 13 real,save,allocatable :: rlatv(:) ! latitude boundaries (rad) 14 !$OMP THREADPRIVATE(rlonv,rlonu,rlatu,rlatv) 15 16 ! vertical grid 17 real,save :: preff ! reference surface pressure (Pa) 18 real,save,allocatable :: ap(:) 19 real,save,allocatable :: bp(:) 20 real,save,allocatable :: presnivs(:) 21 real,save,allocatable :: pseudoalt(:) 22 !$OMP THREADPRIVATE(preff,ap,bp,presnivs,pseudoalt) 23 8 24 contains 9 25 10 subroutine InitComgeomphy 11 USE mod_phys_lmdz_para 12 implicit none 13 26 subroutine InitComgeomphy(klon_omp) 27 implicit none 28 integer,intent(in) :: klon_omp ! number of columns (on local omp grid) 14 29 15 30 allocate(airephy(klon_omp)) … … 21 36 end subroutine InitComgeomphy 22 37 38 subroutine initcomgeomphy_horiz(iim,jjm,rlonu_dyn,rlonv_dyn,& 39 rlatu_dyn,rlatv_dyn) 40 IMPLICIT NONE 41 integer,intent(in) :: iim 42 integer,intent(in) :: jjm 43 real,intent(in) :: rlonu_dyn(iim+1) ! dyn grid boundaries (rad) 44 real,intent(in) :: rlonv_dyn(iim+1) ! dyn grid longitudes (rad) 45 real,intent(in) :: rlatu_dyn(jjm+1) ! dyn grid latitudes (rad) 46 real,intent(in) :: rlatv_dyn(jjm) ! dyn grid boundaries (rad) 47 48 allocate(rlonu(iim+1)) 49 allocate(rlonv(iim+1)) 50 allocate(rlatu(jjm+1)) 51 allocate(rlatv(jjm)) 52 53 rlonu(:)=rlonu_dyn(:) 54 rlonv(:)=rlonv_dyn(:) 55 rlatu(:)=rlatu_dyn(:) 56 rlatv(:)=rlatv_dyn(:) 57 58 end subroutine initcomgeomphy_horiz 59 60 subroutine initcomgeomphy_vert(nlayer,preff_dyn,ap_dyn,bp_dyn,& 61 presnivs_dyn,pseudoalt_dyn) 62 IMPLICIT NONE 63 integer,intent(in) :: nlayer ! number of atmospheric layers 64 real,intent(in) :: preff_dyn ! reference surface pressure (Pa) 65 real,intent(in) :: ap_dyn(nlayer+1) ! hybrid coordinate at interfaces 66 real,intent(in) :: bp_dyn(nlayer+1) ! hybrid coordinate at interfaces 67 real,intent(in) :: presnivs_dyn(nlayer) ! Appproximative pressure of atm. layers (Pa) 68 real,intent(in) :: pseudoalt_dyn(nlayer) ! pseudo-altitude of atm. layers (km) 69 70 allocate(ap(nlayer+1)) 71 allocate(bp(nlayer+1)) 72 allocate(presnivs(nlayer)) 73 allocate(pseudoalt(nlayer)) 74 75 preff=preff_dyn 76 ap(:)=ap_dyn(:) 77 bp(:)=bp_dyn(:) 78 presnivs(:)=presnivs_dyn(:) 79 pseudoalt(:)=pseudoalt_dyn(:) 80 81 end subroutine initcomgeomphy_vert 82 23 83 end module comgeomphy -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/comvert_phy_mod.f90
r3814 r3816 1 1 MODULE comvert_phy_mod 2 2 3 REAL,ALLOCATABLE,SAVE :: ap(:) ! hybrid pressure contribution at interlayers 4 !$OMP THREADPRIVATE(ap) 5 REAL,ALLOCATABLE,SAVE :: bp(:) ! hybrid sigma contribution at interlayer 6 !$OMP THREADPRIVATE(bp) 7 REAL,ALLOCATABLE,SAVE :: presnivs(:) ! (reference) pressure at mid-layers 8 !$OMP THREADPRIVATE(presnivs) 9 REAL,SAVE :: preff ! reference surface pressure (Pa) 10 !$OMP THREADPRIVATE(preff) 11 3 ! REAL,ALLOCATABLE,SAVE :: ap(:) ! hybrid pressure contribution at interlayers 4 !!$OMP THREADPRIVATE(ap) 5 ! REAL,ALLOCATABLE,SAVE :: bp(:) ! hybrid sigma contribution at interlayer 6 !!$OMP THREADPRIVATE(bp) 7 ! REAL,ALLOCATABLE,SAVE :: presnivs(:) ! (reference) pressure at mid-layers 8 !!$OMP THREADPRIVATE(presnivs) 9 ! REAL,SAVE :: preff ! reference surface pressure (Pa) 10 !!$OMP THREADPRIVATE(preff) 12 11 12 !!! => all moved to comgeomphy 13 13 14 14 END MODULE comvert_phy_mod -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/condsurf.F90
r3814 r3816 6 6 USE mod_phys_lmdz_para 7 7 USE indice_sol_mod 8 USE temps_phy_mod 8 !USE temps_phy_mod 9 USE inifis_mod, ONLY: annee_ref 9 10 IMPLICIT NONE 10 11 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/conf_phys_m.F90
r3814 r3816 27 27 USE phys_cal_mod 28 28 USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl 29 USE control_phy_mod29 !USE control_phy_mod 30 30 USE mod_grid_phy_lmdz, only: klon_glo 31 31 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/control_phy_mod.f90
r3814 r3816 1 1 MODULE control_phy_mod 2 2 3 INTEGER,SAVE :: iphysiq ! call physics every iphysiq dynamical steps3 !INTEGER,SAVE :: iphysiq ! call physics every iphysiq dynamical steps 4 4 !$OMP THREADPRIVATE(iphysiq) 5 ! => ifinis_mod 5 6 6 INTEGER,SAVE :: day_step ! # of dynamical time steps per day7 !INTEGER,SAVE :: day_step ! # of dynamical time steps per day 7 8 !$OMP THREADPRIVATE(day_step) 9 ! => inifis_mod 8 10 9 INTEGER,SAVE :: nday ! # of days to run11 !INTEGER,SAVE :: nday ! # of days to run 10 12 !$OMP THREADPRIVATE(nday) 13 ! => inifis_mod 11 14 12 INTEGER,SAVE :: dayref15 !INTEGER,SAVE :: dayref 13 16 !$OMP THREADPRIVATE(dayref) 17 ! => inifis_mod 14 18 15 CHARACTER(len=4),SAVE :: config_inca19 !CHARACTER(len=4),SAVE :: config_inca 16 20 !$OMP THREADPRIVATE(config_inca) 21 ! => inifis_mod 17 22 18 INTEGER,SAVE :: raz_date23 !INTEGER,SAVE :: raz_date 19 24 !$OMP THREADPRIVATE(raz_date) 25 ! => inifis_mod 20 26 21 LOGICAL,SAVE :: offline27 !LOGICAL,SAVE :: offline 22 28 !$OMP THREADPRIVATE(offline) 29 ! => inifis_mod 23 30 24 31 END MODULE control_phy_mod -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cpl_mod.F90
r3814 r3816 24 24 USE oasis 25 25 USE write_field_phy 26 USE control_phy_mod 26 !USE control_phy_mod 27 USE inifis_mod, ONLY: day_step, iphysiq 27 28 28 29 … … 102 103 USE surface_data 103 104 USE indice_sol_mod 104 USE temps_phy_mod 105 ! USE temps_phy_mod 106 USE inifis_mod, ONLY: annee_ref, day_ini, itau_phy, itaufin 105 107 INCLUDE "dimensions.h" 106 108 INCLUDE "iniprint.h" … … 296 298 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl 297 299 USE indice_sol_mod 298 USE temps_phy_mod 299 300 INCLUDE "iniprint.h" 300 ! USE temps_phy_mod 301 USE inifis_mod, ONLY: start_time, itau_phy 302 303 ! INCLUDE "iniprint.h" 301 304 INCLUDE "YOMCST.h" 302 305 INCLUDE "dimensions.h" … … 1027 1030 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl 1028 1031 USE indice_sol_mod 1029 USE temps_phy_mod 1032 ! USE temps_phy_mod 1033 USE inifis_mod, ONLY: start_time, itau_phy 1030 1034 1031 1035 ! Some includes -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/infotrac_phy.f90
r3814 r3816 42 42 CONTAINS 43 43 44 SUBROUTINE init_infotrac_phy(nbtr_,tname_,ttext_,niadv_) 44 SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,tname_,ttext_,type_trac_,& 45 niadv_,conv_flg_,pbl_flg_,solsym_) 45 46 IMPLICIT NONE 46 INTEGER :: nbtr_ 47 CHARACTER(len=20), DIMENSION(:) :: tname_ ! tracer short name for restart and diagnostics 48 CHARACTER(len=23), DIMENSION(:) :: ttext_ ! tracer long name for diagnostics 49 INTEGER, DIMENSION(:) :: niadv_ ! equivalent dyn / physique 50 47 INTEGER,INTENT(IN) :: nqtot_ 48 INTEGER,INTENT(IN) :: nqo_ 49 INTEGER,INTENT(IN) :: nbtr_ 50 CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics 51 CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics 52 CHARACTER(len=4),INTENT(IN) :: type_trac_(nqtot_) 53 INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique 54 INTEGER,INTENT(IN) :: conv_flg_(nbtr_) 55 INTEGER,INTENT(IN) :: pbl_flg_(nbtr_) 56 CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_) 57 58 nqtot=nqtot_ 59 nqo=nqo_ 51 60 nbtr=nbtr_ 52 ALLOCATE(tname( size(tname_)))53 ALLOCATE(ttext( size(ttext_)))54 ALLOCATE(niadv( size(niadv_)))61 ALLOCATE(tname(nqtot)) 62 ALLOCATE(ttext(nqtot)) 63 ALLOCATE(niadv(nqtot)) 55 64 tname(:) = tname_(:) 56 65 ttext(:) = ttext_(:) 57 66 niadv(:) = niadv_(:) 67 ALLOCATE(niadv(nqtot)) 68 niadv(:)=niadv_(:) 69 ALLOCATE(conv_flg(nbtr)) 70 conv_flg(:)=conv_flg_(:) 71 ALLOCATE(pbl_flg(nbtr)) 72 pbl_flg(:)=pbl_flg_(:) 73 ALLOCATE(solsym(nbtr)) 74 solsym(:)=solsym_(:) 58 75 59 76 END SUBROUTINE init_infotrac_phy -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/inifis_mod.F90
r3814 r3816 1 1 2 ! $Id: inifis.F90 1992 2014-03-05 13:19:12Z lguez $ 2 ! $Id: $ 3 MODULE inifis_mod 3 4 4 SUBROUTINE inifis(ngrid, nlayer, punjours, pdayref, ptimestep, plat, plon, & 5 parea, prad, pg, pr, pcpp) 6 USE dimphy 5 IMPLICIT NONE 6 ! for now constants and flags transmitted from dyn to phys are stored here 7 REAL,SAVE :: daysec ! length of reference day (s) 8 REAL,SAVE :: dtphys ! physics time step (s) 9 INTEGER,SAVE :: day_step ! number of dynamical steps per day 10 INTEGER,SAVE :: iphysiq ! physics called every iphysiq dynamical step 11 INTEGER,SAVE :: dayref 12 INTEGER,SAVE :: anneeref ! reference year, ase deifined in run.def 13 INTEGER,SAVE :: nday ! number of days to run 14 !$THREADPRIVATE(daysec,dtphys,day_step,iphysiq,dayref,anneeref,nday) 15 INTEGER,SAVE :: annee_ref ! reference year as read from start file 16 INTEGER,SAVE :: day_ini 17 INTEGER,SAVE :: day_end 18 !$THREADPRIVATE(annee_ref,day_ini,day_end) 19 INTEGER,SAVE :: itau_phy 20 INTEGER,SAVE :: itaufin 21 REAL,SAVE :: start_time 22 INTEGER,SAVE :: day_ref 23 REAL,SAVE :: jD_ref 24 !$THREADPRIVATE(itau_phy,itaufin,start_time,day_ref,JD_ref) 25 LOGICAL,SAVE :: offline 26 INTEGER,SAVE :: raz_date 27 CHARACTER(len=4),SAVE :: config_inca 28 INTEGER,SAVE :: lunout ! default output file identifier (6==screen) 29 INTEGER,SAVE :: prt_level ! Output level 30 LOGICAL,SAVE :: debug ! flag to specify if in "debug mode" 31 !$THREADPRIVATE(offline,raz_date,config_inca,lunout,prt_level,debug) 32 33 CONTAINS 34 35 SUBROUTINE inifis(punjours,prad,pg,pr,pcpp,ptimestep,& 36 day_step_dyn,iphysiq_dyn,& 37 dayref_dyn,anneeref_dyn,nday_dyn,& 38 annee_ref_dyn,day_ini_dyn,day_end_dyn,& 39 itau_phy_dyn,itaufin_dyn,& 40 start_time_dyn,day_ref_dyn,jD_ref_dyn,& 41 offline_dyn,raz_date_dyn,config_inca_dyn, & 42 lunout_dyn,prt_level_dyn,debug_dyn) 43 ! Initialize physics constant and flags from dynamics 7 44 IMPLICIT NONE 8 45 9 ! ======================================================================= 10 11 ! subject: 12 ! -------- 13 14 ! Initialisation for the physical parametrisations of the LMD 15 ! martian atmospheric general circulation modele. 16 17 ! author: Frederic Hourdin 15 / 10 /93 18 ! ------- 19 20 ! arguments: 21 ! ---------- 22 23 ! input: 24 ! ------ 25 26 ! ngrid Size of the horizontal grid. 27 ! All internal loops are performed on that grid. 28 ! nlayer Number of vertical layers. 29 ! pdayref Day of reference for the simulation 30 ! firstcall True at the first call 31 ! lastcall True at the last call 32 ! pday Number of days counted from the North. Spring 33 ! equinoxe. 34 35 ! ======================================================================= 36 37 ! ----------------------------------------------------------------------- 38 ! declarations: 39 ! ------------- 40 41 ! ym#include "dimensions.h" 42 ! ym#include "dimphy.h" 43 44 include 'iniprint.h' 45 REAL prad, pg, pr, pcpp, punjours 46 47 INTEGER ngrid, nlayer 48 REAL plat(ngrid), plon(ngrid), parea(klon) 49 INTEGER pdayref 50 51 REAL ptimestep 46 include "YOMCST.h" 47 ! include 'iniprint.h' 48 REAL,INTENT(IN) :: punjours,prad, pg, pr, pcpp 49 REAL,INTENT(IN) :: ptimestep ! physics time step (s) 50 INTEGER,INTENT(IN) :: day_step_dyn 51 INTEGER,INTENT(IN) :: iphysiq_dyn 52 INTEGER,INTENT(IN) :: dayref_dyn 53 INTEGER,INTENT(IN) :: anneeref_dyn 54 INTEGER,INTENT(IN) :: nday_dyn 55 INTEGER,INTENT(IN) :: annee_ref_dyn 56 INTEGER,INTENT(IN) :: day_ini_dyn 57 INTEGER,INTENT(IN) :: day_end_dyn 58 INTEGER,INTENT(IN) :: itau_phy_dyn 59 INTEGER,INTENT(IN) :: itaufin_dyn 60 REAL,INTENT(IN) :: start_time_dyn 61 INTEGER,INTENT(IN) :: day_ref_dyn 62 REAL,INTENT(IN) :: jD_ref_dyn 63 LOGICAL,INTENT(IN) :: offline_dyn 64 INTEGER,INTENT(IN) :: raz_date_dyn 65 CHARACTER(len=4),INTENT(IN) :: config_inca_dyn 66 INTEGER,INTENT(IN) :: lunout_dyn 67 INTEGER,INTENT(IN) :: prt_level_dyn 68 LOGICAL,INTENT(IN) :: debug_dyn 52 69 CHARACTER (LEN=20) :: modname = 'inifis' 53 70 CHARACTER (LEN=80) :: abort_message 54 71 72 ! Some general settings and associated flags 73 daysec=punjours 74 dtphys=ptimestep 75 day_step=day_step_dyn 76 iphysiq=iphysiq_dyn 77 dayref=dayref_dyn 78 anneeref=anneeref_dyn 79 nday=nday_dyn 80 annee_ref=annee_ref_dyn 81 day_ini=day_ini_dyn 82 day_end=day_end_dyn 83 itau_phy=itau_phy_dyn 84 itaufin=itaufin_dyn 85 start_time=start_time_dyn 86 day_ref=day_ref_dyn 87 jD_ref= jD_ref_dyn 88 offline=offline_dyn 89 raz_date=raz_date_dyn 90 config_inca=config_inca_dyn 91 lunout=lunout_dyn 92 prt_level=prt_level_dyn 93 debug=debug_dyn 55 94 56 IF (nlayer/=klev) THEN 57 PRINT *, 'STOP in inifis' 58 PRINT *, 'Probleme de dimensions :' 59 PRINT *, 'nlayer = ', nlayer 60 PRINT *, 'klev = ', klev 61 abort_message = '' 62 CALL abort_physic(modname, abort_message, 1) 95 ! suphel => initialize some physical constants (orbital parameters, 96 ! geoid, gravity, thermodynamical constants, etc.) in the 97 ! physics 98 CALL suphel 99 100 ! check that physical constants set in 'suphel' are coherent 101 ! with values set in the dynamics: 102 IF (rday/=punjours) THEN 103 WRITE (lunout, *) 'inifis: length of day discrepancy!!!' 104 WRITE (lunout, *) ' in the dynamics punjours=', punjours 105 WRITE (lunout, *) ' but in the physics RDAY=', rday 106 IF (abs(rday-punjours)>0.01*punjours) THEN 107 ! stop here if the relative difference is more than 1% 108 abort_message = 'length of day discrepancy' 109 CALL abort_physic(modname, abort_message, 1) 110 END IF 111 END IF 112 IF (rg/=pg) THEN 113 WRITE (lunout, *) 'inifis: gravity discrepancy !!!' 114 WRITE (lunout, *) ' in the dynamics pg=', pg 115 WRITE (lunout, *) ' but in the physics RG=', rg 116 IF (abs(rg-pg)>0.01*pg) THEN 117 ! stop here if the relative difference is more than 1% 118 abort_message = 'gravity discrepancy' 119 CALL abort_physic(modname, abort_message, 1) 120 END IF 121 END IF 122 IF (ra/=prad) THEN 123 WRITE (lunout, *) 'inifis: planet radius discrepancy !!!' 124 WRITE (lunout, *) ' in the dynamics prad=', prad 125 WRITE (lunout, *) ' but in the physics RA=', ra 126 IF (abs(ra-prad)>0.01*prad) THEN 127 ! stop here if the relative difference is more than 1% 128 abort_message = 'planet radius discrepancy' 129 CALL abort_physic(modname, abort_message, 1) 130 END IF 131 END IF 132 IF (rd/=pr) THEN 133 WRITE (lunout, *) 'inifis: reduced gas constant discrepancy !!!' 134 WRITE (lunout, *) ' in the dynamics pr=', pr 135 WRITE (lunout, *) ' but in the physics RD=', rd 136 IF (abs(rd-pr)>0.01*pr) THEN 137 ! stop here if the relative difference is more than 1% 138 abort_message = 'reduced gas constant discrepancy' 139 CALL abort_physic(modname, abort_message, 1) 140 END IF 141 END IF 142 IF (rcpd/=pcpp) THEN 143 WRITE (lunout, *) 'inifis: specific heat discrepancy !!!' 144 WRITE (lunout, *) ' in the dynamics pcpp=', pcpp 145 WRITE (lunout, *) ' but in the physics RCPD=', rcpd 146 IF (abs(rcpd-pcpp)>0.01*pcpp) THEN 147 ! stop here if the relative difference is more than 1% 148 abort_message = 'specific heat discrepancy' 149 CALL abort_physic(modname, abort_message, 1) 150 END IF 63 151 END IF 64 152 65 IF (ngrid/=klon) THEN 66 PRINT *, 'STOP in inifis' 67 PRINT *, 'Probleme de dimensions :' 68 PRINT *, 'ngrid = ', ngrid 69 PRINT *, 'klon = ', klon 70 abort_message = '' 71 CALL abort_physic(modname, abort_message, 1) 72 END IF 153 END SUBROUTINE inifis 73 154 74 RETURN 75 abort_message = 'Cette version demande les fichier rnatur.dat & 76 & & 77 & et surf.def' 78 CALL abort_physic(modname, abort_message, 1) 79 80 END SUBROUTINE inifis 155 END MODULE inifis_mod -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/initphysto.F90
r3814 r3816 8 8 USE IOIPSL 9 9 USE iophy 10 USE control_phy_mod10 !USE control_phy_mod 11 11 USE indice_sol_mod 12 USE comconst_phy_mod 13 USE temps_phy_mod 12 !USE comconst_phy_mod 13 !USE temps_phy_mod 14 USE inifis_mod, ONLY: day_ref, annee_ref 15 14 16 IMPLICIT NONE 15 17 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/iophy.F90
r3814 r3816 451 451 use phys_output_var_mod, only: type_ecri, zoutm, zdtime_moy, lev_files, & 452 452 nid_files, nhorim, swaero_diag, nfiles 453 USE temps_phy_mod454 453 IMPLICIT NONE 455 454 INCLUDE "dimensions.h" … … 506 505 nhorim, zdtime_moy, levmin, levmax, & 507 506 nvertm, nfiles 508 USE temps_phy_mod509 507 IMPLICIT NONE 510 508 … … 565 563 use wxios, only: wxios_add_field_to_file 566 564 #endif 567 USE temps_phy_mod568 565 IMPLICIT NONE 569 566 … … 652 649 use wxios, only: wxios_add_field_to_file 653 650 #endif 654 USE temps_phy_mod655 651 IMPLICIT NONE 656 652 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/o3_chem_m.F90
r3814 r3816 20 20 use dimphy, only: klon 21 21 use regr_pr_comb_coefoz_m, only: c_Mob, a4_mass, a2, r_het_interm 22 use comconst_phy_mod 22 ! use comconst_phy_mod 23 use nrtype, only: pi 23 24 24 25 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/pbl_surface_mod.F90
r3814 r3816 23 23 USE climb_wind_mod, ONLY : climb_wind_down, climb_wind_up 24 24 USE coef_diff_turb_mod, ONLY : coef_diff_turb 25 USE control_phy_mod25 ! USE control_phy_mod 26 26 27 27 … … 261 261 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send 262 262 USE indice_sol_mod 263 USE temps_phy_mod 263 ! USE temps_phy_mod 264 USE inifis_mod, ONLY: annee_ref, day_ini, itau_phy 264 265 IMPLICIT NONE 265 266 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyaqua_mod.F90
r3814 r3816 25 25 USE fonte_neige_mod, ONLY: fonte_neige_init 26 26 USE phys_state_var_mod 27 USE control_phy_mod, ONLY: dayref, nday, iphysiq 27 !USE control_phy_mod, ONLY: dayref, nday, iphysiq 28 USE inifis_mod, ONLY: dayref, nday, iphysiq, dtphys, & 29 daysec, day_ini,day_end 28 30 USE indice_sol_mod 29 USE temps_phy_mod 30 USE comconst_phy_mod 31 !USE temps_phy_mod 32 !USE comconst_phy_mod 33 USE nrtype, ONLY: pi 31 34 USE ioipsl 32 35 IMPLICIT NONE … … 277 280 ! Ecriture etat initial physique 278 281 279 timestep = dt vr*float(iphysiq)282 timestep = dtphys 280 283 radpas = nint(daysec/timestep/float(nbapp_rad)) 281 284 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyetat0.F90
r3814 r3816 26 26 USE indice_sol_mod, only: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic 27 27 USE ocean_slab_mod, ONLY: tslab, seaice, tice, ocean_slab_init 28 USE temps_phy_mod 28 !USE temps_phy_mod 29 USE inifis_mod, ONLY: itau_phy 29 30 30 31 IMPLICIT none -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyredem.F90
r3814 r3816 12 12 USE traclmdz_mod, ONLY : traclmdz_to_restart 13 13 USE infotrac_phy 14 USE control_phy_mod14 !USE control_phy_mod 15 15 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send 16 16 USE indice_sol_mod 17 17 USE surface_data 18 18 USE ocean_slab_mod, ONLY : tslab, seaice, tice, fsic 19 USE temps_phy_mod 19 !USE temps_phy_mod 20 USE inifis_mod, ONLY: annee_ref, day_end, itau_phy 20 21 21 22 IMPLICIT none -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_mod.F90
r3814 r3816 45 45 USE phys_output_ctrlout_mod 46 46 USE mod_grid_phy_lmdz, only: klon_glo 47 USE temps_phy_mod 48 Use comvert_phy_mod 47 !USE temps_phy_mod 48 USE comgeomphy, ONLY: ap,bp,presnivs,preff 49 !Use comvert_phy_mod 50 USE inifis_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref 49 51 #ifdef CPP_XIOS 50 52 ! ug Pour les sorties XIOS … … 522 524 use ioipsl 523 525 USE phys_cal_mod 524 USE comconst_phy_mod 525 USE temps_phy_mod 526 !USE comconst_phy_mod 527 !USE temps_phy_mod 528 USE inifis_mod, ONLY: day_ref, annee_ref 526 529 IMPLICIT NONE 527 530 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_write_mod.F90
r3814 r3816 25 25 26 26 USE dimphy, only: klon, klev, klevp1, nslay 27 USE control_phy_mod, only: day_step, iphysiq 27 !USE control_phy_mod, only: day_step, iphysiq 28 USE inifis_mod, only: day_step, iphysiq 28 29 USE phys_output_ctrlout_mod, only: o_phis, o_aire, is_ter, is_lic, is_oce, & 29 30 is_ave, is_sic, o_contfracATM, o_contfracOR, & … … 247 248 #endif 248 249 USE phys_cal_mod, only : mth_len 249 USE temps_phy_mod 250 !USE temps_phy_mod 251 USE inifis_mod, ONLY: start_time, itau_phy 250 252 251 253 IMPLICIT NONE -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_state_var_mod.F90
r3814 r3816 404 404 !USE control_mod 405 405 USE aero_mod 406 USE infotrac_phy, ONLY : nbtr 406 !USE infotrac_phy, ONLY : nbtr 407 USE phytrac_mod, ONLY: nbtr 407 408 USE indice_sol_mod 408 409 IMPLICIT NONE -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/physiq.F90
r3814 r3816 12 12 USE ioipsl, only: histbeg, histvert, histdef, histend, histsync, & 13 13 histwrite, ju2ymds, ymds2ju, getin 14 USE comgeomphy 14 USE comgeomphy, ONLY: airephy 15 15 USE phys_cal_mod, only: year_len, mth_len, days_elapsed, jh_1jan, year_cur, & 16 16 mth_cur, phys_cal_update … … 46 46 use radlwsw_m, only: radlwsw 47 47 use phyaqua_mod, only: zenang_an 48 USE control_phy_mod 49 USE temps_phy_mod 48 !USE control_phy_mod 49 !USE temps_phy_mod 50 USE inifis_mod, only: config_inca,day_step,iphysiq,offline,raz_date, & 51 annee_ref, day_ref, itau_phy, jD_ref, start_time 50 52 #ifdef REPROBUS 51 53 USE CHEM_REP, ONLY : Init_chem_rep_xjour -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phystokenc.F90
r3814 r3816 11 11 USE infotrac_phy, ONLY : nqtot 12 12 USE iophy 13 USE control_phy_mod14 13 USE indice_sol_mod 15 14 USE tracstoke_phy_mod -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phytrac_mod.F90
r3814 r3816 20 20 !================================================================================= 21 21 22 23 IMPLICIT NONE 24 ! tracer settings, inherited from the dynamics (see ini_trac_mod) 25 ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included 26 INTEGER, SAVE :: nqtot 27 ! nqo: numbre of water tracers 28 INTEGER, SAVE :: nqo 29 ! nbtr : number of tracers not including higher order of moment or water vapor or liquid 30 ! number of tracers used in the physics 31 INTEGER, SAVE :: nbtr 32 !$OMP THREADRIVATE(nqtot,nqo,nbtr) 33 ! Name variables 34 CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics 35 CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics 36 ! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the 37 ! dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code. 38 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: niadv ! equivalent dyn / physique 39 !$OMP THREADRIVATE(tname,ttext,niadv) 40 ! conv_flg(it)=0 : convection desactivated for tracer number it 41 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: conv_flg 42 ! pbl_flg(it)=0 : boundary layer diffusion desactivaded for tracer number it 43 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: pbl_flg 44 CHARACTER(len=4),SAVE :: type_trac 45 CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym 46 !$OMP THREADRIVATE(conv_flg,pbl_flg,type_trac,solsym) 22 47 ! 23 48 ! Tracer tendencies, for outputs … … 54 79 CONTAINS 55 80 81 SUBROUTINE ini_phytrac_mod(nqtot_dyn,nqo_dyn,nbtr_dyn, & 82 tname_dyn,ttext_dyn,type_trac_dyn, & 83 niadv_dyn,conv_flg_dyn,pbl_flg_dyn,solsym_dyn) 84 IMPLICIT NONE 85 86 INTEGER,INTENT(IN) :: nqtot_dyn 87 INTEGER,INTENT(IN) :: nqo_dyn 88 INTEGER,INTENT(IN) :: nbtr_dyn 89 CHARACTER(len=*),INTENT(IN) :: tname_dyn(nqtot_dyn) 90 CHARACTER(len=*),INTENT(IN) :: ttext_dyn(nqtot_dyn) 91 CHARACTER(len=*),INTENT(IN) :: type_trac_dyn 92 INTEGER,INTENT(IN) :: niadv_dyn(nqtot_dyn) 93 INTEGER,INTENT(IN) :: conv_flg_dyn(nbtr_dyn) 94 INTEGER,INTENT(IN) :: pbl_flg_dyn(nbtr_dyn) 95 CHARACTER(len=*),INTENT(IN) :: solsym_dyn(nbtr_dyn) 96 97 INTEGER :: i 98 99 nqtot=nqtot_dyn 100 nqo=nqo_dyn 101 nbtr=nbtr_dyn 102 type_trac=type_trac_dyn 103 104 allocate(tname(nqtot)) 105 allocate(ttext(nqtot)) 106 allocate(niadv(nqtot)) 107 allocate(conv_flg(nbtr)) 108 allocate(pbl_flg(nbtr)) 109 allocate(solsym(nbtr)) 110 111 DO i=1,nqtot_dyn 112 tname(i)=tname_dyn(i) 113 ttext(i)=ttext_dyn(i) 114 niadv(i)=niadv_dyn(i) 115 ENDDO 116 DO i=1,nbtr_dyn 117 conv_flg(i)=conv_flg_dyn(i) 118 pbl_flg(i)=pbl_flg_dyn(i) 119 solsym(i)=solsym_dyn(i) 120 ENDDO 121 122 END SUBROUTINE ini_phytrac_mod 123 56 124 SUBROUTINE phytrac( & 57 125 nstep, julien, gmtime, debutphy, & … … 89 157 USE phys_cal_mod, only : hour 90 158 USE dimphy 91 USE infotrac_phy159 !USE infotrac_phy 92 160 USE mod_grid_phy_lmdz 93 161 USE mod_phys_lmdz_para 94 USE comgeomphy95 162 USE iophy 96 163 USE traclmdz_mod 97 164 USE tracinca_mod 98 165 USE tracreprobus_mod 99 USE control_phy_mod 166 !USE control_phy_mod 167 USE inifis_mod, ONLY: config_inca 168 100 169 USE indice_sol_mod 101 170 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosol.F90
r3814 r3816 333 333 ! IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN 334 334 IF (nbr_tsteps /= 12 ) THEN 335 CALL abort_physic('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)',1) 335 CALL abort_physic('get_aero_fromfile', & 336 'not the right number of months in aerosol file read (should be 12 for the moment)',1) 336 337 ENDIF 337 338 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_climoz_m.F90
r3814 r3816 73 73 use netcdf, only: nf90_get_att, nf90_get_var, nf90_noerr, nf90_nowrite 74 74 use assert_m, only: assert 75 use comconst_phy_mod, only : pi 76 use comgeom2_phy_mod, only : rlatv 75 !use comconst_phy_mod, only : pi 76 !use comgeom2_phy_mod, only : rlatv 77 use comgeomphy, only: rlatv 78 use nrtype, only: pi 77 79 integer, intent(in):: read_climoz ! read ozone climatology 78 80 ! Allowed values are 1 and 2 … … 334 336 nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var 335 337 use netcdf, only: nf90_clobber, nf90_float, nf90_global 336 use comconst_phy_mod, only : pi 337 use comgeom2_phy_mod, only : rlatu 338 !use comconst_phy_mod, only : pi 339 !use comgeom2_phy_mod, only : rlatu 340 use nrtype, only: pi 341 use comgeomphy, only: rlatu 338 342 integer, intent(in):: ncid_in, n_plev 339 343 integer, intent(out):: ncid_out, varid_plev, varid_time -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_coefoz_m.F90
r3814 r3816 45 45 nf95_put_var, nf95_gw_var 46 46 use netcdf, only: nf90_nowrite, nf90_get_var 47 use comgeom2_phy_mod, only : rlatv 48 use comconst_phy_mod, only : pi 47 !use comgeom2_phy_mod, only : rlatv 48 !use comconst_phy_mod, only : pi 49 use nrtype, only: pi 50 use comgeomphy, only: rlatv 49 51 ! Variables local to the procedure: 50 52 … … 247 249 nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var 248 250 use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global 249 use comgeom2_phy_mod, only : rlatu 250 use comconst_phy_mod, only : pi 251 !use comgeom2_phy_mod, only : rlatu 252 !use comconst_phy_mod, only : pi 253 use nrtype, only: pi 254 use comgeomphy, only: rlatu 251 255 252 256 integer, intent(in):: ncid_in, varid_in(:), n_plev -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_o3_m.F90
r3814 r3816 30 30 use regr1_step_av_m, only: regr1_step_av 31 31 use press_coefoz_m, only: press_in_edg 32 use control_phy_mod, only: dayref 32 !use control_phy_mod, only: dayref 33 use inifis_mod, only: dayref 33 34 34 35 REAL, intent(in):: p3d(:, :, :) ! pressure at layer interfaces, in Pa -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/surf_land_orchidee_mod.F90
r3814 r3816 45 45 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl 46 46 USE indice_sol_mod 47 USE temps_phy_mod 47 48 48 ! 49 49 ! Cette routine sert d'interface entre le modele atmospherique et le -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/temps_phy_mod.f90
r3814 r3816 1 1 MODULE temps_phy_mod 2 2 3 INTEGER,SAVE :: itaufin4 ! $OMP THREADPRIVATE(itaufin)3 !INTEGER,SAVE :: itaufin => inifis_mod 4 !!$OMP THREADPRIVATE(itaufin) 5 5 6 INTEGER,SAVE :: day_ini7 ! $OMP THREADPRIVATE(day_ini)6 !INTEGER,SAVE :: day_ini => inifis_mod 7 !!$OMP THREADPRIVATE(day_ini) 8 8 9 INTEGER,SAVE :: day_end10 ! $OMP THREADPRIVATE(day_end)9 !INTEGER,SAVE :: day_end => inifis_mod 10 !!$OMP THREADPRIVATE(day_end) 11 11 12 INTEGER,SAVE :: itau_phy13 ! $OMP THREADPRIVATE(itau_phy)12 !INTEGER,SAVE :: itau_phy => inifis_mod 13 !!$OMP THREADPRIVATE(itau_phy) 14 14 15 INTEGER,SAVE :: annee_ref16 ! $OMP THREADPRIVATE(annee_ref)15 !INTEGER,SAVE :: annee_ref 16 !!$OMP THREADPRIVATE(annee_ref) 17 17 18 INTEGER,SAVE :: day_ref19 ! $OMP THREADPRIVATE(day_ref)18 !INTEGER,SAVE :: day_ref 19 !!$OMP THREADPRIVATE(day_ref) 20 20 21 REAL,SAVE :: start_time22 ! $OMP THREADPRIVATE(start_time)21 !REAL,SAVE :: start_time 22 !!$OMP THREADPRIVATE(start_time) 23 23 24 REAL,SAVE :: jD_ref25 ! $OMP THREADPRIVATE(jD_ref)24 !REAL,SAVE :: jD_ref 25 !!$OMP THREADPRIVATE(jD_ref) 26 26 27 27 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/tracinca_mod.F90
r3814 r3816 45 45 USE vampir 46 46 USE comgeomphy 47 USE control_phy_mod 47 !USE control_phy_mod 48 USE inifis_mod, ONLY: config_inca 48 49 USE indice_sol_mod 49 50 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/traclmdz_mod.F90
r3814 r3816 430 430 !================================================================= 431 431 432 CALL q_sat _phy(klon*klev,t_seri,pplay,qsat)432 CALL q_sat(klon*klev,t_seri,pplay,qsat) 433 433 434 434 IF ( id_pcsat /= 0 ) THEN
Note: See TracChangeset
for help on using the changeset viewer.