Ignore:
Timestamp:
Jan 5, 2012, 8:28:41 AM (13 years ago)
Author:
emillour
Message:

Common dynamics: updates to keep up with LMDZ5 Earth (rev 1605)
See file "DOC/chantiers/commit_importants.log" for details.
EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/ce0l.F90

    r270 r492  
    2828  IMPLICIT NONE
    2929#ifndef CPP_EARTH
    30   WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
     30  WRITE(*,*)'limit_netcdf: Earth-specific program, needs Earth physics'
    3131#else
    3232!-------------------------------------------------------------------------------
     
    6767#endif
    6868
    69   IF (config_inca /= 'none') THEN
     69  IF (type_trac == 'inca') THEN
    7070#ifdef INCA
    7171    CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F

    r270 r492  
    1313      use ioipsl_getincom
    1414#endif
     15      USE infotrac, ONLY : type_trac
    1516      IMPLICIT NONE
    1617c-----------------------------------------------------------------------
     
    156157      nday = 10
    157158      CALL getin('nday',nday)
     159
     160!Config  Key  = starttime
     161!Config  Desc = Heure de depart de la simulation
     162!Config  Def  = 0
     163!Config  Help = Heure de depart de la simulation
     164!Config         en jour
     165      starttime = 0
     166      CALL getin('starttime',starttime)
    158167
    159168!Config  Key  = less1day
     
    600609       offline = .FALSE.
    601610       CALL getin('offline',offline)
     611     
     612!Config  Key  = type_trac
     613!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     614!Config  Def  = lmdz
     615!Config  Help =
     616!Config         'lmdz' = pas de couplage, pur LMDZ
     617!Config         'inca' = model de chime INCA
     618!Config         'repr' = model de chime REPROBUS
     619      type_trac = 'lmdz'
     620      CALL getin('type_trac',type_trac)
    602621
    603622!Config  Key  = config_inca
     
    677696      write(lunout,*)' tauyy = ', tauyy
    678697      write(lunout,*)' offline = ', offline
     698      write(lunout,*)' type_trac = ', type_trac
    679699      write(lunout,*)' config_inca = ', config_inca
    680700      write(lunout,*)' ok_dynzon = ', ok_dynzon
     
    795815       offline = .FALSE.
    796816       CALL getin('offline',offline)
     817
     818!Config  Key  = type_trac
     819!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     820!Config  Def  = lmdz
     821!Config  Help =
     822!Config         'lmdz' = pas de couplage, pur LMDZ
     823!Config         'inca' = model de chime INCA
     824!Config         'repr' = model de chime REPROBUS
     825      type_trac = 'lmdz'
     826      CALL getin('type_trac',type_trac)
    797827
    798828!Config  Key  = config_inca
     
    921951      write(lunout,*)' tauy = ', tauy
    922952      write(lunout,*)' offline = ', offline
     953      write(lunout,*)' type_trac = ', type_trac
    923954      write(lunout,*)' config_inca = ', config_inca
    924955      write(lunout,*)' ok_dynzon = ', ok_dynzon
  • trunk/LMDZ.COMMON/libf/dyn3d/control_mod.F90

    r270 r492  
    1010  IMPLICIT NONE
    1111
    12   REAL    :: periodav
     12  REAL    :: periodav, starttime
    1313  INTEGER :: nday,day_step,iperiod,iapp_tracvl,nsplit_phys
    1414  INTEGER :: iconser,iecri,dissip_period,iphysiq,iecrimoy
  • trunk/LMDZ.COMMON/libf/dyn3d/dynetat0.F

    r1 r492  
    119119      day_ini = tab_cntrl(30)
    120120      itau_dyn = tab_cntrl(31)
     121      start_time = tab_cntrl(32)
    121122c   .................................................................
    122123c
  • trunk/LMDZ.COMMON/libf/dyn3d/dynredem.F

    r6 r492  
    120120       tab_cntrl(30) = REAL(iday_end)
    121121       tab_cntrl(31) = REAL(itau_dyn + itaufin)
     122c start_time: start_time of simulation (not necessarily 0.)
     123       tab_cntrl(32) = start_time
    122124c
    123125c    .........................................................
     
    640642#endif
    641643
    642       IF (config_inca /= 'none') THEN
     644      IF (type_trac == 'inca') THEN
    643645! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    644646         ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac)
     
    653655      do iq=1,nqtot
    654656
    655          IF (config_inca == 'none') THEN
     657         IF (type_trac /= 'inca') THEN
    656658            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    657659            IF (ierr .NE. NF_NOERR) THEN
     
    665667            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    666668#endif
    667         ELSE ! config_inca = 'chem' ou 'aero'
     669        ELSE ! type_trac = inca
    668670! lecture de la valeur du traceur dans start_trac.nc
    669671           IF (ierr_file .ne. 2) THEN
     
    729731#endif
    730732          ENDIF ! (ierr_file .ne. 2)
    731        END IF   ! config_inca
     733       END IF   !type_trac
    732734     
    733735      ENDDO
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F

    r270 r492  
    223223c-----------------------------------------------------------------------
    224224
    225       IF (config_inca /= 'none') THEN
     225      IF (type_trac == 'inca') THEN
    226226#ifdef INCA
    227227      call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday,
     
    277277      endif ! of if (read_start)
    278278
    279       IF (config_inca /= 'none') THEN
     279      IF (type_trac == 'inca') THEN
    280280#ifdef INCA
    281281         call init_inca_dim(klon,llm,iim,jjm,
     
    319319C on remet le calendrier à zero si demande
    320320c
     321      IF (start_time /= starttime) then
     322        WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le'
     323     &,' fichier restart ne correspond pas à celle lue dans le run.def'
     324        IF (raz_date == 1) then
     325          WRITE(lunout,*)'Je prends l''heure lue dans run.def'
     326          start_time = starttime
     327        ELSE
     328          WRITE(lunout,*)'Je m''arrete'
     329          CALL abort
     330        ENDIF
     331      ENDIF
    321332      IF (raz_date == 1) THEN
    322333        annee_ref = anneeref
  • trunk/LMDZ.COMMON/libf/dyn3d/infotrac.F90

    r66 r492  
    3232  SUBROUTINE infotrac_init
    3333    USE control_mod
     34#ifdef REPROBUS
     35    USE CHEM_REP, ONLY : Init_chem_rep_trac
     36#endif
    3437    IMPLICIT NONE
    3538!=======================================================================
     
    8588   
    8689    IF (planet_type=='earth') THEN
    87      IF (config_inca=='none') THEN
    88        type_trac='lmdz'
     90     ! Coherence test between parameter type_trac, config_inca and preprocessing keys
     91     IF (type_trac=='inca') THEN
     92       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
     93            type_trac,' config_inca=',config_inca
     94       IF (config_inca/='aero' .AND. config_inca/='chem') THEN
     95          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
     96          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     97       END IF
     98#ifndef INCA
     99       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
     100       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
     101#endif
     102     ELSE IF (type_trac=='repr') THEN
     103       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
     104#ifndef REPROBUS
     105       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
     106       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
     107#endif
     108     ELSE IF (type_trac == 'lmdz') THEN
     109       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
    89110     ELSE
    90        type_trac='inca'
     111       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
     112       CALL abort_gcm('infotrac_init','bad parameter',1)
     113     END IF
     114
     115     ! Test if config_inca is other then none for run without INCA
     116     IF (type_trac/='inca' .AND. config_inca/='none') THEN
     117       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
     118       config_inca='none'
    91119     END IF
    92120    ELSE
    93121     type_trac='plnt'  ! planets... May want to dissociate between each later.
    94     ENDIF
     122    ENDIF ! of IF (planet_type=='earth')
    95123
    96124!-----------------------------------------------------------------------
     
    101129!-----------------------------------------------------------------------
    102130    IF (planet_type=='earth') THEN
    103      IF (type_trac == 'lmdz') THEN
     131     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    104132       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    105133       IF(ierr.EQ.0) THEN
    106           WRITE(lunout,*) 'Open traceur.def : ok'
     134          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
    107135          READ(90,*) nqtrue
    108136       ELSE
    109           WRITE(lunout,*) 'Problem in opening traceur.def'
    110           WRITE(lunout,*) 'ATTENTION using defaut values'
     137          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
     138          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
    111139          nqtrue=4 ! Defaut value
    112140       END IF
    113141       ! For Earth, water vapour & liquid tracers are not in the physics
    114142       nbtr=nqtrue-2
    115      ELSE
     143     ELSE ! type_trac=inca
    116144       ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
    117145       nqtrue=nbtr+2
     
    121149       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
    122150       CALL abort_gcm('infotrac_init','Not enough tracers',1)
     151     END IF
     152
     153! Transfert number of tracers to Reprobus
     154     IF (type_trac == 'repr') THEN
     155#ifdef REPROBUS
     156       CALL Init_chem_rep_trac(nbtr)
     157#endif
    123158     END IF
    124159
     
    173208!---------------------------------------------------------------------
    174209    IF (planet_type=='earth') THEN
    175      IF (type_trac == 'lmdz') THEN
     210     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    176211       IF(ierr.EQ.0) THEN
    177212          ! Continue to read tracer.def
  • trunk/LMDZ.COMMON/libf/dyn3d/iniacademic.F90

    r270 r492  
    209209        ! surface pressure
    210210        if (iflag_phys>2) then
    211            ps(:)=108080.  ! Earth aqua/terra planets
    212         else
     211           ! specific value for CMIP5 aqua/terra planets
     212           ! "Specify the initial dry mass to be equivalent to
     213           !  a global mean surface pressure (101325 minus 245) Pa."
     214           ps(:)=101080. 
     215        else
     216           ! use reference surface pressure
    213217           ps(:)=preff
    214218        endif
     219       
    215220        ! ground geopotential
    216221        phis(:)=0.
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r270 r492  
    270270   1  CONTINUE
    271271
    272       jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec)
    273       jH_cur = jH_ref +                                                 &
     272      jD_cur = jD_ref + day_ini - day_ref +                             &
     273     &          int (itau * dtvr / daysec)
     274      jH_cur = jH_ref + start_time +                                    &
    274275     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     276      jD_cur = jD_cur + int(jH_cur)
     277      jH_cur = jH_cur - int(jH_cur)
    275278
    276279
     
    422425!           rdaym_ini  = itau * dtvr / daysec
    423426!           rdayvrai   = rdaym_ini  + day_ini
    424            jD_cur = jD_ref + day_ini - day_ref
    425      $        + int (itau * dtvr / daysec)
    426            jH_cur = jH_ref +                                            &
    427      &              (itau * dtvr / daysec - int(itau * dtvr / daysec))
     427           jD_cur = jD_ref + day_ini - day_ref +                        &
     428     &          int (itau * dtvr / daysec)
     429           jH_cur = jH_ref + start_time +                               &
     430     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     431           jD_cur = jD_cur + int(jH_cur)
     432           jH_cur = jH_cur - int(jH_cur)
    428433!         write(lunout,*)'itau, jD_cur = ', itau, jD_cur, jH_cur
    429434!         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
     
    727732                call abort_gcm(modname,abort_message,0)
    728733              else
    729                 CALL dynredem1("restart.nc",0.0,
     734                CALL dynredem1("restart.nc",start_time,
    730735     &                         vcov,ucov,teta,q,masse,ps)
    731736              endif ! of if (planet_type.eq."mars")
     
    847852                  call abort_gcm(modname,abort_message,0)
    848853                else
    849                   CALL dynredem1("restart.nc",0.0,
     854                  CALL dynredem1("restart.nc",start_time,
    850855     &                         vcov,ucov,teta,q,masse,ps)
    851856                endif ! of if (planet_type.eq."mars")
  • trunk/LMDZ.COMMON/libf/dyn3d/temps.h

    r1 r492  
    11!
    2 ! $Id: temps.h 1279 2009-12-10 09:02:56Z fairhead $
     2! $Id: temps.h 1577 2011-10-20 15:06:47Z fairhead $
    33!
    44!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
     
    1414
    1515      COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref,   &
    16      &             itau_dyn, itau_phy, jD_ref, jH_ref, calend
     16     &             itau_dyn, itau_phy, jD_ref, jH_ref, calend,          &
     17     &             start_time
     18
    1719
    1820      INTEGER   itaufin
    1921      INTEGER itau_dyn, itau_phy
    2022      INTEGER day_ini, day_end, annee_ref, day_ref
    21       REAL      dt, jD_ref, jH_ref
     23      REAL      dt, jD_ref, jH_ref, start_time
    2224      CHARACTER (len=10) :: calend
    2325
Note: See TracChangeset for help on using the changeset viewer.