Changeset 1824


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

Location:
trunk/LMDZ.COMMON
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/ioipsl/install_ioipsl_ifort.bash

    r1567 r1824  
    44
    55#0. Preliminary stuff
     6NETCDF="/opt/netcdf3/ifort"
    67netcdf_include="$NETCDF/include"
    78netcdf_lib="$NETCDF/lib"
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F90

    r1650 r1824  
    1616                         offline, ok_dyn_ave, ok_dyn_ins, ok_dynzon, &
    1717                         output_grads_dyn, periodav, planet_type, &
    18                          raz_date, resetvarc, starttime, timestart
     18                         raz_date, resetvarc, starttime, timestart, &
     19                         ecritstart
    1920  USE infotrac, ONLY : type_trac
    2021  use assert_m, only: assert
     
    183184  call getin("timestart",timestart)
    184185     
     186!Config  Key  = ecritstart
     187!Config  Desc = Mars - frequency of restart.nc output (dyn timesteps)
     188!Config  Def  = 0
     189!Config  Help = Mars - frequency of restart.nc output (dyn timesteps)
     190  ecritstart = 0
     191  CALL getin('ecritstart',ecritstart)
     192
    185193!Config  Key  = less1day
    186194!Config  Desc = Possibilite d'integrer moins d'un jour
  • 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.
  • trunk/LMDZ.COMMON/libf/dyn3d_common/dynetat0.F90

    r1508 r1824  
    307307    s1='value of '//TRIM(str1)//' ='
    308308    s2=' read in starting file differs from parametrized '//TRIM(str2)//' ='
    309     WRITE(msg,'(10x,a,i4,2x,a,i4)'),s1,n1,s2,n2
     309    WRITE(msg,'(10x,a,i4,2x,a,i4)')TRIM(s1),n1,TRIM(s2),n2
    310310    CALL ABORT_gcm(TRIM(modname),TRIM(msg),1)
    311311  END IF
  • trunk/LMDZ.COMMON/libf/dyn3d_common/dynredem_mod.F90

    r1508 r1824  
    3434  INTEGER :: start(4), count(4)
    3535!===============================================================================
    36   start(:)=[1,1,1,1]; count(:)=[iip1,jjp1,ll,nb]
     36  IF (ll.eq.1) THEN
     37    start(:)=[1,1,nb,1]
     38    count(:)=[iip1,jjp1,1,1]
     39  ELSE
     40    start(:)=[1,1,1,nb]
     41    count(:)=[iip1,jjp1,ll,1]
     42  ENDIF
    3743  CALL err(NF90_INQ_VARID(ncid,id,nvarid),"inq",id)
    3844  CALL err(NF90_PUT_VAR(ncid,nvarid,var,start,count),"put",id)
     
    6066  INTEGER :: start(4), count(4)
    6167!===============================================================================
    62   start(:)=[1,1,1,1]; count(:)=[iip1,jjm,ll,nb]
     68  IF (ll.eq.1) THEN
     69    start(:)=[1,1,nb,1]
     70    count(:)=[iip1,jjm,1,1]
     71  ELSE
     72    start(:)=[1,1,1,nb]
     73    count(:)=[iip1,jjm,ll,1]
     74  ENDIF
    6375  CALL err(NF90_INQ_VARID(ncid,id,nvarid),"inq",id)
    6476  CALL err(NF90_PUT_VAR(ncid,nvarid,var,start,count),"put",id)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F90

    r1650 r1824  
    205205  timestart=-9999 ! default value; if <0, use last stored time
    206206  call getin("timestart",timestart)
    207      
     207
     208!Config  Key  = ecritstart
     209!Config  Desc = Mars - frequency of restart.nc output (dyn timesteps)
     210!Config  Def  = 0
     211!Config  Help = Mars - frequency of restart.nc output (dyn timesteps)
     212  ecritstart = 0
     213  CALL getin('ecritstart',ecritstart)
     214
    208215!Config  Key  = less1day
    209216!Config  Desc = Possibilite d'integrer moins d'un jour
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r1703 r1824  
    2929     &                       ok_dynzon,periodav,ok_dyn_ave,iecri,
    3030     &                       ok_dyn_ins,output_grads_dyn,
    31      &                       iapp_tracvl
     31     &                       iapp_tracvl,ecritstart
    3232       use cpdet_mod, only: cpdet,tpot2t_glo_p,t2tpot_glo_p
    3333       use sponge_mod_p, only: callsponge,mode_sponge,sponge_p
     
    3939     .                  statcl,conser,apdiss,purmats,tidal,ok_strato
    4040       USE temps_mod, ONLY: itaufin,jD_ref,jH_ref,day_ini,
    41      .                  day_ref,start_time,dt
     41     .                  day_ref,start_time,dt,hour_ini
    4242
    4343
     
    141141c   variables pour le fichier histoire
    142142      REAL dtav      ! intervalle de temps elementaire
     143      LOGICAL lrestart
    143144
    144145      REAL tppn(iim),tpps(iim),tpn,tps
     
    304305c et du parallelisme !!
    305306
     307c     RMBY: check that hour_ini and start_time are not both non-zero
     308      if ((hour_ini.ne.0.0).and.(start_time.ne.0.0)) then
     309        write(*,*) "ERROR: hour_ini = ", hour_ini,
     310     &             "start_time = ", start_time
     311        abort_message = 'hour_ini and start_time both nonzero'
     312        call abort_gcm(modname,abort_message,1)
     313      endif
     314
    306315   1  CONTINUE ! Matsuno Forward step begins here
    307316
     
    311320      jD_cur = jD_ref + day_ini - day_ref +                             &
    312321     &          (itau+1)/day_step
    313       jH_cur = jH_ref + start_time +                                    &
    314      &         mod(itau+1,day_step)/float(day_step)
     322      IF (planet_type .eq. "mars") THEN
     323        jH_cur = jH_ref + hour_ini +                                    &
     324     &           mod(itau+1,day_step)/float(day_step)
     325      ELSE
     326        jH_cur = jH_ref + start_time +                                  &
     327     &           mod(itau+1,day_step)/float(day_step)
     328      ENDIF
    315329      if (jH_cur > 1.0 ) then
    316330        jD_cur = jD_cur +1.
     
    416430        jD_cur = jD_ref + day_ini - day_ref +
    417431     &            (itau+1)/day_step
    418         jH_cur = jH_ref + start_time +
    419      &           mod(itau+1,day_step)/float(day_step)
     432        IF (planet_type .eq. "mars") THEN
     433          jH_cur = jH_ref + hour_ini +
     434     &             mod(itau+1,day_step)/float(day_step)
     435        ELSE
     436          jH_cur = jH_ref + start_time +
     437     &             mod(itau+1,day_step)/float(day_step)
     438        ENDIF
    420439        if (jH_cur > 1.0 ) then
    421440          jD_cur = jD_cur +1.
     
    873892           ENDIF
    874893
    875            jH_cur = jH_ref + start_time +                                &
    876      &              mod(itau+1,day_step)/float(day_step)
    877            IF ((planet_type .eq."generic").or.
    878      &         (planet_type .eq."mars")) THEN
    879              jH_cur = jH_ref + start_time +                               &
    880      &          mod(itau,day_step)/float(day_step)
     894           IF (planet_type .eq. "mars") THEN
     895             jH_cur = jH_ref + hour_ini +                               &
     896     &                mod(itau,day_step)/float(day_step)
     897           ELSE IF (planet_type .eq. "generic") THEN
     898             jH_cur = jH_ref + start_time +                             &
     899     &                mod(itau,day_step)/float(day_step)
     900           ELSE
     901             jH_cur = jH_ref + start_time +                             &
     902     &                mod(itau+1,day_step)/float(day_step)
    881903           ENDIF
    882904           if (jH_cur > 1.0 ) then
     
    17561778            ENDIF ! of IF(MOD(itau,iecri).EQ.0)
    17571779
    1758             IF(itau.EQ.itaufin) THEN
    1759 
    1760 c$OMP BARRIER
    1761 c$OMP MASTER
    1762 
     1780c           Determine whether to write to the restart.nc file
     1781c           Decision can't be made in one IF statement as if
     1782c           ecritstart==0 there will be a divide-by-zero error
     1783            lrestart = .false.
     1784            IF (itau.EQ.itaufin) THEN
     1785              lrestart = .true.
     1786            ELSE IF (ecritstart.GT.0) THEN
     1787              IF (MOD(itau,ecritstart).EQ.0) lrestart  = .true.
     1788            ENDIF
     1789
     1790c           Write to restart.nc if required
     1791            IF (lrestart) THEN
     1792c$OMP BARRIER
     1793c$OMP MASTER
    17631794              if (planet_type=="mars") then
    17641795                CALL dynredem1_p("restart.nc",REAL(itau)/REAL(day_step),
     
    17701801!              CLOSE(99)
    17711802c$OMP END MASTER
    1772             ENDIF ! of IF (itau.EQ.itaufin)
     1803            ENDIF ! of IF (lrestart)
    17731804
    17741805c-----------------------------------------------------------------------
     
    19611992              ENDIF ! of IF(MOD(itau,iecri).EQ.0)
    19621993
    1963               IF(itau.EQ.itaufin) THEN
     1994c             Determine whether to write to the restart.nc file
     1995c             Decision can't be made in one IF statement as if
     1996c             ecritstart==0 there will be a divide-by-zero error
     1997              lrestart = .false.
     1998              IF (itau.EQ.itaufin) THEN
     1999                lrestart = .true.
     2000              ELSE IF (ecritstart.GT.0) THEN
     2001                IF (MOD(itau,ecritstart).EQ.0) lrestart  = .true.
     2002              ENDIF
     2003
     2004c             Write to restart.nc if required
     2005              IF (lrestart) THEN
    19642006c$OMP MASTER
    19652007                if (planet_type=="mars") then
     
    19702012                  CALL dynredem1_p("restart.nc",start_time,
    19712013     &                               vcov,ucov,teta,q,masse,ps)
    1972                
    19732014                endif
    19742015c$OMP END MASTER
    1975               ENDIF ! of IF(itau.EQ.itaufin)
     2016              ENDIF ! of IF (lrestart)
    19762017
    19772018              forward = .TRUE.
Note: See TracChangeset for help on using the changeset viewer.