Changeset 4217 for dynamico_lmdz


Ignore:
Timestamp:
Jan 7, 2020, 6:39:22 PM (5 years ago)
Author:
dubos
Message:

simple_physics : converted iniphysiq_param to F90

Location:
dynamico_lmdz/simple_physics/phyparam
Files:
2 moved

Legend:

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

    r4196 r4217  
    1 !
    2 ! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
    3 !
    4 c
    5 c
    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 c
    20 c=======================================================================
    21 c
    22 c   subject:
    23 c   --------
    24 c
    25 c   Initialisation for the physical parametrisations of the LMD
    26 c   martian atmospheric general circulation modele.
    27 c
    28 c   author: Frederic Hourdin 15 / 10 /93
    29 c   -------
    30 c
    31 c   arguments:
    32 c   ----------
    33 c
    34 c   input:
    35 c   ------
    36 c
    37 c    ngrid                 Size of the horizontal grid.
    38 c                          All internal loops are performed on that grid.
    39 c    nlayer                Number of vertical layers.
    40 c    pdayref               Day of reference for the simulation
    41 c    firstcall             True at the first call
    42 c    lastcall              True at the last call
    43 c    pday                  Number of days counted from the North. Spring
    44 c                          equinoxe.
    45 c
    46 c=======================================================================
    47 c
    48 c-----------------------------------------------------------------------
    49 c   declarations:
    50 c   -------------
    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.)
     1!                                                                       
     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.) 
    6666      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 c$OMP PARALLEL PRIVATE(ibegin,iend)
    85 c$OMP+         SHARED(parea,pcu,pcv,plon,plat)
    86      
    87       print*,'Dans iniphysiq '
    88       offset=klon_mpi_begin-1
    89 !     cell_area(1:klon_omp)=parea(offset+klon_omp_begin:
    90 !    &                          offset+klon_omp_end)
    91       !cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
    92       !cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
    93       indmin=offset+klon_omp_begin
    94       indmax=offset+klon_omp_end
    95 !     longitude_deg(1:klon_omp)=180./pi*lonfi(indmin:indmax)
    96 !     latitude_deg(1:klon_omp)=180./pi*latfi(indmin:indmax)
    97        print*,'latitude0 deg ',latitude_deg(1),latitude_deg(klon_omp)
    98 
    99 !     call suphel
    100 !     prad,pg,pr,pcpp
    101 !      rradius=prad
    102 !      rg=pg
    103 !      rr=pr
    104 !      rcpp=pcpp
    105 
    106 !     return
    107      
    108       CALL iniphyparam(ngrid,nlayer,
    109      $           punjours,
    110      $           pdayref,ptimestep,
    111      $           prad,pg,pr,pcpp)
    112 
    113 
    114       print*,'OK iniphyparam ',size(plat)
    115 
    116 c$OMP END PARALLEL
    117 
    118       print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
    119       print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
    120 
    121       RETURN
    122 9999  CONTINUE
    123       abort_message ='Cette version demande les fichier rnatur.dat
    124      & et surf.def'
    125       CALL abort_gcm (modname,abort_message,1)
    126 
    127 
    128       END
     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                                           
Note: See TracChangeset for help on using the changeset viewer.