Changeset 4218 for dynamico_lmdz


Ignore:
Timestamp:
Jan 7, 2020, 7:01:18 PM (5 years ago)
Author:
dubos
Message:

simple_physics : cleanup iniphysiq_param

File:
1 moved

Legend:

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

    r4217 r4218  
     1!
     2! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $                 
     3!
    14!                                                                       
    2 ! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $                 
    3 !                                                                       
    4 !                                                                       
    5 !                                                                       
    6       SUBROUTINE iniphysiq_param(ngrid,nlayer,                          &
    7      &           punjours,                                              &
    8      &           pdayref,ptimestep,                                     &
    9      &           plat,plon,parea,pcu,pcv,                               &
    10      &           prad,pg,pr,pcpp,iflag_phys)                           
    11       USE dimphy
    12       USE mod_grid_phy_lmdz
    13       USE mod_phys_lmdz_para
    14       USE geometry_mod, ONLY: cell_area, latitude_deg, longitude_deg
    15 !      USE inigeomphy_mod, ONLY : lonfi,latfi                           
    16                                                                        
    17                                                                        
    18       IMPLICIT NONE
    19 !                                                                       
    20 !=======================================================================
    21 !                                                                       
    22 !   subject:                                                           
    23 !   --------                                                           
    24 !                                                                       
    25 !   Initialisation for the physical parametrisations of the LMD         
    26 !   martian atmospheric general circulation modele.                     
    27 !                                                                       
    28 !   author: Frederic Hourdin 15 / 10 /93                               
    29 !   -------                                                             
    30 !                                                                       
    31 !   arguments:                                                         
    32 !   ----------                                                         
    33 !                                                                       
    34 !   input:                                                             
    35 !   ------                                                             
    36 !                                                                       
    37 !    ngrid                 Size of the horizontal grid.                 
    38 !                          All internal loops are performed on that grid
    39 !    nlayer                Number of vertical layers.                   
    40 !    pdayref               Day of reference for the simulation         
    41 !    firstcall             True at the first call                       
    42 !    lastcall              True at the last call                       
    43 !    pday                  Number of days counted from the North. Spring
    44 !                          equinoxe.                                   
    45 !                                                                       
    46 !=======================================================================
    47 !                                                                       
    48 !-----------------------------------------------------------------------
    49 !   declarations:                                                       
    50 !   -------------                                                       
    51                                                                        
    52       REAL prad,pg,pr,pcpp,punjours
    53                                                                        
    54       INTEGER ngrid,nlayer,iflag_phys
    55       REAL plat(ngrid),plon(ngrid),parea(klon_glo)
    56       REAL pcu(klon_glo),pcv(klon_glo)
    57       INTEGER pdayref
    58       INTEGER :: ibegin,iend,offset,indmin,indmax
    59       REAL pi
    60                                                                        
    61       REAL ptimestep
    62       CHARACTER (LEN=20) :: modname='iniphysiq'
    63       CHARACTER (LEN=80) :: abort_message
    64                                                                        
    65       pi=2.*asin(1.)
    66       print*,'INInnn ENTREE DANS INIPHYSIQ'
    67       IF (nlayer.NE.klev) THEN
    68          PRINT*,'STOP in inifis'
    69          PRINT*,'Probleme de dimensions :'
    70          PRINT*,'nlayer     = ',nlayer
    71          PRINT*,'klev   = ',klev
    72          abort_message = ''
    73          CALL abort_gcm (modname,abort_message,1)
    74       ENDIF
    75                                                                        
    76       IF (ngrid.NE.klon_omp) THEN
    77          PRINT*,'STOP in inifis'
    78          PRINT*,'Probleme de dimensions :'
    79          PRINT*,'ngrid     = ',ngrid
    80          PRINT*,'klon   = ',klon_omp
    81          abort_message = ''
    82          CALL abort_gcm (modname,abort_message,1)
    83       ENDIF
    84 !$OMP PARALLEL PRIVATE(ibegin,iend)                                     
    85 !$OMP+         SHARED(parea,pcu,pcv,plon,plat)                         
    86                                                                        
    87       print*,'Dans iniphysiq '
    88       offset=klon_mpi_begin-1
    89       indmin=offset+klon_omp_begin
    90       indmax=offset+klon_omp_end
    91        print*,'latitude0 deg ',latitude_deg(1),latitude_deg(klon_omp)
    92                                                                        
    93       CALL iniphyparam(ngrid,nlayer,                                    &
    94      &           punjours,                                              &
    95      &           pdayref,ptimestep,                                     &
    96      &           prad,pg,pr,pcpp)                                       
    97                                                                        
    98                                                                        
    99       print*,'OK iniphyparam ',size(plat)
    100                                                                        
    101 !$OMP END PARALLEL                                                     
    102                                                                        
    103       print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
    104       print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
    105                                                                        
    106       RETURN
    107  9999 CONTINUE
    108       abort_message ='Cette version demande les fichier rnatur.dat      &
    109      & et surf.def'                                                     
    110       CALL abort_gcm (modname,abort_message,1)
    111                                                                        
    112                                                                        
    113       END                                           
     5!
     6
     7SUBROUTINE iniphysiq_param(ngrid,nlayer,  &
     8     &           punjours,                &
     9     &           pdayref,ptimestep,       &
     10     &           prad,pg,pr,pcpp)
     11  USE dimphy,             ONLY : klev
     12  USE mod_phys_lmdz_para, ONLY : klon_omp
     13 
     14  INTEGER, INTENT(IN) :: &                                                                       
     15       ngrid,   & ! Size of the horizontal grid.                 
     16       nlayer,  & ! Number of vertical layers.                   
     17       pdayref    ! Day of reference for the simulation
     18  REAL, INTENT(IN) :: ptimestep, prad, pg, pr, pcpp, punjours
     19 
     20  CHARACTER(LEN=20), PARAMETER :: modname='iniphysiq'
     21  CHARACTER(LEN=80) :: abort_message
     22 
     23  print*,'INInnn ENTREE DANS INIPHYSIQ'
     24  IF (nlayer.NE.klev) THEN
     25     PRINT*,'STOP in inifis'
     26     PRINT*,'Probleme de dimensions :'
     27     PRINT*,'nlayer     = ',nlayer
     28     PRINT*,'klev   = ',klev
     29     abort_message = ''
     30     CALL abort_gcm (modname,abort_message,1)
     31  ENDIF
     32 
     33  IF (ngrid.NE.klon_omp) THEN
     34     PRINT*,'STOP in inifis'
     35     PRINT*,'Probleme de dimensions :'
     36     PRINT*,'ngrid     = ',ngrid
     37     PRINT*,'klon   = ',klon_omp
     38     abort_message = ''
     39     CALL abort_gcm (modname,abort_message,1)
     40  ENDIF
     41 
     42  !$OMP PARALLEL   
     43  print*,'Dans iniphysiq '
     44 
     45  CALL iniphyparam(ngrid,nlayer,        &
     46       &           punjours,            &
     47       &           pdayref,ptimestep,   &
     48       &           prad,pg,pr,pcpp)                                       
     49 
     50 
     51  print*,'OK iniphyparam '   
     52  !$OMP END PARALLEL                                                     
     53 
     54  print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
     55  print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
     56 
     57END SUBROUTINE iniphysiq_param
Note: See TracChangeset for help on using the changeset viewer.