Changeset 4223 for dynamico_lmdz
- Timestamp:
- Jan 10, 2020, 12:09:43 AM (5 years ago)
- Location:
- dynamico_lmdz/simple_physics/phyparam
- Files:
-
- 2 added
- 3 edited
- 5 moved
Legend:
- Unmodified
- Added
- Removed
-
dynamico_lmdz/simple_physics/phyparam/dynphy_lonlat/iniphysiq_mod.F90
r4222 r4223 21 21 USE phyaqua_mod, ONLY: iniaqua 22 22 USE nrtype, ONLY: pi 23 23 ! USE vertical_layers_mod, ONLY : presnivs 24 24 25 ! 25 26 !======================================================================= … … 81 82 CALL iniaqua(klon_omp,iflag_phys) 82 83 ENDIF 84 ! 85 ! call iophys_ini('phys.nc ',presnivs) 83 86 84 87 CALL setup_phyparam -
dynamico_lmdz/simple_physics/phyparam/dynphy_lonlat/iophys.F90
r4196 r4223 1 MODULE iophys 2 IMPLICIT NONE 3 PRIVATE 4 5 PUBLIC :: iophys_ini 6 7 CONTAINS 8 1 9 subroutine iophys_ecrit(nom,lllm,titre,unite,px) 2 10 USE dimphy … … 67 75 68 76 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 77 78 SUBROUTINE writefield1(name, longname, unit, var) 79 CHARACTER(*), INTENT(IN) :: name, longname, unit 80 REAL, INTENT(IN) :: var(:) 81 CALL iophys_ecrit(name, 1, longname, unit, var) 82 END SUBROUTINE writefield1 83 84 SUBROUTINE writefield2(name, longname, unit, var) 85 CHARACTER(*), INTENT(IN) :: name, longname, unit 86 REAL, INTENT(IN) :: var(:,:) 87 PRINT *, 'writefield2', name, SHAPE(var) 88 CALL iophys_ecrit(name, SIZE(var,2), longname, unit, var) 89 END SUBROUTINE writefield2 90 91 92 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 69 93 SUBROUTINE iophys_ini(fichnom,presnivs) 70 94 USE mod_phys_lmdz_para 71 95 USE writefield_mod 72 96 IMPLICIT NONE 73 97 … … 100 124 ! ---------- 101 125 126 writefield1_plugin => writefield1 127 writefield2_plugin => writefield2 128 102 129 !$OMP MASTER 103 130 IF (is_mpi_root) THEN … … 109 136 110 137 END 138 139 END MODULE -
dynamico_lmdz/simple_physics/phyparam/dynphy_lonlat/physiq_mod.F90
r4214 r4223 28 28 29 29 USE infotrac_phy, only : nqtot 30 USE iophys, ONLY : iophys_ini 30 31 USE phyparam_mod, ONLY : phyparam 31 32 ! … … 72 73 ENDIF 73 74 74 CALL phyparam(klon,klev,nqtot, & 75 debut,lafin, & 75 IF(debut) CALL iophys_ini('phys.nc ',presnivs) ! calls iotd_ini 76 77 CALL phyparam(klon,klev, & 78 debut,lafin, & 76 79 rjourvrai,gmtime,pdtphys, & 77 paprs,pplay,pphi,pphis,presnivs, & 78 u,v,t,qx, & 79 flxmass_w, & 80 d_u,d_v,d_t,d_qx,d_ps) 80 paprs,pplay,pphi, & 81 u,v,t, & 82 d_u,d_v,d_t,d_ps) 83 84 IF(lafin) THEN 85 call iotd_fin 86 PRINT*,'Ecriture du fichier de reinitialiastion de la physique' 87 ! write(75) tsurf,tsoil FIXME 88 ENDIF 89 81 90 82 91 print*,'PHYDEV: itau=',itau -
dynamico_lmdz/simple_physics/phyparam/physics/phyparam_mod.F90
r4220 r4223 27 27 28 28 CONTAINS 29 30 SUBROUTINE phyparam(ngrid,nlayer, nq,&31 & firstcall,lastcall, &29 30 SUBROUTINE phyparam(ngrid,nlayer, & 31 & firstcall,lastcall, & 32 32 & rjourvrai,gmtime,ptimestep, & 33 & pplev,pplay,pphi,pphis,presnivs, & 34 & pu,pv,pt,pq, & 35 & pw, & 36 & pdu,pdv,pdt,pdq,pdpsrf) 33 & pplev,pplay,pphi, & 34 & pu,pv,pt, & 35 & pdu,pdv,pdt,pdpsrf) 37 36 USE phys_const, ONLY : g, rcp, r, unjours 38 37 USE surface, ONLY : soil 39 38 USE turbulence, ONLY : vdif 40 39 USE convection, ONLY : convadj 40 USE writefield_mod, ONLY : writefield 41 41 42 42 !======================================================================= … … 53 53 INTEGER, INTENT(IN) :: & 54 54 ngrid, & ! Size of the horizontal grid. 55 nlayer, & ! Number of vertical layers. 56 nq ! Number of advected fields (tracers) 55 nlayer ! Number of vertical layers. 57 56 LOGICAL, INTENT(IN) :: & 58 57 firstcall, & ! True at the first call … … 65 64 pplay(ngrid,nlayer), & ! Pressure at the middle of the layers (Pa) 66 65 pphi(ngrid,nlayer), & ! Geopotential at the middle of the layers (m2s-2) 67 pphis(ngrid), & ! surface geopotential (unused)68 presnivs(nlayer), &69 66 pu(ngrid,nlayer), & ! u component of the wind (ms-1) 70 67 pv(ngrid,nlayer), & ! v component of the wind (ms-1) 71 pw(ngrid,nlayer), & ! vertical velocity (unused) 72 pt(ngrid,nlayer), & ! Temperature (K) 73 pq(ngrid,nlayer,nq) ! Advected fields (unused) 68 pt(ngrid,nlayer) ! Temperature (K) 74 69 REAL, INTENT(OUT) :: & ! output : physical tendencies 75 70 pdu(ngrid,nlayer), & 76 71 pdv(ngrid,nlayer), & 77 72 pdt(ngrid,nlayer), & 78 pdq(ngrid,nlayer,nq), &79 73 pdpsrf(ngrid) 80 74 81 75 ! Local variables : 82 76 REAL, DIMENSION(ngrid) :: mu0,fract 83 INTEGER :: j,l,ig,ierr,aslun,nlevel,igout,it1,it2,isoil,iq 84 INTEGER*4 day_ini 77 INTEGER :: j,l,ig,nlevel,igout 85 78 ! 86 79 REAL :: zday, zdtime … … 96 89 REAL zdtlw(ngrid,nlayer),zdtsw(ngrid,nlayer) 97 90 REAL zfluxsw(ngrid),zfluxlw(ngrid) 98 REAL factq(nq),tauq(nq)99 character*3 nomq100 101 ! Local saved variables:102 ! ----------------------103 91 104 92 print*,'OK DANS PHYPARAM' 105 print*,'nq ',nq106 93 print*,'latitude0',ngrid,lati(1:2),lati(ngrid-1:ngrid) 107 94 print*,'nlayer',nlayer 108 print*,'size pdq ',ngrid*nlayer*4,ngrid*nlayer*nq, &109 & size(pdq),size(lati),size(pq),size(factq)110 95 111 96 IF (ngrid.NE.ngridmax) THEN … … 142 127 ENDDO 143 128 ENDIF 144 145 PRINT*,'FIRSTCALL B '146 print*,'INIIO avant iophys_ini '147 call iophys_ini('phys.nc ',presnivs)148 129 ENDIF 149 130 … … 154 135 icount=icount+1 155 136 156 pdq(:,:,:) = 0. ! we do not use tracers in this physics package157 137 pdv(:,:) = 0. 158 138 pdu(:,:) = 0. … … 315 295 enddo 316 296 317 call iophys_ecrit('u',nlayer,'Vent zonal moy','m/s',pu) 318 call iophys_ecrit('v',nlayer,'Vent meridien moy','m/s',pv) 319 call iophys_ecrit('temp',nlayer,'Temperature','K',pt) 320 call iophys_ecrit('geop',nlayer,'Geopotential','m2/s2',pphi) 321 call iophys_ecrit('plev',nlayer,'plev','Pa',pplev(:,1:nlayer)) 322 323 call iophys_ecrit('du',nlayer,'du',' ',pdu) 324 call iophys_ecrit('dv',nlayer,'du',' ',pdv) 325 call iophys_ecrit('dt',nlayer,'du',' ',pdt) 326 call iophys_ecrit('dtsw',nlayer,'dtsw',' ',zdtsw) 327 call iophys_ecrit('dtlw',nlayer,'dtlw',' ',zdtlw) 328 329 do iq=1,nq 330 nomq="tr." 331 write(nomq(2:3),'(i1.1)') iq 332 call iophys_ecrit(nomq,nlayer,nomq,' ',pq(:,:,iq)) 333 enddo 334 335 call iophys_ecrit('ts',1,'Surface temper','K',tsurf) 336 call iophys_ecrit('coslon',1,'coslon',' ',coslon) 337 call iophys_ecrit('sinlon',1,'sinlon',' ',sinlon) 338 call iophys_ecrit('coslat',1,'coslat',' ',coslat) 339 call iophys_ecrit('sinlat',1,'sinlat',' ',sinlat) 340 call iophys_ecrit('mu0',1,'mu0',' ',mu0) 341 call iophys_ecrit('alb',1,'alb',' ',albedo) 342 call iophys_ecrit('fract',1,'fract',' ',fract) 343 call iophys_ecrit('ps',1,'Surface pressure','Pa',pplev) 344 call iophys_ecrit('slp',1,'Sea level pressure','Pa',zpmer) 345 call iophys_ecrit('swsurf',1,'SW surf','Pa',zfluxsw) 346 call iophys_ecrit('lwsurf',1,'LW surf','Pa',zfluxlw) 297 call writefield('u','Vent zonal moy','m/s',pu) 298 call writefield('v','Vent meridien moy','m/s',pv) 299 call writefield('temp','Temperature','K',pt) 300 call writefield('geop','Geopotential','m2/s2',pphi) 301 call writefield('plev','plev','Pa',pplev(:,1:nlayer)) 302 303 call writefield('du','du',' ',pdu) 304 call writefield('dv','du',' ',pdv) 305 call writefield('dt','du',' ',pdt) 306 call writefield('dtsw','dtsw',' ',zdtsw) 307 call writefield('dtlw','dtlw',' ',zdtlw) 308 309 call writefield('ts','Surface temper','K',tsurf) 310 call writefield('coslon','coslon',' ',coslon) 311 call writefield('sinlon','sinlon',' ',sinlon) 312 call writefield('coslat','coslat',' ',coslat) 313 call writefield('sinlat','sinlat',' ',sinlat) 314 call writefield('mu0','mu0',' ',mu0) 315 call writefield('alb','alb',' ',albedo) 316 call writefield('fract','fract',' ',fract) 317 call writefield('ps','Surface pressure','Pa',pplev(:,1)) 318 call writefield('slp','Sea level pressure','Pa',zpmer) 319 call writefield('swsurf','SW surf','Pa',zfluxsw) 320 call writefield('lwsurf','LW surf','Pa',zfluxlw) 347 321 348 322 endif 349 350 !-----------------------------------------------------------------------351 IF(lastcall) THEN352 call iotd_fin353 PRINT*,'Ecriture du fichier de reinitialiastion de la physique'354 write(75) tsurf,tsoil355 ENDIF356 323 357 324 END SUBROUTINE phyparam -
dynamico_lmdz/simple_physics/phyparam/physics/radiative_lw.F90
r4199 r4223 68 68 REAL zup(ngrid,nlayer+1),zdup(ngrid) 69 69 70 CHARACTER( :), PARAMETER :: tag='rad/lw'70 CHARACTER(6), PARAMETER :: tag='rad/lw' 71 71 !----------------------------------------------------------------------- 72 72 ! initialisations:
Note: See TracChangeset
for help on using the changeset viewer.