Changeset 1994
- Timestamp:
- Mar 5, 2014, 4:42:42 PM (11 years ago)
- Location:
- LMDZ5/trunk/libf/phydev
- Files:
-
- 1 added
- 1 deleted
- 4 moved
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/phydev/gr_fi_ecrit.F90
r1992 r1994 2 2 ! $Id $ 3 3 ! 4 SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit) 5 IMPLICIT NONE 6 c 7 c Transfer a field from the full physics grid 8 c to a full 2D (lonxlat) grid suitable for outputs 9 c 10 INTEGER,INTENT(IN) :: nfield,nlon,iim,jjmp1 11 REAL,INTENT(IN) :: fi(nlon,nfield) 12 REAL,INTENT(out) :: ecrit(iim*jjmp1,nfield) 13 c 14 INTEGER :: i, n, ig, jjm 15 c 16 jjm = jjmp1 - 1 17 DO n = 1, nfield 18 DO i=1,iim 19 ecrit(i,n) = fi(1,n) 20 ecrit(i+jjm*iim,n) = fi(nlon,n) 21 ENDDO 22 DO ig = 1, nlon - 2 23 ecrit(iim+ig,n) = fi(1+ig,n) 24 ENDDO 25 ENDDO 4 SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit) 5 IMPLICIT NONE 6 ! 7 ! Transfer a field from the full physics grid 8 ! to a full 2D (lonxlat) grid suitable for outputs 9 ! 10 INTEGER,INTENT(IN) :: nfield,nlon,iim,jjmp1 11 REAL,INTENT(IN) :: fi(nlon,nfield) 12 REAL,INTENT(out) :: ecrit(iim*jjmp1,nfield) 26 13 27 END 14 INTEGER :: i, n, ig, jjm 15 16 jjm = jjmp1 - 1 17 DO n = 1, nfield 18 DO i=1,iim 19 ecrit(i,n) = fi(1,n) 20 ecrit(i+jjm*iim,n) = fi(nlon,n) 21 ENDDO 22 DO ig = 1, nlon - 2 23 ecrit(iim+ig,n) = fi(1+ig,n) 24 ENDDO 25 ENDDO 26 27 END SUBROUTINE gr_fi_ecrit -
LMDZ5/trunk/libf/phydev/iniphysiq.F90
r1992 r1994 2 2 ! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $ 3 3 ! 4 SUBROUTINE iniphysiq(ngrid,nlayer, 5 $ punjours, 6 $ pdayref,ptimestep, 7 $ plat,plon,parea,pcu,pcv, 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 16 IMPLICIT NONE 17 c 18 c======================================================================= 19 c 20 c Initialisation of the physical constants and some positional and 21 c geometrical arrays for the physics 22 c 23 c 24 c ngrid Size of the horizontal grid. 25 c All internal loops are performed on that grid. 26 c nlayer Number of vertical layers. 27 c pdayref Day of reference for the simulation 28 c 29 c======================================================================= 4 SUBROUTINE iniphysiq(ngrid, nlayer, punjours, pdayref, ptimestep, plat, plon, & 5 parea, pcu, pcv, prad, pg, pr, pcpp, iflag_phys) 6 USE dimphy, ONLY: klev 7 USE mod_grid_phy_lmdz, ONLY: klon_glo 8 USE mod_phys_lmdz_para, ONLY: klon_omp, klon_omp_begin, klon_omp_end, & 9 klon_mpi_begin 10 USE comgeomphy, ONLY: airephy, cuphy, cvphy, rlond, rlatd 11 USE comcstphy, ONLY: rradius, rg, rr, rcpp 12 USE phyaqua_mod, ONLY: iniaqua 13 IMPLICIT NONE 14 ! 15 !======================================================================= 16 ! 17 ! Initialisation of the physical constants and some positional and 18 ! geometrical arrays for the physics 19 ! 20 ! 21 ! ngrid Size of the horizontal grid. 22 ! All internal loops are performed on that grid. 23 ! nlayer Number of vertical layers. 24 ! pdayref Day of reference for the simulation 25 ! 26 !======================================================================= 30 27 31 28 32 cym#include "dimensions.h" 33 cym#include "dimphy.h" 34 cym#include "comgeomphy.h" 35 #include "iniprint.h" 29 include "iniprint.h" 36 30 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 31 REAL,INTENT(IN) :: prad ! radius of the planet (m) 32 REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2) 33 REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu 34 REAL,INTENT(IN) :: pcpp ! specific heat Cp 35 REAL,INTENT(IN) :: punjours ! length (in s) of a standard day 36 INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics 37 INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers 38 REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid 39 REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid 40 REAL,INTENT(IN) :: parea(klon_glo) ! area (m2) 41 REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u) 42 REAL,INTENT(IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v) 43 INTEGER,INTENT(IN) :: pdayref ! reference day of for the simulation 44 REAL,INTENT(IN) :: ptimestep !physics time step (s) 45 INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called 52 46 53 54 55 47 INTEGER :: ibegin,iend,offset 48 CHARACTER (LEN=20) :: modname='iniphysiq' 49 CHARACTER (LEN=80) :: abort_message 56 50 57 58 write(lunout,*) 'STOP in ',trim(modname)59 write(lunout,*) 'Problem with dimensions :'60 write(lunout,*) 'nlayer = ',nlayer61 write(lunout,*) 'klev = ',klev62 63 64 51 IF (nlayer.NE.klev) THEN 52 WRITE(lunout,*) 'STOP in ',trim(modname) 53 WRITE(lunout,*) 'Problem with dimensions :' 54 WRITE(lunout,*) 'nlayer = ',nlayer 55 WRITE(lunout,*) 'klev = ',klev 56 abort_message = '' 57 CALL abort_gcm (modname,abort_message,1) 58 ENDIF 65 59 66 67 write(lunout,*) 'STOP in ',trim(modname)68 write(lunout,*) 'Problem with dimensions :'69 write(lunout,*) 'ngrid = ',ngrid70 write(lunout,*) 'klon = ',klon_glo71 72 73 60 IF (ngrid.NE.klon_glo) THEN 61 WRITE(lunout,*) 'STOP in ',trim(modname) 62 WRITE(lunout,*) 'Problem with dimensions :' 63 WRITE(lunout,*) 'ngrid = ',ngrid 64 WRITE(lunout,*) 'klon = ',klon_glo 65 abort_message = '' 66 CALL abort_gcm (modname,abort_message,1) 67 ENDIF 74 68 75 !$OMP PARALLEL PRIVATE(ibegin,iend) 76 !$OMP+SHARED(parea,pcu,pcv,plon,plat)69 !$OMP PARALLEL PRIVATE(ibegin,iend) & 70 !$OMP SHARED(parea,pcu,pcv,plon,plat) 77 71 78 offset=klon_mpi_begin-1 79 airephy(1:klon_omp)=parea(offset+klon_omp_begin: 80 & offset+klon_omp_end) 81 cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end) 82 cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end) 83 rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end) 84 rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end) 72 offset = klon_mpi_begin - 1 73 airephy(1:klon_omp) = parea(offset+klon_omp_begin:offset+klon_omp_end) 74 cuphy(1:klon_omp) = pcu(offset+klon_omp_begin:offset+klon_omp_end) 75 cvphy(1:klon_omp) = pcv(offset+klon_omp_begin:offset+klon_omp_end) 76 rlond(1:klon_omp) = plon(offset+klon_omp_begin:offset+klon_omp_end) 77 rlatd(1:klon_omp) = plat(offset+klon_omp_begin:offset+klon_omp_end) 85 78 86 ! copy some fundamental parameters to physics87 88 89 90 79 ! copy some fundamental parameters to physics 80 rradius=prad 81 rg=pg 82 rr=pr 83 rcpp=pcpp 91 84 92 !$OMP END PARALLEL85 !$OMP END PARALLEL 93 86 94 ! print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ' 95 ! print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...' 87 ! Additional initializations for aquaplanets 88 !$OMP PARALLEL 89 IF (iflag_phys>=100) THEN 90 CALL iniaqua(klon_omp,rlatd,rlond,iflag_phys) 91 ENDIF 92 !$OMP END PARALLEL 96 93 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 103 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) 109 110 END 94 END SUBROUTINE iniphysiq -
LMDZ5/trunk/libf/phydev/phyaqua_mod.F90
r1992 r1994 2 2 ! $Id: $ 3 3 ! 4 MODULE phyaqua_mod 4 5 5 subroutine iniaqua(nlon,latfi,lonfi,iflag_phys)6 IMPLICIT NONE 6 7 7 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 8 ! Create an initial state (startphy.nc) for the physics 9 ! Usefull for idealised cases (e.g. aquaplanets or testcases) 10 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 8 CONTAINS 11 9 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 10 SUBROUTINE iniaqua(nlon, latfi, lonfi, iflag_phys) 11 12 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 13 ! Create an initial state (startphy.nc) for the physics 14 ! Usefull for idealised cases (e.g. aquaplanets or testcases) 15 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 16 17 USE phys_state_var_mod, ONLY: rlat, rlon, phys_state_var_init 18 USE mod_phys_lmdz_para, ONLY: klon_omp 19 USE comgeomphy, ONLY: rlond, rlatd 20 IMPLICIT NONE 17 21 18 integer,intent(in) :: nlon,iflag_phys19 real,intent(in) :: lonfi(nlon),latfi(nlon)22 INTEGER,INTENT(IN) :: nlon,iflag_phys 23 REAL,INTENT(IN) :: lonfi(nlon),latfi(nlon) 20 24 21 ! local variables22 real:: pi25 ! local variables 26 REAL :: pi 23 27 24 ! initializations:25 pi=2.*asin(1.)28 ! initializations: 29 pi=2.*ASIN(1.) 26 30 27 callphys_state_var_init()31 CALL phys_state_var_init() 28 32 29 30 33 rlat(1:klon_omp)=rlatd(1:klon_omp)*180./pi 34 rlon(1:klon_omp)=rlond(1:klon_omp)*180./pi 31 35 32 36 33 ! Here you could create an initial condition for the physics34 ! ...35 ! ... fill in the fields...36 ! ...37 ! ... and create a "startphy.nc" file37 ! Here you could create an initial condition for the physics 38 ! ... 39 ! ... fill in the fields... 40 ! ... 41 ! ... and create a "startphy.nc" file 38 42 CALL phyredem ("startphy.nc") 39 43 40 end44 END SUBROUTINE iniaqua 41 45 46 END MODULE phyaqua_mod -
LMDZ5/trunk/libf/phydev/phyredem.F90
r1992 r1994 2 2 ! $Id: $ 3 3 ! 4 4 SUBROUTINE phyredem (fichnom) 5 5 6 use iostart, only : open_restartphy,close_restartphy, 7 & put_var,put_field 8 use phys_state_var_mod, only : rlon,rlat 6 USE iostart, ONLY: open_restartphy, close_restartphy, put_var, put_field 7 USE phys_state_var_mod, ONLY: rlon, rlat 9 8 10 implicit none9 IMPLICIT NONE 11 10 12 character(len=*),intent(in) :: fichnom11 CHARACTER(LEN=*),INTENT(IN) :: fichnom 13 12 14 integer,parameter:: tab_cntrl_len=10015 real:: tab_cntrl(tab_cntrl_len)13 INTEGER,PARAMETER :: tab_cntrl_len=100 14 REAL :: tab_cntrl(tab_cntrl_len) 16 15 17 ! open file16 ! open file 18 17 19 18 CALL open_restartphy(fichnom) 20 19 21 ! tab_cntrl() contains run parameters20 ! tab_cntrl() contains run parameters 22 21 23 22 tab_cntrl(:)=0.0 24 23 25 24 26 CALL put_var("controle","Parametres de controle",tab_cntrl)25 CALL put_var("controle", "Control parameters", tab_cntrl) 27 26 28 ! coordinates27 ! coordinates 29 28 30 CALL put_field("longitude", 31 . "Longitudes de la grille physique",rlon) 29 CALL put_field("longitude", "Longitudes on physics grid", rlon) 32 30 33 CALL put_field("latitude","Latitudes de la grille physique",rlat)31 CALL put_field("latitude", "Latitudes on physics grid", rlat) 34 32 35 ! close file33 ! close file 36 34 37 38 !$OMP BARRIER35 CALL close_restartphy 36 !$OMP BARRIER 39 37 40 END 38 END SUBROUTINE phyredem
Note: See TracChangeset
for help on using the changeset viewer.