Ignore:
Timestamp:
Mar 5, 2014, 4:42:42 PM (10 years ago)
Author:
Ehouarn Millour
Message:

Follow the trend; convert all fixed form sources in phydev to free form.
EM

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phydev/iniphysiq.F90

    r1992 r1994  
    22! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
    33!
    4       SUBROUTINE iniphysiq(ngrid,nlayer,
    5      $           punjours,
    6      $           pdayref,ptimestep,
    7      $           plat,plon,parea,pcu,pcv,
    8      $           prad,pg,pr,pcpp,iflag_phys)
    9       USE dimphy, only : klev
    10       USE mod_grid_phy_lmdz, only : klon_glo
    11       USE mod_phys_lmdz_para, only : klon_omp,klon_omp_begin,
    12      &                               klon_omp_end,klon_mpi_begin
    13       USE comgeomphy, only : airephy,cuphy,cvphy,rlond,rlatd
    14       USE comcstphy, only : rradius,rg,rr,rcpp
    15 
    16       IMPLICIT NONE
    17 c
    18 c=======================================================================
    19 c
    20 c   Initialisation of the physical constants and some positional and
    21 c   geometrical arrays for the physics
    22 c
    23 c
    24 c    ngrid                 Size of the horizontal grid.
    25 c                          All internal loops are performed on that grid.
    26 c    nlayer                Number of vertical layers.
    27 c    pdayref               Day of reference for the simulation
    28 c
    29 c=======================================================================
     4SUBROUTINE 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
     12  USE phyaqua_mod, ONLY: iniaqua
     13  IMPLICIT NONE
     14  !
     15  !=======================================================================
     16  !
     17  !   Initialisation of the physical constants and some positional and
     18  !   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  !
     26  !=======================================================================
    3027 
    3128 
    32 cym#include "dimensions.h"
    33 cym#include "dimphy.h"
    34 cym#include "comgeomphy.h"
    35 #include "iniprint.h"
     29  include "iniprint.h"
    3630
    37       REAL,INTENT(IN) :: prad ! radius of the planet (m)
    38       REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
    39       REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
    40       REAL,INTENT(IN) :: pcpp ! specific heat Cp
    41       REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
    42       INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics
    43       INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
    44       REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid
    45       REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid
    46       REAL,INTENT(IN) :: parea(klon_glo) ! area (m2)
    47       REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u)
    48       REAL,INTENT(IN) :: pcv(klon_glo) ! 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
     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) :: 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
     44  REAL,INTENT(IN) :: ptimestep !physics time step (s)
     45  INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
    5246
    53       INTEGER :: ibegin,iend,offset
    54       CHARACTER (LEN=20) :: modname='iniphysiq'
    55       CHARACTER (LEN=80) :: abort_message
     47  INTEGER :: ibegin,iend,offset
     48  CHARACTER (LEN=20) :: modname='iniphysiq'
     49  CHARACTER (LEN=80) :: abort_message
    5650 
    57       IF (nlayer.NE.klev) THEN
    58          write(lunout,*) 'STOP in ',trim(modname)
    59          write(lunout,*) 'Problem with dimensions :'
    60          write(lunout,*) 'nlayer     = ',nlayer
    61          write(lunout,*) 'klev   = ',klev
    62          abort_message = ''
    63          CALL abort_gcm (modname,abort_message,1)
    64       ENDIF
     51  IF (nlayer.NE.klev) THEN
     52    WRITE(lunout,*) 'STOP in ',trim(modname)
     53    WRITE(lunout,*) 'Problem with dimensions :'
     54    WRITE(lunout,*) 'nlayer     = ',nlayer
     55    WRITE(lunout,*) 'klev   = ',klev
     56    abort_message = ''
     57    CALL abort_gcm (modname,abort_message,1)
     58  ENDIF
    6559
    66       IF (ngrid.NE.klon_glo) THEN
    67          write(lunout,*) 'STOP in ',trim(modname)
    68          write(lunout,*) 'Problem with dimensions :'
    69          write(lunout,*) 'ngrid     = ',ngrid
    70          write(lunout,*) 'klon   = ',klon_glo
    71          abort_message = ''
    72          CALL abort_gcm (modname,abort_message,1)
    73       ENDIF
     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
    7468
    75 !$OMP PARALLEL PRIVATE(ibegin,iend)
    76 !$OMP+         SHARED(parea,pcu,pcv,plon,plat)
     69  !$OMP PARALLEL PRIVATE(ibegin,iend) &
     70  !$OMP          SHARED(parea,pcu,pcv,plon,plat)
    7771     
    78       offset=klon_mpi_begin-1
    79       airephy(1:klon_omp)=parea(offset+klon_omp_begin:
    80      &                          offset+klon_omp_end)
    81       cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
    82       cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
    83       rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
    84       rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
     72  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)
    8578
    86 ! copy some fundamental parameters to physics
    87       rradius=prad
    88       rg=pg
    89       rr=pr
    90       rcpp=pcpp
     79  ! copy some fundamental parameters to physics
     80  rradius=prad
     81  rg=pg
     82  rr=pr
     83  rcpp=pcpp
    9184
    92 !$OMP END PARALLEL
     85  !$OMP END PARALLEL
    9386
    94 !      print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
    95 !      print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
     87  ! Additional initializations for aquaplanets
     88  !$OMP PARALLEL
     89  IF (iflag_phys>=100) THEN
     90    CALL iniaqua(klon_omp,rlatd,rlond,iflag_phys)
     91  ENDIF
     92  !$OMP END PARALLEL
    9693
    97 ! Additional initializations for aquaplanets
    98 !$OMP PARALLEL
    99       if (iflag_phys>=100) then
    100         call iniaqua(klon_omp,rlatd,rlond,iflag_phys)
    101       endif
    102 !$OMP END PARALLEL
    103 
    104 !      RETURN
    105 !9999  CONTINUE
    106 !      abort_message ='Cette version demande les fichier rnatur.dat
    107 !     & et surf.def'
    108 !      CALL abort_gcm (modname,abort_message,1)
    109 
    110       END
     94END SUBROUTINE iniphysiq
Note: See TracChangeset for help on using the changeset viewer.