Ignore:
Timestamp:
Apr 13, 2015, 10:21:09 AM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes 2216:2237 into testing branch

Location:
LMDZ5/branches/testing
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phydev/iniphysiq.F90

    r1999 r2258  
    22! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
    33!
    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
     4SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep,         &
     5                     rlatu,rlonv,aire,cu,cv,                             &
     6                     prad,pg,pr,pcpp,iflag_phys)
     7  USE dimphy, ONLY: klev ! number of atmospheric levels
     8  USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of atmospheric columns
     9                                        ! (on full grid)
     10  USE mod_phys_lmdz_para, ONLY: klon_omp, & ! number of columns (on local omp grid)
     11                                klon_omp_begin, & ! start index of local omp subgrid
     12                                klon_omp_end, & ! end index of local omp subgrid
     13                                klon_mpi_begin ! start indes of columns (on local mpi grid)
     14  USE comgeomphy, ONLY: initcomgeomphy, &
     15                        airephy, & ! physics grid area (m2)
     16                        cuphy, & ! cu coeff. (u_covariant = cu * u)
     17                        cvphy, & ! cv coeff. (v_covariant = cv * v)
     18                        rlond, & ! longitudes
     19                        rlatd ! latitudes
     20  USE comcstphy, ONLY: rradius, & ! planet radius (m)
     21                       rr, & ! recuced gas constant: R/molar mass of atm
     22                       rg, & ! gravity
     23                       rcpp  ! specific heat of the atmosphere
    1224  USE phyaqua_mod, ONLY: iniaqua
    1325  IMPLICIT NONE
    1426  !
    1527  !=======================================================================
    16   !
    1728  !   Initialisation of the physical constants and some positional and
    1829  !   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   !
    2630  !=======================================================================
    2731 
     
    3438  REAL,INTENT(IN) :: pcpp ! specific heat Cp
    3539  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
     40  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
     41  INTEGER, INTENT (IN) :: iim ! number of atmospheric coulumns along longitudes
     42  INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
     43  REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
     44  REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
     45  REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
     46  REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
     47  REAL, INTENT (IN) :: cv((iim+1)*jjm) ! cv coeff. (v_covariant = cv * v)
     48  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
    4449  REAL,INTENT(IN) :: ptimestep !physics time step (s)
    4550  INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
    4651
    4752  INTEGER :: ibegin,iend,offset
     53  INTEGER :: i,j
    4854  CHARACTER (LEN=20) :: modname='iniphysiq'
    4955  CHARACTER (LEN=80) :: abort_message
    50  
     56  REAL :: total_area_phy, total_area_dyn
     57
     58
     59  ! global array, on full physics grid:
     60  REAL,ALLOCATABLE :: latfi(:)
     61  REAL,ALLOCATABLE :: lonfi(:)
     62  REAL,ALLOCATABLE :: cufi(:)
     63  REAL,ALLOCATABLE :: cvfi(:)
     64  REAL,ALLOCATABLE :: airefi(:)
     65
    5166  IF (nlayer.NE.klev) THEN
    5267    WRITE(lunout,*) 'STOP in ',trim(modname)
     
    5873  ENDIF
    5974
    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
     75  !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
     76 
     77  ! Generate global arrays on full physics grid
     78  ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
     79  ALLOCATE(airefi(klon_glo))
    6880
    69   !$OMP PARALLEL PRIVATE(ibegin,iend) &
    70   !$OMP          SHARED(parea,pcu,pcv,plon,plat)
    71      
     81    ! North pole
     82    latfi(1)=rlatu(1)
     83    lonfi(1)=0.
     84    cufi(1) = cu(1)
     85    cvfi(1) = cv(1)
     86    DO j=2,jjm
     87      DO i=1,iim
     88        latfi((j-2)*iim+1+i)= rlatu(j)
     89        lonfi((j-2)*iim+1+i)= rlonv(i)
     90        cufi((j-2)*iim+1+i) = cu((j-1)*iim+1+i)
     91        cvfi((j-2)*iim+1+i) = cv((j-1)*iim+1+i)
     92      ENDDO
     93    ENDDO
     94    ! South pole
     95    latfi(klon_glo)= rlatu(jjm+1)
     96    lonfi(klon_glo)= 0.
     97    cufi(klon_glo) = cu((iim+1)*jjm+1)
     98    cvfi(klon_glo) = cv((iim+1)*jjm-iim)
     99
     100    ! build airefi(), mesh area on physics grid
     101    CALL gr_dyn_fi(1,iim+1,jjm+1,klon_glo,aire,airefi)
     102    ! Poles are single points on physics grid
     103    airefi(1)=sum(aire(1:iim,1))
     104    airefi(klon_glo)=sum(aire(1:iim,jjm+1))
     105
     106    ! Sanity check: do total planet area match between physics and dynamics?
     107    total_area_dyn=sum(aire(1:iim,1:jjm+1))
     108    total_area_phy=sum(airefi(1:klon_glo))
     109    IF (total_area_dyn/=total_area_phy) THEN
     110      WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!'
     111      WRITE (lunout, *) '     in the dynamics total_area_dyn=', total_area_dyn
     112      WRITE (lunout, *) '  but in the physics total_area_phy=', total_area_phy
     113      IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN
     114        ! stop here if the relative difference is more than 0.001%
     115        abort_message = 'planet total surface discrepancy'
     116        CALL abort_gcm(modname, abort_message, 1)
     117      ENDIF
     118    ENDIF
     119
     120!$OMP PARALLEL
     121  ! Now generate local lon/lat/cu/cv/area arrays
     122  CALL initcomgeomphy
     123
    72124  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)
     125  airephy(1:klon_omp) = airefi(offset+klon_omp_begin:offset+klon_omp_end)
     126  cuphy(1:klon_omp) = cufi(offset+klon_omp_begin:offset+klon_omp_end)
     127  cvphy(1:klon_omp) = cvfi(offset+klon_omp_begin:offset+klon_omp_end)
     128  rlond(1:klon_omp) = lonfi(offset+klon_omp_begin:offset+klon_omp_end)
     129  rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end)
    78130
    79131  ! copy some fundamental parameters to physics
     
    83135  rcpp=pcpp
    84136
    85   !$OMP END PARALLEL
     137!$OMP END PARALLEL
    86138
    87139  ! Additional initializations for aquaplanets
    88   !$OMP PARALLEL
     140!$OMP PARALLEL
    89141  IF (iflag_phys>=100) THEN
    90142    CALL iniaqua(klon_omp,rlatd,rlond,iflag_phys)
    91143  ENDIF
    92   !$OMP END PARALLEL
     144!$OMP END PARALLEL
    93145
    94146END SUBROUTINE iniphysiq
  • LMDZ5/branches/testing/libf/phydev/physiq.F90

    r2160 r2258  
    44      SUBROUTINE physiq (nlon,nlev, &
    55     &            debut,lafin,jD_cur, jH_cur,pdtphys, &
    6      &            paprs,pplay,pphi,pphis,presnivs,clesphy0, &
     6     &            paprs,pplay,pphi,pphis,presnivs, &
    77     &            u,v,t,qx, &
    88     &            flxmass_w, &
     
    4545      real,intent(in) :: pphis(klon) ! surface geopotential
    4646      real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
    47       integer,parameter :: longcles=20
    48       real,intent(in) :: clesphy0(longcles) ! Not used
    4947      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
    5048      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
Note: See TracChangeset for help on using the changeset viewer.