Ignore:
Timestamp:
May 19, 2016, 1:10:50 PM (9 years ago)
Author:
aslmd
Message:

iniphysiq in all GCMs


iniphysiq was performing two main tasks

  • one that is planet-independent

i.e. setting the physics grid and geometry
(we checked: the lines of code
in phyxxx/iniphysiq_mod were doing
the exact same things)

  • one that is planet-dependent

i.e. time settings, planetary constants

now the planet-independent
initialization is done by inigeom_mod
which is in dynphy_lonlat

and the planet-dependent
initialization
is done in the respective phyxxx folders

this commit is intended
for interface lisibility
and modular approach
following the framework
adopted by Ehouarn
in the last commits

it paves the path for
a similar (and, now, easy)
counterpart for mesoscale
models

we adopted the sanity convention
ii and jj for dimensions
rlatudyn etc.. for grids
this is to avoid collision with
fields named iim or rlatu
possily defined elsewhere

compilation is OK
running is OK (checked for Mars)
outputs are exactly the same bit-by-bit

thx to Ehouarn and Maxence

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/iniphysiq_mod.F90

    r1543 r1563  
    66                     nbp, communicator, &
    77                     punjours, pdayref,ptimestep, &
    8                      rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
     8                     rlatudyn,rlatvdyn,rlonudyn,rlonvdyn, &
     9                     airedyn,cudyn,cvdyn, &
    910                     prad,pg,pr,pcpp,iflag_phys)
    1011
    11 use dimphy, only : init_dimphy
    12 use mod_grid_phy_lmdz, only : klon_glo, & ! number of atmospheric columns (on full grid)
    13                               regular_lonlat  ! regular longitude-latitude grid type
    14 use mod_phys_lmdz_para, only : klon_omp, & ! number of columns (on local omp grid)
    15                                klon_omp_begin, & ! start index of local omp subgrid
    16                                klon_omp_end, & ! end index of local omp subgrid
    17                                klon_mpi_begin ! start indes of columns (on local mpi grid)
    18 use geometry_mod, only: init_geometry
    19 !use comgeomphy, only : initcomgeomphy, &
    20 !                       cell_area, & ! physics grid area (m2)
    21 !                       dx, & ! cu coeff. (u_covariant = cu * u)
    22 !                       dy, & ! cv coeff. (v_covariant = cv * v)
    23 !                       longitude, & ! longitudes (rad)
    24 !                       latitude ! latitudes (rad)
    2512use infotrac, only : nqtot ! number of advected tracers
    2613use comgeomfi_h, only: ini_fillgeom
    2714use temps_mod, only: day_ini, hour_ini
    2815use phys_state_var_init_mod, only: phys_state_var_init
    29 use physics_distribution_mod, only: init_physics_distribution
    30 use regular_lonlat_mod, only: init_regular_lonlat, &
    31                               east, west, north, south, &
    32                               north_east, north_west, &
    33                               south_west, south_east
    34 use mod_interface_dyn_phys, only: init_interface_dyn_phys
     16
     17use geometry_mod, only: cell_area, & ! physics grid area (m2)
     18                        longitude, & ! longitudes (rad)
     19                        latitude ! latitudes (rad)
     20! necessary to get klon_omp
     21USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
    3522
    3623implicit none
     
    4330real,intent(in) :: pcpp ! specific heat Cp
    4431real,intent(in) :: punjours ! length (in s) of a standard day
    45 !integer,intent(in) :: ngrid ! number of horizontal grid points in the physics (full grid)
    4632integer,intent(in) :: nlayer ! number of atmospheric layers
    4733integer,intent(in) :: ii ! number of atmospheric coulumns along longitudes
     
    4935integer,intent(in) :: nbp ! number of physics columns for this MPI process
    5036integer,intent(in) :: communicator ! MPI communicator
    51 real,intent(in) :: rlatu(jj+1) ! latitudes of the physics grid
    52 real,intent(in) :: rlatv(jj) ! latitude boundaries of the physics grid
    53 real,intent(in) :: rlonv(ii+1) ! longitudes of the physics grid
    54 real,intent(in) :: rlonu(ii+1) ! longitude boundaries of the physics grid
    55 real,intent(in) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
    56 real,intent(in) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
    57 real,intent(in) :: cv((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
     37real,intent(in) :: rlatudyn(jj+1) ! latitudes of the physics grid
     38real,intent(in) :: rlatvdyn(jj) ! latitude boundaries of the physics grid
     39real,intent(in) :: rlonvdyn(ii+1) ! longitudes of the physics grid
     40real,intent(in) :: rlonudyn(ii+1) ! longitude boundaries of the physics grid
     41real,intent(in) :: airedyn(ii+1,jj+1) ! area of the dynamics grid (m2)
     42real,intent(in) :: cudyn((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
     43real,intent(in) :: cvdyn((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
    5844integer,intent(in) :: pdayref ! reference day of for the simulation
    5945real,intent(in) :: ptimestep !physics time step (s)
    6046integer,intent(in) :: iflag_phys ! type of physics to be called
    6147
    62 integer :: ibegin,iend,offset
    63 integer :: i,j,k
    64 character(len=20) :: modname='iniphysiq'
    65 character(len=80) :: abort_message
    66 real :: total_area_phy, total_area_dyn
    67 real :: pi
     48  ! the common part for all planetary physics
     49  !------------------------------------------
     50  ! --> initialize physics distribution, global fields and geometry
     51  CALL inigeom(ii,jj,nlayer, &
     52               nbp, communicator, &
     53               rlatudyn,rlatvdyn, &
     54               rlonudyn,rlonvdyn, &
     55               airedyn,cudyn,cvdyn)
    6856
    69 ! boundaries, on global grid
    70 real,allocatable :: boundslon_reg(:,:)
    71 real,allocatable :: boundslat_reg(:,:)
     57  ! the distinct part for all planetary physics
     58  !------------------------------------------
    7259
    73 ! global array, on full physics grid:
    74 real,allocatable :: latfi_glo(:)
    75 real,allocatable :: lonfi_glo(:)
    76 real,allocatable :: cufi_glo(:)
    77 real,allocatable :: cvfi_glo(:)
    78 real,allocatable :: airefi_glo(:)
    79 real,allocatable :: boundslonfi_glo(:,:)
    80 real,allocatable :: boundslatfi_glo(:,:)
    81 
    82 ! local arrays, on given MPI/OpenMP domain:
    83 real,allocatable,save :: latfi(:)
    84 real,allocatable,save :: lonfi(:)
    85 real,allocatable,save :: cufi(:)
    86 real,allocatable,save :: cvfi(:)
    87 real,allocatable,save :: airefi(:)
    88 real,allocatable,save :: boundslonfi(:,:)
    89 real,allocatable,save :: boundslatfi(:,:)
    90 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi)
    91 
    92 
    93 pi=2.*asin(1.0)
    94 
    95 ! Initialize Physics distibution and parameters and interface with dynamics
    96 CALL init_physics_distribution(regular_lonlat,4, &
    97                                  nbp,ii,jj+1,nlayer,communicator)
    98 CALL init_interface_dyn_phys
    99 
    100 ! init regular global longitude-latitude grid points and boundaries
    101 ALLOCATE(boundslon_reg(ii,2))
    102 ALLOCATE(boundslat_reg(jj+1,2))
     60!$OMP PARALLEL
    10361 
    104 DO i=1,ii
    105    boundslon_reg(i,east)=rlonu(i)
    106    boundslon_reg(i,west)=rlonu(i+1)
    107 ENDDO
    108 
    109 boundslat_reg(1,north)= PI/2
    110 boundslat_reg(1,south)= rlatv(1)
    111 DO j=2,jj
    112    boundslat_reg(j,north)=rlatv(j-1)
    113    boundslat_reg(j,south)=rlatv(j)
    114 ENDDO
    115 boundslat_reg(jj+1,north)= rlatv(jj)
    116 boundslat_reg(jj+1,south)= -PI/2
    117 
    118 ! Write values in module regular_lonlat_mod
    119 CALL init_regular_lonlat(ii,jj+1, rlonv(1:ii), rlatu, &
    120                          boundslon_reg, boundslat_reg)
    121 
    122 ! Generate global arrays on full physics grid
    123 allocate(latfi_glo(klon_glo),lonfi_glo(klon_glo))
    124 allocate(cufi_glo(klon_glo),cvfi_glo(klon_glo))
    125 allocate(airefi_glo(klon_glo))
    126 allocate(boundslonfi_glo(klon_glo,4))
    127 allocate(boundslatfi_glo(klon_glo,4))
    128 
    129 ! North pole
    130 latfi_glo(1)=rlatu(1)
    131 lonfi_glo(1)=0.
    132 cufi_glo(1) = cu(1)
    133 cvfi_glo(1) = cv(1)
    134 boundslonfi_glo(1,north_east)=0
    135 boundslatfi_glo(1,north_east)=PI/2
    136 boundslonfi_glo(1,north_west)=2*PI
    137 boundslatfi_glo(1,north_west)=PI/2
    138 boundslonfi_glo(1,south_west)=2*PI
    139 boundslatfi_glo(1,south_west)=rlatv(1)
    140 boundslonfi_glo(1,south_east)=0
    141 boundslatfi_glo(1,south_east)=rlatv(1)
    142 DO j=2,jj
    143   DO i=1,ii
    144     k=(j-2)*ii+1+i
    145     latfi_glo((j-2)*ii+1+i)= rlatu(j)
    146     lonfi_glo((j-2)*ii+1+i)= rlonv(i)
    147     cufi_glo((j-2)*ii+1+i) = cu((j-1)*(ii+1)+i)
    148     cvfi_glo((j-2)*ii+1+i) = cv((j-1)*(ii+1)+i)
    149     boundslonfi_glo(k,north_east)=rlonu(i)
    150     boundslatfi_glo(k,north_east)=rlatv(j-1)
    151     boundslonfi_glo(k,north_west)=rlonu(i+1)
    152     boundslatfi_glo(k,north_west)=rlatv(j-1)
    153     boundslonfi_glo(k,south_west)=rlonu(i+1)
    154     boundslatfi_glo(k,south_west)=rlatv(j)
    155     boundslonfi_glo(k,south_east)=rlonu(i)
    156     boundslatfi_glo(k,south_east)=rlatv(j)
    157   ENDDO
    158 ENDDO
    159 ! South pole
    160 latfi_glo(klon_glo)= rlatu(jj+1)
    161 lonfi_glo(klon_glo)= 0.
    162 cufi_glo(klon_glo) = cu((ii+1)*jj+1)
    163 cvfi_glo(klon_glo) = cv((ii+1)*jj-ii)
    164 boundslonfi_glo(klon_glo,north_east)= 0
    165 boundslatfi_glo(klon_glo,north_east)= rlatv(jj)
    166 boundslonfi_glo(klon_glo,north_west)= 2*PI
    167 boundslatfi_glo(klon_glo,north_west)= rlatv(jj)
    168 boundslonfi_glo(klon_glo,south_west)= 2*PI
    169 boundslatfi_glo(klon_glo,south_west)= -PI/2
    170 boundslonfi_glo(klon_glo,south_east)= 0
    171 boundslatfi_glo(klon_glo,south_east)= -Pi/2
    172 
    173 ! build airefi(), mesh area on physics grid
    174 CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,aire,airefi_glo)
    175 ! Poles are single points on physics grid
    176 airefi_glo(1)=sum(aire(1:ii,1))
    177 airefi_glo(klon_glo)=sum(aire(1:ii,jj+1))
    178 
    179 ! Sanity check: do total planet area match between physics and dynamics?
    180 total_area_dyn=sum(aire(1:ii,1:jj+1))
    181 total_area_phy=sum(airefi_glo(1:klon_glo))
    182 IF (total_area_dyn/=total_area_phy) THEN
    183   WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!'
    184   WRITE (lunout, *) '     in the dynamics total_area_dyn=', total_area_dyn
    185   WRITE (lunout, *) '  but in the physics total_area_phy=', total_area_phy
    186   IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN
    187     ! stop here if the relative difference is more than 0.001%
    188     abort_message = 'planet total surface discrepancy'
    189     CALL abort_gcm(modname, abort_message, 1)
    190   ENDIF
    191 ENDIF
    192 
    193 
    194 
    195 !$OMP PARALLEL
    196 ! Now generate local lon/lat/cu/cv/area arrays
    197 allocate(latfi(klon_omp),lonfi(klon_omp),cufi(klon_omp),cvfi(klon_omp))
    198 allocate(airefi(klon_omp))
    199 allocate(boundslonfi(klon_omp,4))
    200 allocate(boundslatfi(klon_omp,4))
    201 !call initcomgeomphy
    202      
    203 offset=klon_mpi_begin-1
    204 airefi(1:klon_omp)=airefi_glo(offset+klon_omp_begin:offset+klon_omp_end)
    205 cufi(1:klon_omp)=cufi_glo(offset+klon_omp_begin:offset+klon_omp_end)
    206 cvfi(1:klon_omp)=cvfi_glo(offset+klon_omp_begin:offset+klon_omp_end)
    207 lonfi(1:klon_omp)=lonfi_glo(offset+klon_omp_begin:offset+klon_omp_end)
    208 latfi(1:klon_omp)=latfi_glo(offset+klon_omp_begin:offset+klon_omp_end)
    209 boundslonfi(1:klon_omp,:)=boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)
    210 boundslatfi(1:klon_omp,:)=boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)
    211 
    212 ! copy over local grid longitudes and latitudes
    213 CALL init_geometry(klon_omp,lonfi,latfi,boundslonfi,boundslatfi, &
    214                    airefi,cufi,cvfi)
    215 
    21662! copy some fundamental parameters to physics
    21763! and do some initializations
    21864
    219 call init_dimphy(klon_omp,nlayer) ! Initialize dimphy module
    22065call phys_state_var_init(klon_omp,nlayer,nqtot, &
    22166                         day_ini,hour_ini,punjours,ptimestep, &
    22267                         prad,pg,pr,pcpp)
    223 call ini_fillgeom(klon_omp,latfi,lonfi,airefi)
     68call ini_fillgeom(klon_omp,latitude,longitude,cell_area)
     69! work is needed to put what is in comgeomfi_h in geometry_mod?
     70
    22471call conf_phys(klon_omp,nlayer,nqtot)
    22572
     
    22976!$OMP END PARALLEL
    23077
    231 
    23278end subroutine iniphysiq
    23379
Note: See TracChangeset for help on using the changeset viewer.