Changeset 4222 for dynamico_lmdz


Ignore:
Timestamp:
Jan 9, 2020, 4:58:29 PM (5 years ago)
Author:
dubos
Message:

simple_physics : cleanup iniphysiq + iniphyparam

Location:
dynamico_lmdz/simple_physics/phyparam
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/simple_physics/phyparam/dynphy_lonlat/iniphysiq_mod.F90

    r4221 r4222  
    33!
    44MODULE iniphysiq_mod
     5  IMPLICIT NONE
     6 
     7CONTAINS
     8 
     9  SUBROUTINE iniphysiq(iim,jjm,nlayer, &
     10       &               nbp, communicator, &
     11       &               punjours, pdayref,ptimestep, &
     12       &               rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
     13       &               prad,pg,pr,pcpp,iflag_phys)
     14    USE dimphy, ONLY: init_dimphy
     15    USE inigeomphy_mod, ONLY: inigeomphy
     16    USE iniphyparam_mod, ONLY : iniphyparam
     17    USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
     18    USE infotrac, ONLY: nqtot, type_trac
     19    USE infotrac_phy, ONLY: init_infotrac_phy
     20    USE inifis_mod, ONLY: inifis
     21    USE phyaqua_mod, ONLY: iniaqua
     22    USE nrtype, ONLY: pi
     23   
     24    !
     25    !=======================================================================
     26    !   Initialisation of the physical constants and some positional and
     27    !   geometrical arrays for the physics
     28    !=======================================================================   
     29   
     30    include "iniprint.h"
     31   
     32    REAL,INTENT(IN) :: prad ! radius of the planet (m)
     33    REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
     34    REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
     35    REAL,INTENT(IN) :: pcpp ! specific heat Cp
     36    REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
     37    INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
     38    INTEGER, INTENT (IN) :: iim ! number of atmospheric coulumns along longitudes
     39    INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
     40    INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
     41    INTEGER, INTENT(IN) :: communicator ! MPI communicator
     42    REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
     43    REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
     44    REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
     45    REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
     46    REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
     47    REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
     48    REAL, INTENT (IN) :: cv((iim+1)*jjm) ! 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   
     53    INTEGER :: ibegin,iend,offset
     54    INTEGER :: i,j,k
     55    CHARACTER (LEN=20) :: modname='iniphysiq'
     56    CHARACTER (LEN=80) :: abort_message
     57   
     58   
     59    print*,'INInnn   iniphysiq_mod'
     60   
     61    ! --> initialize physics distribution, global fields and geometry
     62    ! (i.e. things in phy_common or dynphy_lonlat)
     63    CALL inigeomphy(iim,jjm,nlayer, &
     64         nbp, communicator, &
     65         rlatu,rlatv, &
     66         rlonu,rlonv, &
     67         aire,cu,cv)
     68   
     69    ! --> now initialize things specific to the phydev physics package
     70   
     71    !$OMP PARALLEL
     72   
     73    ! Initialize physical constants in physics:
     74    CALL inifis(prad,pg,pr,pcpp)
     75   
     76    ! Initialize tracer names, numbers, etc. for physics
     77    CALL init_infotrac_phy(nqtot,type_trac)
     78   
     79    ! Additional initializations for aquaplanets
     80    IF (iflag_phys>=100) THEN
     81       CALL iniaqua(klon_omp,iflag_phys)
     82    ENDIF
    583
    6 CONTAINS
     84    CALL setup_phyparam
    785
    8 SUBROUTINE iniphysiq(iim,jjm,nlayer, &
    9                      nbp, communicator, &
    10                      punjours, pdayref,ptimestep, &
    11                      rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
    12                      prad,pg,pr,pcpp,iflag_phys)
    13   USE dimphy, ONLY: init_dimphy
    14   USE inigeomphy_mod, ONLY: inigeomphy
    15   USE iniphyparam_mod, ONLY : iniphyparam
    16   USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
    17   USE infotrac, ONLY: nqtot, type_trac
    18   USE infotrac_phy, ONLY: init_infotrac_phy
    19   USE inifis_mod, ONLY: inifis
    20   USE phyaqua_mod, ONLY: iniaqua
    21   USE nrtype, ONLY: pi
    22   IMPLICIT NONE
     86    CALL iniphyparam(klon_omp,nlayer, &
     87         punjours, &
     88         pdayref,ptimestep, &
     89         prad,pg,pr,pcpp)
     90   
     91    !$OMP END PARALLEL
     92   
     93   
     94  END SUBROUTINE iniphysiq
     95 
     96  SUBROUTINE setup_phyparam
     97    USE comgeomfi,          ONLY : nlayermx, init_comgeomfi
     98    USE dimphy,             ONLY : klon, klev
     99    USE mod_grid_phy_lmdz,  ONLY : klon_glo
     100    USE mod_phys_lmdz_para, ONLY : klon_omp
     101    USE geometry_mod,       ONLY : longitude,latitude
     102    USE read_param_mod
     103    USE phyparam_plugins_lmdz
    23104
    24   !
    25   !=======================================================================
    26   !   Initialisation of the physical constants and some positional and
    27   !   geometrical arrays for the physics
    28   !=======================================================================
    29  
    30  
    31   include "iniprint.h"
     105    read_paramr_plugin => read_paramr
     106    read_parami_plugin => read_parami
     107    read_paramb_plugin => read_paramb
    32108
    33   REAL,INTENT(IN) :: prad ! radius of the planet (m)
    34   REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
    35   REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
    36   REAL,INTENT(IN) :: pcpp ! specific heat Cp
    37   REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
    38   INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
    39   INTEGER, INTENT (IN) :: iim ! number of atmospheric coulumns along longitudes
    40   INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
    41   INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
    42   INTEGER, INTENT(IN) :: communicator ! MPI communicator
    43   REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
    44   REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
    45   REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
    46   REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
    47   REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
    48   REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
    49   REAL, INTENT (IN) :: cv((iim+1)*jjm) ! cv coeff. (v_covariant = cv * v)
    50   INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
    51   REAL,INTENT(IN) :: ptimestep !physics time step (s)
    52   INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
     109    CALL init_comgeomfi(klon_omp, klev, longitude, latitude)
    53110
    54   INTEGER :: ibegin,iend,offset
    55   INTEGER :: i,j,k
    56   CHARACTER (LEN=20) :: modname='iniphysiq'
    57   CHARACTER (LEN=80) :: abort_message
     111    IF (klon.NE.klon_omp) THEN
     112       PRINT*,'STOP in setup_phyparam'
     113       PRINT*,'Probleme de dimensions :'
     114       PRINT*,'klon     = ',klon
     115       PRINT*,'klon_omp   = ',klon_omp
     116       STOP
     117    ENDIF
    58118
     119    IF (klev.NE.nlayermx) THEN
     120       PRINT*,'STOP in setup_phyparam'
     121       PRINT*,'Probleme de dimensions :'
     122       PRINT*,'nlayer     = ',klev
     123       PRINT*,'nlayermx   = ',nlayermx
     124       STOP
     125    ENDIF
    59126
    60   print*,'INInnn   iniphysiq_mod'
     127    IF (klon_omp.NE.klon_glo) THEN
     128       PRINT*,'STOP in setup_phyparam'
     129       PRINT*,'Probleme de dimensions :'
     130       PRINT*,'ngrid     = ', klon_omp
     131       PRINT*,'ngridmax   = ',klon_glo
     132       STOP
     133    ENDIF
    61134
    62   ! --> initialize physics distribution, global fields and geometry
    63   ! (i.e. things in phy_common or dynphy_lonlat)
    64   CALL inigeomphy(iim,jjm,nlayer, &
    65                nbp, communicator, &
    66                rlatu,rlatv, &
    67                rlonu,rlonv, &
    68                aire,cu,cv)
    69 
    70   ! --> now initialize things specific to the phydev physics package
    71 
    72 !$OMP PARALLEL
    73 
    74   ! Initialize physical constants in physics:
    75   CALL inifis(prad,pg,pr,pcpp)
     135  END SUBROUTINE setup_phyparam
    76136 
    77   ! Initialize tracer names, numbers, etc. for physics
    78   CALL init_infotrac_phy(nqtot,type_trac)
    79 
    80   ! Additional initializations for aquaplanets
    81   IF (iflag_phys>=100) THEN
    82     CALL iniaqua(klon_omp,iflag_phys)
    83   ENDIF
    84   CALL iniphyparam(klon_omp,nlayer, &
    85              punjours, &
    86              pdayref,ptimestep, &
    87              prad,pg,pr,pcpp)
    88 
    89 !$OMP END PARALLEL
    90    
    91 
    92 END SUBROUTINE iniphysiq
    93 
    94137END MODULE iniphysiq_mod
  • dynamico_lmdz/simple_physics/phyparam/param/iniphyparam.F90

    r4221 r4222  
    33  PRIVATE
    44
    5   REAL, PARAMETER :: perfect_gas_const = 8134.
     5  REAL, PARAMETER :: perfect_gas_const = 8314.46261815324 ! NB using g instead of kg for mass
    66
    77  PUBLIC :: iniphyparam
     
    1313       &           pdayref,ptimestep,     &
    1414       &           prad,pg,pr,pcpp)
    15     use getparam
    16     use dimphy
    17     USE mod_grid_phy_lmdz
    18     USE mod_phys_lmdz_para
    1915    USE callkeys
    20     use comgeomfi
    21     USE geometry_mod, ONLY : longitude,latitude
    2216    USE phys_const, ONLY : planet_rad,g,r,cpp,rcp,dtphys,unjours,mugaz
    2317    USE planet, ONLY : coefir, coefvis
     
    2620    USE surface
    2721    USE read_param_mod
    28     USE phyparam_plugins_lmdz
    2922
    30     IMPLICIT NONE
    31    
    32     !    ngrid                 Size of the horizontal grid.
    33     !                          All internal loops are performed on that grid.
    34     !    nlayer                Number of vertical layers.
    35     !    pdayref               Day of reference for the simulation
    36     !    firstcall             True at the first call
    37     !    lastcall              True at the last call
    38     !    pday                  Number of days counted from the North. Spring
    39     !                          equinox
    40 
    41     REAL prad,pg,pr,pcpp,punjours
    42    
    43     INTEGER ngrid, nlayer, pdayref
    44    
    45     REAL ptimestep
     23    INTEGER, INTENT(IN) :: &
     24         ngrid, &       ! Size of the horizontal grid
     25         nlayer, &      ! Number of vertical layers.
     26         pdayref        ! Day of reference for the simulation
     27    REAL, INTENT(IN)  :: ptimestep, prad, pg, pr, pcpp, punjours
    4628   
    4729    print*,'INIPHYPARAM'
    48    
    49     read_paramr_plugin => read_paramr
    50     read_parami_plugin => read_parami
    51     read_paramb_plugin => read_paramb
     30    print*,'Avant les getpar '
    5231
    53     CALL init_comgeomfi(klon_omp, klev, longitude, latitude)
    54    
    55     IF (klon.NE.klon_omp) THEN
    56        PRINT*,'STOP in iniphyparam'
    57        PRINT*,'Probleme de dimensions :'
    58        PRINT*,'klon     = ',klon
    59        PRINT*,'klon_omp   = ',klon_omp
    60        STOP
    61     ENDIF
    62    
    63     IF (nlayer.NE.nlayermx) THEN
    64        PRINT*,'STOP in iniphyparam'
    65        PRINT*,'Probleme de dimensions :'
    66        PRINT*,'nlayer     = ',nlayer
    67        PRINT*,'nlayermx   = ',nlayermx
    68        STOP
    69     ENDIF
    70    
    71     IF (ngrid.NE.klon_glo) THEN
    72        PRINT*,'STOP in iniphyparam'
    73        PRINT*,'Probleme de dimensions :'
    74        PRINT*,'ngrid     = ',ngrid
    75        PRINT*,'ngridmax   = ',klon_glo
    76        STOP
    77     ENDIF
    78    
    79     print*,'Avant les getpar '
    8032    CALL read_param('unjours', 86400., unjours,'unjours')
    81     CALL read_param('planet_rad',6.4e6,planet_rad,'planet_rad')
     33    CALL read_param('planet_rad',prad,planet_rad,'planet_rad')
    8234    CALL read_param('g',9.8           ,g,'g')
    8335    CALL read_param('cpp',1004.       ,cpp,'cpp')
    8436    CALL read_param('mugaz',28.       ,mugaz,'mugaz')
     37    r=perfect_gas_const/mugaz
     38    rcp=r/cpp
     39
    8540    CALL read_param('year_day',360.   ,year_day,'year_day')
    8641    CALL read_param('periheli',150.   ,periheli,'periheli')
     
    11166    CALL read_param('period_sort',1.,period_sort,'period sorties en jour')
    11267   
     68    CALL check_mismatch('unjours', punjours, unjours)
     69    CALL check_mismatch('rad', prad, planet_rad)
     70    CALL check_mismatch('g', pg, g)
     71    CALL check_mismatch('R', pr, r)
     72    CALL check_mismatch('cpp', pcpp, cpp)
     73   
    11374    print*,'Activation de la physique:'
     75    print*,' R=',r
    11476    print*,' Rayonnement ',callrad
    11577    print*,' Diffusion verticale turbulente ', calldifv
     
    12991         &   iradia,' physical time-step or each ', &
    13092         &   iradia*ptimestep,' seconds'
    131    
    132     !-----------------------------------------------------------------------
    133    
    134     print*,'latitude0  ohe',latitude(1:3),latitude(klon_omp)
    135     print*,'OK17 AAA'
    136    
    137     prad=planet_rad
    138     pg=g
    139     r=perfect_gas_const/mugaz
    140     print*,'R=',r
    141     pr=r
    142     pcpp=cpp
    143     rcp=r/cpp
     93
    14494    dtphys=ptimestep
    145     punjours=unjours
    146    
     95
    14796  END SUBROUTINE iniphyparam
    148  
     97
     98  SUBROUTINE check_mismatch(name, a,b)
     99    CHARACTER(*), INTENT(IN) :: name
     100    REAL, INTENT(IN) :: a,b
     101    IF(a /= b) THEN
     102       PRINT *, 'Phys/dyn mismatch for ', name, ' : ',a,b
     103    END IF
     104  END SUBROUTINE check_mismatch
     105
    149106END MODULE iniphyparam_mod
Note: See TracChangeset for help on using the changeset viewer.