Ignore:
Timestamp:
Jul 24, 2024, 4:39:59 PM (4 months ago)
Author:
abarral
Message:

Replace iniprint.h by lmdz_iniprint.f90
(lint) along the way

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phydev/iniphysiq_mod.F90

    r5117 r5118  
    1 
    21! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
    32
     
    65CONTAINS
    76
    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 lmdz_phys_para, ONLY: klon_omp ! number of columns (on local omp grid)
    16   USE infotrac, ONLY: nqtot, type_trac
    17   USE infotrac_phy, ONLY: init_infotrac_phy
    18   USE inifis_mod, ONLY: inifis
    19   USE phyaqua_mod, ONLY: iniaqua
    20   USE lmdz_physical_constants, ONLY: pi
    21   IMPLICIT NONE
     7  SUBROUTINE iniphysiq(iim, jjm, nlayer, &
     8          nbp, communicator, &
     9          punjours, pdayref, ptimestep, &
     10          rlatu, rlatv, rlonu, rlonv, aire, cu, cv, &
     11          prad, pg, pr, pcpp, iflag_phys)
     12    USE dimphy, ONLY: init_dimphy
     13    USE inigeomphy_mod, ONLY: inigeomphy
     14    USE lmdz_phys_para, ONLY: klon_omp ! number of columns (on local omp grid)
     15    USE infotrac, ONLY: nqtot, type_trac
     16    USE infotrac_phy, ONLY: init_infotrac_phy
     17    USE inifis_mod, ONLY: inifis
     18    USE phyaqua_mod, ONLY: iniaqua
     19    USE lmdz_physical_constants, ONLY: pi
     20    USE lmdz_iniprint, ONLY: lunout, prt_level
     21    IMPLICIT NONE
    2222
    23   !=======================================================================
    24   !   Initialisation of the physical constants and some positional and
    25   !   geometrical arrays for the physics
    26   !=======================================================================
    27  
    28  
    29   include "iniprint.h"
     23    !=======================================================================
     24    !   Initialisation of the physical constants and some positional and
     25    !   geometrical arrays for the physics
     26    !=======================================================================
    3027
    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) :: nlayer ! number of atmospheric layers
    37   INTEGER, INTENT (IN) :: iim ! number of atmospheric coulumns along longitudes
    38   INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
    39   INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
    40   INTEGER, INTENT(IN) :: communicator ! MPI communicator
    41   REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
    42   REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
    43   REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
    44   REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries 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
    49   REAL,INTENT(IN) :: ptimestep !physics time step (s)
    50   INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
     28    REAL, INTENT(IN) :: prad ! radius of the planet (m)
     29    REAL, INTENT(IN) :: pg ! gravitational acceleration (m/s2)
     30    REAL, INTENT(IN) :: pr ! reduced gas constant R/mu
     31    REAL, INTENT(IN) :: pcpp ! specific heat Cp
     32    REAL, INTENT(IN) :: punjours ! length (in s) of a standard day
     33    INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
     34    INTEGER, INTENT (IN) :: iim ! number of atmospheric coulumns along longitudes
     35    INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
     36    INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
     37    INTEGER, INTENT(IN) :: communicator ! MPI communicator
     38    REAL, INTENT (IN) :: rlatu(jjm + 1) ! latitudes of the physics grid
     39    REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
     40    REAL, INTENT (IN) :: rlonv(iim + 1) ! longitudes of the physics grid
     41    REAL, INTENT (IN) :: rlonu(iim + 1) ! longitude boundaries 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)
     45    INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
     46    REAL, INTENT(IN) :: ptimestep !physics time step (s)
     47    INTEGER, INTENT(IN) :: iflag_phys ! type of physics to be called
    5148
    52   INTEGER :: ibegin,iend,offset
    53   INTEGER :: i,j,k
    54   CHARACTER (LEN=20) :: modname='iniphysiq'
    55   CHARACTER (LEN=80) :: abort_message
     49    INTEGER :: ibegin, iend, offset
     50    INTEGER :: i, j, k
     51    CHARACTER (LEN = 20) :: modname = 'iniphysiq'
     52    CHARACTER (LEN = 80) :: abort_message
    5653
    5754
    58   ! --> initialize physics distribution, global fields and geometry
    59   ! (i.e. things in phy_common or dynphy_lonlat)
    60   CALL inigeomphy(iim,jjm,nlayer, &
    61                nbp, communicator, &
    62                rlatu,rlatv, &
    63                rlonu,rlonv, &
    64                aire,cu,cv)
     55    ! --> initialize physics distribution, global fields and geometry
     56    ! (i.e. things in phy_common or dynphy_lonlat)
     57    CALL inigeomphy(iim, jjm, nlayer, &
     58            nbp, communicator, &
     59            rlatu, rlatv, &
     60            rlonu, rlonv, &
     61            aire, cu, cv)
    6562
    66   ! --> now initialize things specific to the phydev physics package
     63    ! --> now initialize things specific to the phydev physics package
    6764
    68 !$OMP PARALLEL
     65    !$OMP PARALLEL
    6966
    70   ! Initialize physical constants in physics:
    71   CALL inifis(prad,pg,pr,pcpp)
    72  
    73   ! Initialize tracer names, numbers, etc. for physics
    74   CALL init_infotrac_phy(nqtot,type_trac)
     67    ! Initialize physical constants in physics:
     68    CALL inifis(prad, pg, pr, pcpp)
    7569
    76   ! Additional initializations for aquaplanets
    77   IF (iflag_phys>=100) THEN
    78     CALL iniaqua(klon_omp,iflag_phys)
    79   ENDIF
    80 !$OMP END PARALLEL
     70    ! Initialize tracer names, numbers, etc. for physics
     71    CALL init_infotrac_phy(nqtot, type_trac)
    8172
    82 END SUBROUTINE iniphysiq
     73    ! Additional initializations for aquaplanets
     74    IF (iflag_phys>=100) THEN
     75      CALL iniaqua(klon_omp, iflag_phys)
     76    ENDIF
     77    !$OMP END PARALLEL
     78
     79  END SUBROUTINE iniphysiq
    8380
    8481END MODULE iniphysiq_mod
Note: See TracChangeset for help on using the changeset viewer.