Changeset 1707 for LMDZ5/branches/testing/libf/phydev
- Timestamp:
- Jan 11, 2013, 10:19:19 AM (12 years ago)
- Location:
- LMDZ5/branches/testing
- Files:
-
- 1 deleted
- 4 edited
- 6 copied
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/branches/testing
- Property svn:mergeinfo changed
/LMDZ5/trunk merged: 1670-1692,1694-1703,1705-1706
- Property svn:mergeinfo changed
-
LMDZ5/branches/testing/libf/phydev/iniphysiq.F
r1665 r1707 2 2 ! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $ 3 3 ! 4 c5 c6 4 SUBROUTINE iniphysiq(ngrid,nlayer, 7 5 $ punjours, 8 6 $ pdayref,ptimestep, 9 7 $ plat,plon,parea,pcu,pcv, 10 $ prad,pg,pr,pcpp) 11 USE dimphy 12 USE mod_grid_phy_lmdz 13 USE mod_phys_lmdz_para 14 USE comgeomphy 8 $ prad,pg,pr,pcpp,iflag_phys) 9 USE dimphy, only : klev 10 USE mod_grid_phy_lmdz, only : klon_glo 11 USE mod_phys_lmdz_para, only : klon_omp,klon_omp_begin, 12 & klon_omp_end,klon_mpi_begin 13 USE comgeomphy, only : airephy,cuphy,cvphy,rlond,rlatd 14 USE comcstphy, only : rradius,rg,rr,rcpp 15 15 16 16 IMPLICIT NONE … … 18 18 c======================================================================= 19 19 c 20 c subject:21 c --------20 c Initialisation of the physical constants and some positional and 21 c geometrical arrays for the physics 22 22 c 23 c Initialisation for the physical parametrisations of the LMD24 c martian atmospheric general circulation modele.25 c26 c author: Frederic Hourdin 15 / 10 /9327 c -------28 c29 c arguments:30 c ----------31 c32 c input:33 c ------34 23 c 35 24 c ngrid Size of the horizontal grid. … … 37 26 c nlayer Number of vertical layers. 38 27 c pdayref Day of reference for the simulation 39 c firstcall True at the first call40 c lastcall True at the last call41 c pday Number of days counted from the North. Spring42 c equinoxe.43 28 c 44 29 c======================================================================= 45 c 46 c----------------------------------------------------------------------- 47 c declarations: 48 c ------------- 30 49 31 50 32 cym#include "dimensions.h" 51 33 cym#include "dimphy.h" 52 34 cym#include "comgeomphy.h" 53 #include "comcstphy.h" 54 REAL prad,pg,pr,pcpp,punjours 55 56 INTEGER ngrid,nlayer 57 REAL plat(ngrid),plon(ngrid),parea(klon_glo) 58 REAL pcu(klon_glo),pcv(klon_glo) 59 INTEGER pdayref 35 #include "iniprint.h" 36 37 REAL,INTENT(IN) :: prad ! radius of the planet (m) 38 REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2) 39 REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu 40 REAL,INTENT(IN) :: pcpp ! specific heat Cp 41 REAL,INTENT(IN) :: punjours ! length (in s) of a standard day 42 INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics 43 INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers 44 REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid 45 REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid 46 REAL,INTENT(IN) :: parea(klon_glo) ! area (m2) 47 REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u) 48 REAL,INTENT(IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v) 49 INTEGER,INTENT(IN) :: pdayref ! reference day of for the simulation 50 REAL,INTENT(IN) :: ptimestep !physics time step (s) 51 INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called 52 60 53 INTEGER :: ibegin,iend,offset 61 62 REAL ptimestep63 54 CHARACTER (LEN=20) :: modname='iniphysiq' 64 55 CHARACTER (LEN=80) :: abort_message 65 56 66 57 IF (nlayer.NE.klev) THEN 67 PRINT*,'STOP in inifis'68 PRINT*,'Probleme dedimensions :'69 PRINT*,'nlayer = ',nlayer70 PRINT*,'klev = ',klev58 write(lunout,*) 'STOP in ',trim(modname) 59 write(lunout,*) 'Problem with dimensions :' 60 write(lunout,*) 'nlayer = ',nlayer 61 write(lunout,*) 'klev = ',klev 71 62 abort_message = '' 72 63 CALL abort_gcm (modname,abort_message,1) … … 74 65 75 66 IF (ngrid.NE.klon_glo) THEN 76 PRINT*,'STOP in inifis'77 PRINT*,'Probleme dedimensions :'78 PRINT*,'ngrid = ',ngrid79 PRINT*,'klon = ',klon_glo67 write(lunout,*) 'STOP in ',trim(modname) 68 write(lunout,*) 'Problem with dimensions :' 69 write(lunout,*) 'ngrid = ',ngrid 70 write(lunout,*) 'klon = ',klon_glo 80 71 abort_message = '' 81 72 CALL abort_gcm (modname,abort_message,1) 82 73 ENDIF 83 c$OMP PARALLEL PRIVATE(ibegin,iend) 84 c$OMP+ SHARED(parea,pcu,pcv,plon,plat) 74 75 !$OMP PARALLEL PRIVATE(ibegin,iend) 76 !$OMP+ SHARED(parea,pcu,pcv,plon,plat) 85 77 86 78 offset=klon_mpi_begin-1 … … 92 84 rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end) 93 85 94 ! call suphel 95 ! prad,pg,pr,pcpp 86 ! copy some fundamental parameters to physics 96 87 rradius=prad 97 88 rg=pg … … 99 90 rcpp=pcpp 100 91 101 92 !$OMP END PARALLEL 102 93 103 c$OMP END PARALLEL 94 ! print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ' 95 ! print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...' 104 96 105 print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ' 106 print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...' 97 ! Additional initializations for aquaplanets 98 !$OMP PARALLEL 99 if (iflag_phys>=100) then 100 call iniaqua(klon_omp,rlatd,rlond,iflag_phys) 101 endif 102 !$OMP END PARALLEL 107 103 108 RETURN109 9999 CONTINUE110 abort_message ='Cette version demande les fichier rnatur.dat111 & et surf.def'112 CALL abort_gcm (modname,abort_message,1)104 ! RETURN 105 !9999 CONTINUE 106 ! abort_message ='Cette version demande les fichier rnatur.dat 107 ! & et surf.def' 108 ! CALL abort_gcm (modname,abort_message,1) 113 109 114 110 END -
LMDZ5/branches/testing/libf/phydev/phyaqua.F
r1665 r1707 1 ! Routines complementaires pour la physique planetaire. 2 1 ! 2 ! $Id: $ 3 ! 3 4 4 5 subroutine iniaqua(nlon,latfi,lonfi,iflag_phys) 5 6 6 7 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 7 ! Creation d'un etat initial et de conditions aux limites 8 ! (resp startphy.nc et limit.nc) pour des configurations idealisees 9 ! du modele LMDZ dans sa version terrestre. 10 ! iflag_phys est un parametre qui controle 11 ! iflag_phys = N 12 ! de 100 a 199 : aqua planetes avec SST forcees 13 ! N-100 determine le type de SSTs 14 ! de 200 a 299 : terra planetes avec Ts calcule 15 ! 8 ! Create an initial state (startphy.nc) for the physics 9 ! Usefull for idealised cases (e.g. aquaplanets or testcases) 16 10 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 17 11 12 use phys_state_var_mod, only : rlat,rlon, 13 & phys_state_var_init 14 use mod_phys_lmdz_para, only : klon_omp 15 use comgeomphy, only : rlond,rlatd 16 implicit none 17 18 integer,intent(in) :: nlon,iflag_phys 19 real,intent(in) :: lonfi(nlon),latfi(nlon) 18 20 19 integer nlon,iflag_phys 20 cIM ajout latfi, lonfi 21 REAL, DIMENSION (nlon) :: lonfi, latfi 21 ! local variables 22 real :: pi 23 24 ! initializations: 25 pi=2.*asin(1.) 26 27 call phys_state_var_init() 28 29 rlat(1:klon_omp)=rlatd(1:klon_omp)*180./pi 30 rlon(1:klon_omp)=rlond(1:klon_omp)*180./pi 22 31 23 32 24 return 33 ! Here you could create an initial condition for the physics 34 ! ... 35 ! ... fill in the fields... 36 ! ... 37 ! ... and create a "startphy.nc" file 38 CALL phyredem ("startphy.nc") 39 25 40 end 26 41 -
LMDZ5/branches/testing/libf/phydev/physiq.F90
r1665 r1707 11 11 & , PVteta) 12 12 13 USE dimphy 14 USE infotrac 15 USE comgeomphy 13 USE dimphy, only : klon,klev 14 USE infotrac, only : nqtot 15 USE comgeomphy, only : rlatd 16 USE comcstphy, only : rg 17 USE iophy, only : histbeg_phy,histwrite_phy 18 USE ioipsl, only : getin,histvert,histdef,histend,ymds2ju 19 USE mod_phys_lmdz_para, only : jj_nb 20 USE phys_state_var_mod, only : phys_state_var_init 16 21 17 22 IMPLICIT none 18 !====================================================================== 19 ! Objet: Moniteur general de la physique du modele 20 !====================================================================== 23 #include "dimensions.h" 24 25 integer,parameter :: jjmp1=jjm+1-1/jjm 26 integer,parameter :: iip1=iim+1 21 27 ! 22 ! Arguments:28 ! Routine argument: 23 29 ! 24 ! nlon----input-I-nombre de points horizontaux 25 ! nlev----input-I-nombre de couches verticales, doit etre egale a klev 26 ! debut---input-L-variable logique indiquant le premier passage 27 ! lafin---input-L-variable logique indiquant le dernier passage 28 ! jD_cur -R-jour courant a l'appel de la physique (jour julien) 29 ! jH_cur -R-heure courante a l'appel de la physique (jour julien) 30 ! pdtphys-input-R-pas d'integration pour la physique (seconde)31 ! paprs---input-R-pression pour chaque inter-couche (enPa)32 ! pplay---input-R-pression pour le mileu de chaque couche (enPa)33 ! pphi----input-R-geopotentiel de chaque couche (g z) (reference sol) 34 ! pphis---input-R-geopotentiel du sol35 ! presnivs-input_R_pressions approximat. des milieux couches ( en PA) 36 ! u-------input-R-vitesse dans la direction X (de O a E) en m/s 37 ! v-------input-R-vitesse Y (de S a N) en m/s 38 ! t-------input-R-temperature (K)39 ! qx------input-R-humidite specifique (kg/kg) et d'autres traceurs 40 ! d_t_dyn-input-R-tendance dynamique pour "t" (K/s)41 ! d_q_dyn-input-R-tendance dynamique pour "q" (kg/kg/s)42 ! flxmass_w -input-R- flux de masse verticale 43 ! d_u-----output-R-tendance physique de "u"(m/s/s)44 ! d_v-----output-R-tendance physique de "v"(m/s/s)45 ! d_t-----output-R-tendance physique de "t"(K/s)46 ! d_qx----output-R-tendance physique de "qx" (kg/kg/s) 47 ! d_ps----output-R-tendance physique de la pression au sol 48 !IM 49 ! PVteta--output-R-vorticite potentielle a des thetas constantes50 ! ======================================================================51 #include "dimensions.h" 52 #include "comcstphy.h" 30 integer,intent(in) :: nlon ! number of atmospheric colums 31 integer,intent(in) :: nlev ! number of vertical levels (should be =klev) 32 real,intent(in) :: jD_cur ! current day number (Julian day) 33 real,intent(in) :: jH_cur ! current time of day (as fraction of day) 34 logical,intent(in) :: debut ! signals first call to physics 35 logical,intent(in) :: lafin ! signals last call to physics 36 real,intent(in) :: pdtphys ! physics time step (s) 37 real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa) 38 real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa) 39 real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer 40 real,intent(in) :: pphis(klon) ! surface geopotential 41 real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers 42 integer,parameter :: longcles=20 43 real,intent(in) :: clesphy0(longcles) ! Not used 44 real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s) 45 real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s) 46 real,intent(in) :: t(klon,klev) ! temperature (K) 47 real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air) 48 real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux 49 real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s) 50 real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s) 51 real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s) 52 real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers 53 real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure 54 real,intent(in) :: dudyn(iim+1,jjmp1,klev) ! Not used 55 !FH! REAL PVteta(klon,nbteta) 56 ! REAL PVteta(klon,1) 57 real,intent(in) :: PVteta(klon,3) ! Not used ; should match definition 58 ! in calfis.F 53 59 54 integer jjmp1 55 parameter (jjmp1=jjm+1-1/jjm) 56 integer iip1 57 parameter (iip1=iim+1) 60 integer,save :: itau=0 ! counter to count number of calls to physics 61 !$OMP THREADPRIVATE(itau) 62 real :: temp_newton(klon,klev) 63 integer :: k 64 logical, save :: first=.true. 65 !$OMP THREADPRIVATE(first) 58 66 59 INTEGER ivap ! indice de traceurs pour vapeur d'eau 60 PARAMETER (ivap=1) 61 INTEGER iliq ! indice de traceurs pour eau liquide 62 PARAMETER (iliq=2) 67 ! For I/Os 68 integer :: itau0 69 real :: zjulian 70 real :: dtime 71 integer :: nhori ! horizontal coordinate ID 72 integer,save :: nid_hist ! output file ID 73 !$OMP THREADPRIVATE(nid_hist) 74 integer :: zvertid ! vertical coordinate ID 75 integer,save :: iwrite_phys ! output every iwrite_phys physics step 76 !$OMP THREADPRIVATE(iwrite_phys) 77 real :: t_ops ! frequency of the IOIPSL operations (eg average over...) 78 real :: t_wrt ! frequency of the IOIPSL outputs 63 79 64 ! 65 ! 66 ! Variables argument: 67 ! 68 INTEGER nlon 69 INTEGER nlev 70 REAL, intent(in):: jD_cur, jH_cur 80 ! initializations 81 if (debut) then ! Things to do only for the first call to physics 82 ! load initial conditions for physics (including the grid) 83 call phys_state_var_init() ! some initializations, required before calling phyetat0 84 call phyetat0("startphy.nc") 71 85 72 REAL pdtphys 73 LOGICAL debut, lafin 74 REAL paprs(klon,klev+1) 75 REAL pplay(klon,klev) 76 REAL pphi(klon,klev) 77 REAL pphis(klon) 78 REAL presnivs(klev) 79 REAL znivsig(klev) 80 real pir 86 ! Initialize outputs: 87 itau0=0 88 iwrite_phys=1 !default: output every physics timestep 89 call getin("iwrite_phys",iwrite_phys) 90 t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation 91 t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file 92 ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0 93 !CALL ymds2ju(annee0, month, dayref, hour, zjulian) 94 call ymds2ju(1979, 1, 1, 0.0, zjulian) 95 dtime=pdtphys 96 call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist) 97 !$OMP MASTER 98 ! define vertical coordinate 99 call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, & 100 presnivs,zvertid,'down') 101 ! define variables which will be written in "histins.nc" file 102 call histdef(nid_hist,'temperature','Atmospheric temperature','K', & 103 iim,jj_nb,nhori,klev,1,klev,zvertid,32, & 104 'inst(X)',t_ops,t_wrt) 105 call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', & 106 iim,jj_nb,nhori,klev,1,klev,zvertid,32, & 107 'inst(X)',t_ops,t_wrt) 108 call histdef(nid_hist,'v','Northward Meridional Wind','m/s', & 109 iim,jj_nb,nhori,klev,1,klev,zvertid,32, & 110 'inst(X)',t_ops,t_wrt) 111 call histdef(nid_hist,'ps','Surface Pressure','Pa', & 112 iim,jj_nb,nhori,1,1,1,zvertid,32, & 113 'inst(X)',t_ops,t_wrt) 114 ! end definition sequence 115 call histend(nid_hist) 116 !$OMP END MASTER 117 endif ! of if (debut) 81 118 82 REAL u(klon,klev) 83 REAL v(klon,klev) 84 REAL t(klon,klev),theta(klon,klev) 85 REAL qx(klon,klev,nqtot) 86 REAL flxmass_w(klon,klev) 87 REAL omega(klon,klev) ! vitesse verticale en Pa/s 88 REAL d_u(klon,klev) 89 REAL d_v(klon,klev) 90 REAL d_t(klon,klev) 91 REAL d_qx(klon,klev,nqtot) 92 REAL d_ps(klon) 93 real da(klon,klev),phi(klon,klev,klev),mp(klon,klev) 94 !IM definition dynamique o_trac dans phys_output_open 95 ! type(ctrl_out) :: o_trac(nqtot) 96 !FH! REAL PVteta(klon,nbteta) 97 REAL PVteta(klon,1) 98 REAL dudyn(iim+1,jjmp1,klev) 119 ! increment counter itau 120 itau=itau+1 99 121 100 INTEGER longcles 101 PARAMETER ( longcles = 20 ) 122 ! set all tendencies to zero 123 d_u(1:klon,1:klev)=0. 124 d_v(1:klon,1:klev)=0. 125 d_t(1:klon,1:klev)=0. 126 d_qx(1:klon,1:klev,1:nqtot)=0. 127 d_ps(1:klon)=0. 102 128 103 real temp_newton(klon,klev) 104 integer k 105 logical, save :: first=.true. 106 107 REAL clesphy0( longcles ) 108 109 d_u=0. 110 d_v=0. 111 d_t=0. 112 d_qx=0. 113 d_ps=0. 114 115 d_u(:,1)=-u(:,1)/86400. 116 do k=1,klev 117 temp_newton(:,k)=280.+cos(rlatd(:))*40.-pphi(:,k)/rg*6.e-3 118 d_t(:,k)=(temp_newton(:,k)-t(:,k))/1.e5 119 enddo 129 ! compute tendencies to return to the dynamics: 130 ! "friction" on the first layer 131 d_u(1:klon,1)=-u(1:klon,1)/86400. 132 d_v(1:klon,1)=-v(1:klon,1)/86400. 133 ! newtonian relaxation towards temp_newton() 134 do k=1,klev 135 temp_newton(1:klon,k)=280.+cos(rlatd(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3 136 d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5 137 enddo 120 138 121 139 122 print*,'COUCOU PHYDEV' 123 return 124 end 140 !print*,'PHYDEV: itau=',itau 141 142 ! write some outputs: 143 if (modulo(itau,iwrite_phys)==0) then 144 call histwrite_phy(nid_hist,.false.,"temperature",itau,t) 145 call histwrite_phy(nid_hist,.false.,"u",itau,u) 146 call histwrite_phy(nid_hist,.false.,"v",itau,v) 147 call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1)) 148 endif 149 150 ! if lastcall, then it is time to write "restartphy.nc" file 151 if (lafin) then 152 call phyredem("restartphy.nc") 153 endif 154 155 end
Note: See TracChangeset
for help on using the changeset viewer.