Ignore:
Timestamp:
Sep 11, 2024, 6:03:07 PM (9 days ago)
Author:
abarral
Message:

Encapsulate files in modules

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/replay3d.F90

    r5159 r5186  
    1 
    21! $Id: gcm.F90 3579 2019-10-09 13:11:07Z fairhead $
    32
     
    65PROGRAM replay3d
    76
    8 
    9 
    10 USE comvert_mod, ONLY:  preff, pa
    11 USE inigeomphy_mod, ONLY: inigeomphy
    12 
     7  USE comvert_mod, ONLY: preff, pa
     8  USE inigeomphy_mod, ONLY: inigeomphy
    139
    1410  USE control_mod
    15   USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref, &
    16                      itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end
     11  USE temps_mod, ONLY: calend, start_time, annee_ref, day_ref, &
     12          itau_dyn, itau_phy, day_ini, jD_ref, jH_ref, day_end
    1713  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
    1814  USE logic_mod, ONLY: ecripar, iflag_phys, read_start
    1915
    20   USE serre_mod, ONLY: clon,clat,transx,transy,alphax,alphay,pxo,pyo,              &
    21         grossismx, grossismy, dzoomx, dzoomy,taux,tauy
     16  USE serre_mod, ONLY: clon, clat, transx, transy, alphax, alphay, pxo, pyo, &
     17          grossismx, grossismy, dzoomx, dzoomy, taux, tauy
    2218  USE mod_const_mpi, ONLY: comm_lmdz
    2319  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     
    2723  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
    2824  USE lmdz_paramet
     25  USE lmdz_conf_gcm, ONLY: conf_gcm
     26
    2927  IMPLICIT NONE
    3028
     
    5957  !   -------------
    6058
    61 
    62 
    63 
    6459  REAL zdtvr
    6560
     
    7469  LOGICAL lafin
    7570
    76   INTEGER :: ntime=10000,it,klon,klev
     71  INTEGER :: ntime = 10000, it, klon, klev
    7772
    7873
     
    8984  !  ---------------------------------------
    9085
    91 preff=101325.
    92  pa=50000.
    93  clon=0.
    94  clat=0.
    95  taux=3.
    96  tauy=3.
    97  dzoomx=0.1
    98  dzoomy=0.1
    99  grossismx=1.
    100  grossismx=1.
    101  transx=0.
    102  transy=0.
     86  preff = 101325.
     87  pa = 50000.
     88  clon = 0.
     89  clat = 0.
     90  taux = 3.
     91  tauy = 3.
     92  dzoomx = 0.1
     93  dzoomy = 0.1
     94  grossismx = 1.
     95  grossismx = 1.
     96  transx = 0.
     97  transy = 0.
    10398
    104   CALL conf_gcm( 99, .TRUE.)
     99  CALL conf_gcm(99, .TRUE.)
    105100
    106101  IF (mod(iphysiq, iperiod) /= 0) CALL abort_gcm("conf_gcm", &
    107        "iphysiq must be a multiple of iperiod", 1)
     102          "iphysiq must be a multiple of iperiod", 1)
    108103
    109  rad=6400000
    110 g=9.81
     104  rad = 6400000
     105  g = 9.81
    111106
    112107
     
    128123  !  on recalcule eventuellement le pas de temps
    129124
    130 
    131   zdtvr    = daysec/REAL(day_step)
     125  zdtvr = daysec / REAL(day_step)
    132126
    133127  ! on remet le calendrier \`a zero si demande
    134128
    135      annee_ref = anneeref
    136      day_ref = dayref
    137      day_ini = dayref
    138      itau_dyn = 0
    139      itau_phy = 0
    140      time_0 = 0.
     129  annee_ref = anneeref
     130  day_ref = dayref
     131  day_ini = dayref
     132  itau_dyn = 0
     133  itau_phy = 0
     134  time_0 = 0.
    141135
    142136  mois = 1
    143137  heure = 0.
    144 ! CALL ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
     138  ! CALL ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
    145139  jH_ref = jD_ref - int(jD_ref)
    146140  jD_ref = int(jD_ref)
    147141
     142  dtvr = zdtvr
     143  CALL iniconst
     144  PRINT*, 'APRES inisconst'
     145  CALL inigeom
    148146
     147  CALL inigeomphy(iim, jjm, llm, &
     148          1, comm_lmdz, &
     149          rlatu, rlatv, &
     150          rlonu, rlonv, &
     151          aire, cu, cv)
    149152
    150      dtvr = zdtvr
    151      CALL iniconst
    152      PRINT*,'APRES inisconst'
    153      CALL inigeom
     153  CALL suphel
     154  !open(82,file='dump_param.bin',form='unformatted',status='old')
    154155
     156  CALL iophys_ini(900.)
     157  PRINT*, 'Rlatu=', rlatu
     158  klon = 2 + iim * (jjm - 1)
     159  klev = llm
    155160
    156   CALL inigeomphy(iim,jjm,llm, &
    157                1, comm_lmdz, &
    158                rlatu,rlatv, &
    159                rlonu,rlonv, &
    160                aire,cu,cv)
     161  !---------------------------------------------------------------------
     162  ! Initialisation de la parametrisation
     163  !---------------------------------------------------------------------
     164  CALL call_ini_replay
    161165
    162 CALL suphel
    163 !open(82,file='dump_param.bin',form='unformatted',status='old')
    164 
    165 
    166 
    167      CALL iophys_ini(900.)
    168 PRINT*,'Rlatu=',rlatu
    169 klon=2+iim*(jjm-1)
    170 klev=llm
    171 
    172 !---------------------------------------------------------------------
    173 ! Initialisation de la parametrisation
    174 !---------------------------------------------------------------------
    175       CALL call_ini_replay
    176 
    177 !---------------------------------------------------------------------
    178 ! Boucle en temps sur l'appel à la parametrisation
    179 !---------------------------------------------------------------------
    180       DO it=1,ntime
    181          PRINT*,'Pas de temps ',it,klon,klev
    182          CALL call_param_replay(klon,klev)
    183       ENDDO
    184 
     166  !---------------------------------------------------------------------
     167  ! Boucle en temps sur l'appel à la parametrisation
     168  !---------------------------------------------------------------------
     169  DO it = 1, ntime
     170    PRINT*, 'Pas de temps ', it, klon, klev
     171    CALL call_param_replay(klon, klev)
     172  ENDDO
    185173
    186174END PROGRAM replay3d
Note: See TracChangeset for help on using the changeset viewer.