Ignore:
Timestamp:
Nov 21, 2017, 4:03:44 PM (7 years ago)
Author:
emillour
Message:

Common dynamics:

  • enable possiblity to store multiple time steps in the restart.nc file (flag "ecritstart" gives the frequency, in dynamical steps).
  • fixed dynredem_mod.F90 to correctly write multiple time steps.
  • fixed computation of JH_cur in the mars case where "hour_ini" contains the initial time of day read from the start.nc file
  • minor fix in dynetat0.F90

RY

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r1703 r1824  
    1919     &                       dissip_period,offline,ip_ebil_dyn,
    2020     &                       ok_dynzon,periodav,ok_dyn_ave,iecri,
    21      &                       ok_dyn_ins,output_grads_dyn
     21     &                       ok_dyn_ins,output_grads_dyn,ecritstart
    2222      use exner_hyb_m, only: exner_hyb
    2323      use exner_milieu_m, only: exner_milieu
     
    3131     .                  statcl,conser,apdiss,purmats,tidal,ok_strato
    3232      USE temps_mod, ONLY: jD_ref,jH_ref,itaufin,day_ini,day_ref,
    33      .                  start_time,dt
     33     .                  start_time,dt,hour_ini
    3434
    3535      IMPLICIT NONE
     
    131131c   variables pour le fichier histoire
    132132!      REAL dtav      ! intervalle de temps elementaire
     133      LOGICAL lrestart
    133134
    134135      REAL tppn(iim),tpps(iim),tpn,tps
     
    289290c   ----------------------------------
    290291
     292c     RMBY: check that hour_ini and start_time are not both non-zero
     293      if ((hour_ini.ne.0.0).and.(start_time.ne.0.0)) then
     294        write(*,*) "ERROR: hour_ini = ", hour_ini,
     295     &             "start_time = ", start_time
     296        abort_message = 'hour_ini and start_time both nonzero'
     297        call abort_gcm(modname,abort_message,1)
     298      endif
     299
    291300   1  CONTINUE ! Matsuno Forward step begins here
    292301
     
    296305      jD_cur = jD_ref + day_ini - day_ref +                             &
    297306     &          (itau+1)/day_step
    298       jH_cur = jH_ref + start_time +                                    &
    299      &          mod(itau+1,day_step)/float(day_step)
     307      IF (planet_type .eq. "mars") THEN
     308        jH_cur = jH_ref + hour_ini +                                    &
     309     &           mod(itau+1,day_step)/float(day_step)
     310      ELSE
     311        jH_cur = jH_ref + start_time +                                  &
     312     &           mod(itau+1,day_step)/float(day_step)
     313      ENDIF
    300314      jD_cur = jD_cur + int(jH_cur)
    301315      jH_cur = jH_cur - int(jH_cur)
     
    351365        jD_cur = jD_ref + day_ini - day_ref +
    352366     &            (itau+1)/day_step
    353         jH_cur = jH_ref + start_time +
    354      &            mod(itau+1,day_step)/float(day_step)
     367        IF (planet_type .eq. "mars") THEN
     368          jH_cur = jH_ref + hour_ini +
     369     &             mod(itau+1,day_step)/float(day_step)
     370        ELSE
     371          jH_cur = jH_ref + start_time +
     372     &             mod(itau+1,day_step)/float(day_step)
     373        ENDIF
    355374        jD_cur = jD_cur + int(jH_cur)
    356375        jH_cur = jH_cur - int(jH_cur)
     
    529548           ENDIF
    530549
    531            jH_cur = jH_ref + start_time +                               &
    532      &          mod(itau+1,day_step)/float(day_step)
    533            IF ((planet_type .eq."generic").or.
    534      &         (planet_type .eq."mars")) THEN
     550           IF (planet_type .eq. "mars") THEN
     551             jH_cur = jH_ref + hour_ini +                                 &
     552     &                mod(itau,day_step)/float(day_step)
     553           ELSE IF (planet_type .eq. "generic") THEN
    535554             jH_cur = jH_ref + start_time +                               &
    536      &          mod(itau,day_step)/float(day_step)
     555     &                mod(itau,day_step)/float(day_step)
     556           ELSE
     557             jH_cur = jH_ref + start_time +                               &
     558     &                mod(itau+1,day_step)/float(day_step)
    537559           ENDIF
    538560           jD_cur = jD_cur + int(jH_cur)
     
    861883            ENDIF ! of IF(MOD(itau,iecri).EQ.0)
    862884
    863             IF(itau.EQ.itaufin) THEN
    864 
     885c           Determine whether to write to the restart.nc file
     886c           Decision can't be made in one IF statement as if
     887c           ecritstart==0 there will be a divide-by-zero error
     888            lrestart = .false.
     889            IF (itau.EQ.itaufin) THEN
     890              lrestart = .true.
     891            ELSE IF (ecritstart.GT.0) THEN
     892              IF (MOD(itau,ecritstart).EQ.0) lrestart  = .true.
     893            ENDIF
     894
     895c           Write to the restart.nc file
     896            IF (lrestart) THEN
    865897              if (planet_type=="mars") then
    866898                CALL dynredem1("restart.nc",REAL(itau)/REAL(day_step),
     
    872904              CLOSE(99)
    873905              !!! Ehouarn: Why not stop here and now?
    874             ENDIF ! of IF (itau.EQ.itaufin)
     906            ENDIF ! of IF (lrestart)
    875907
    876908c-----------------------------------------------------------------------
     
    9921024              ENDIF ! of IF(MOD(itau,iecri         ).EQ.0)
    9931025
    994               IF(itau.EQ.itaufin) THEN
     1026c             Determine whether to write to the restart.nc file
     1027c             Decision can't be made in one IF statement as if
     1028c             ecritstart==0 there will be a divide-by-zero error
     1029              lrestart = .false.
     1030              IF (itau.EQ.itaufin) THEN
     1031                lrestart = .true.
     1032              ELSE IF (ecritstart.GT.0) THEN
     1033                IF (MOD(itau,ecritstart).EQ.0) lrestart = .true.
     1034              ENDIF
     1035
     1036c             Write to the restart.nc file
     1037              IF (lrestart) THEN
    9951038                if (planet_type=="mars") then
    9961039                  CALL dynredem1("restart.nc",REAL(itau)/REAL(day_step),
     
    10001043     &                         vcov,ucov,teta,q,masse,ps)
    10011044                endif
    1002               ENDIF ! of IF(itau.EQ.itaufin)
     1045              ENDIF ! of IF (lrestart)
    10031046
    10041047              forward = .TRUE.
Note: See TracChangeset for help on using the changeset viewer.