Changeset 2225 for LMDZ5/trunk/libf/phylmd/iniphysiq.F90
- Timestamp:
- Mar 11, 2015, 3:55:23 PM (10 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/phylmd/iniphysiq.F90
r1993 r2225 3 3 4 4 5 6 SUBROUTINE iniphysiq(ngrid, nlayer, punjours, pdayref, ptimestep, plat, plon, & 7 parea, pcu, pcv, prad, pg, pr, pcpp, iflag_phys) 8 USE dimphy, ONLY: klev 9 USE mod_grid_phy_lmdz, ONLY: klon_glo 10 USE mod_phys_lmdz_para, ONLY: klon_omp, klon_omp_begin, klon_omp_end, & 11 klon_mpi_begin 12 USE comgeomphy, ONLY: airephy, cuphy, cvphy, rlond, rlatd 5 SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep, & 6 rlatu,rlonv,aire,cu,cv, & 7 prad,pg,pr,pcpp,iflag_phys) 8 USE dimphy, ONLY: klev ! number of atmospheric levels 9 USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of atmospheric columns 10 ! (on full grid) 11 USE mod_phys_lmdz_para, ONLY: klon_omp, & ! number of columns (on local omp grid) 12 klon_omp_begin, & ! start index of local omp subgrid 13 klon_omp_end, & ! end index of local omp subgrid 14 klon_mpi_begin ! start indes of columns (on local mpi grid) 15 USE comgeomphy, ONLY: initcomgeomphy, & 16 airephy, & ! physics grid area (m2) 17 cuphy, & ! cu coeff. (u_covariant = cu * u) 18 cvphy, & ! cv coeff. (v_covariant = cv * v) 19 rlond, & ! longitudes 20 rlatd ! latitudes 13 21 USE phyaqua_mod, ONLY: iniaqua 14 22 IMPLICIT NONE 15 23 16 24 ! ======================================================================= 17 18 25 ! Initialisation of the physical constants and some positional and 19 26 ! geometrical arrays for the physics 20 21 22 ! ngrid Size of the horizontal grid.23 ! All internal loops are performed on that grid.24 ! nlayer Number of vertical layers.25 ! pdayref Day of reference for the simulation26 27 27 ! ======================================================================= 28 28 29 ! ym#include "dimensions.h"30 ! ym#include "dimphy.h"31 ! ym#include "comgeomphy.h"32 29 include "YOMCST.h" 33 30 include "iniprint.h" … … 38 35 REAL, INTENT (IN) :: pcpp ! specific heat Cp 39 36 REAL, INTENT (IN) :: punjours ! length (in s) of a standard day 40 INTEGER, INTENT (IN) :: ngrid ! number of horizontal grid points in the physics41 37 INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers 42 REAL, INTENT (IN) :: plat(ngrid) ! latitudes of the physics grid 43 REAL, INTENT (IN) :: plon(ngrid) ! longitudes of the physics grid 44 REAL, INTENT (IN) :: parea(klon_glo) ! area (m2) 45 REAL, INTENT (IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u) 46 REAL, INTENT (IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v) 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) 47 45 INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation 48 46 REAL, INTENT (IN) :: ptimestep !physics time step (s) … … 50 48 51 49 INTEGER :: ibegin, iend, offset 50 INTEGER :: i,j 52 51 CHARACTER (LEN=20) :: modname = 'iniphysiq' 53 52 CHARACTER (LEN=80) :: abort_message 53 REAL :: total_area_phy, total_area_dyn 54 55 56 ! global array, on full physics grid: 57 REAL,ALLOCATABLE :: latfi(:) 58 REAL,ALLOCATABLE :: lonfi(:) 59 REAL,ALLOCATABLE :: cufi(:) 60 REAL,ALLOCATABLE :: cvfi(:) 61 REAL,ALLOCATABLE :: airefi(:) 54 62 55 63 IF (nlayer/=klev) THEN … … 62 70 END IF 63 71 64 IF (ngrid/=klon_glo) THEN 65 WRITE (lunout, *) 'STOP in ', trim(modname) 66 WRITE (lunout, *) 'Problem with dimensions :' 67 WRITE (lunout, *) 'ngrid = ', ngrid 68 WRITE (lunout, *) 'klon = ', klon_glo 69 abort_message = '' 70 CALL abort_gcm(modname, abort_message, 1) 71 END IF 72 73 !$OMP PARALLEL PRIVATE(ibegin,iend) & 74 !$OMP SHARED(parea,pcu,pcv,plon,plat) 72 !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/)) 73 74 ! Generate global arrays on full physics grid 75 ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo)) 76 ALLOCATE(airefi(klon_glo)) 77 78 IF (klon_glo>1) THEN ! general case 79 ! North pole 80 latfi(1)=rlatu(1) 81 lonfi(1)=0. 82 cufi(1) = cu(1) 83 cvfi(1) = cv(1) 84 DO j=2,jjm 85 DO i=1,iim 86 latfi((j-2)*iim+1+i)= rlatu(j) 87 lonfi((j-2)*iim+1+i)= rlonv(i) 88 cufi((j-2)*iim+1+i) = cu((j-1)*iim+1+i) 89 cvfi((j-2)*iim+1+i) = cv((j-1)*iim+1+i) 90 ENDDO 91 ENDDO 92 ! South pole 93 latfi(klon_glo)= rlatu(jjm+1) 94 lonfi(klon_glo)= 0. 95 cufi(klon_glo) = cu((iim+1)*jjm+1) 96 cvfi(klon_glo) = cv((iim+1)*jjm-iim) 97 98 ! build airefi(), mesh area on physics grid 99 CALL gr_dyn_fi(1,iim+1,jjm+1,klon_glo,aire,airefi) 100 ! Poles are single points on physics grid 101 airefi(1)=sum(aire(1:iim,1)) 102 airefi(klon_glo)=sum(aire(1:iim,jjm+1)) 103 104 ! Sanity check: do total planet area match between physics and dynamics? 105 total_area_dyn=sum(aire(1:iim,1:jjm+1)) 106 total_area_phy=sum(airefi(1:klon_glo)) 107 IF (total_area_dyn/=total_area_phy) THEN 108 WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!' 109 WRITE (lunout, *) ' in the dynamics total_area_dyn=', total_area_dyn 110 WRITE (lunout, *) ' but in the physics total_area_phy=', total_area_phy 111 IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN 112 ! stop here if the relative difference is more than 0.001% 113 abort_message = 'planet total surface discrepancy' 114 CALL abort_gcm(modname, abort_message, 1) 115 ENDIF 116 ENDIF 117 ELSE ! klon_glo==1, running the 1D model 118 ! just copy over input values 119 latfi(1)=rlatu(1) 120 lonfi(1)=rlonv(1) 121 cufi(1)=cu(1) 122 cvfi(1)=cv(1) 123 airefi(1)=aire(1,1) 124 ENDIF ! of IF (klon_glo>1) 125 126 !$OMP PARALLEL 127 ! Now generate local lon/lat/cu/cv/area arrays 128 CALL initcomgeomphy 75 129 76 130 offset = klon_mpi_begin - 1 77 airephy(1:klon_omp) = parea(offset+klon_omp_begin:offset+klon_omp_end)78 cuphy(1:klon_omp) = pcu(offset+klon_omp_begin:offset+klon_omp_end)79 cvphy(1:klon_omp) = pcv(offset+klon_omp_begin:offset+klon_omp_end)80 rlond(1:klon_omp) = plon(offset+klon_omp_begin:offset+klon_omp_end)81 rlatd(1:klon_omp) = plat(offset+klon_omp_begin:offset+klon_omp_end)131 airephy(1:klon_omp) = airefi(offset+klon_omp_begin:offset+klon_omp_end) 132 cuphy(1:klon_omp) = cufi(offset+klon_omp_begin:offset+klon_omp_end) 133 cvphy(1:klon_omp) = cvfi(offset+klon_omp_begin:offset+klon_omp_end) 134 rlond(1:klon_omp) = lonfi(offset+klon_omp_begin:offset+klon_omp_end) 135 rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end) 82 136 83 137 ! suphel => initialize some physical constants (orbital parameters, … … 86 140 CALL suphel 87 141 88 89 90 91 142 !$OMP END PARALLEL 143 144 ! check that physical constants set in 'suphel' are coherent 145 ! with values set in the dynamics: 92 146 IF (rday/=punjours) THEN 93 147 WRITE (lunout, *) 'iniphysiq: length of day discrepancy!!!' … … 142 196 143 197 ! Additional initializations for aquaplanets 144 198 !$OMP PARALLEL 145 199 IF (iflag_phys>=100) THEN 146 200 CALL iniaqua(klon_omp, rlatd, rlond, iflag_phys) 147 201 END IF 148 !$OMP END PARALLEL 149 150 ! RETURN 151 ! 9999 CONTINUE 152 ! abort_message ='Cette version demande les fichier rnatur.dat 153 ! & et surf.def' 154 ! CALL abort_gcm (modname,abort_message,1) 202 !$OMP END PARALLEL 155 203 156 204 END SUBROUTINE iniphysiq
Note: See TracChangeset
for help on using the changeset viewer.