Ignore:
Timestamp:
Nov 19, 2013, 12:52:22 PM (11 years ago)
Author:
emillour
Message:

Common dynamics: Updates and modifications to enable running Mars physics with

LMDZ.COMMON dynamics:

  • For compilation: adapted makelmdz, create_make_gcm and makelmdz_fcm, bld.cfg to compile aeronomy routines in "aerono$physique" if it exists, and added "-P -traditional" preprocessing flags in "arch-linux-ifort*"
  • Added function "cbrt.F" (cubic root) in 'bibio'
  • Adapted the reading/writing of dynamics (re)start.nc files for Mars. The main issue is that different information (on time, reference and current) is stored and used differently, hence a few if (planet_type =="mars") here and there. Moreover in the martian case there is the possibility to store fields over multiple times. Some Mars-specific variables (ecritphy,ecritstart,timestart) added in control_mod.F and (hour_ini) in temps.h

EM

Location:
trunk/LMDZ.COMMON/libf/dyn3dpar
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/calfis_p.F

    r1086 r1107  
    3131      USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root
    3232      USE mod_interface_dyn_phys
    33       USE IOPHY
     33!      USE IOPHY
    3434#endif
    3535      USE parallel_lmdz, ONLY : omp_chunk, using_mpi, AllGather_Field
     
    933933     .             tracerdyn)      !! tracerdyn <-- utilite ???
    934934
    935       else ! a moduler pour Mars
    936         CALL physiq (klon,
    937      .             llm,
    938      .             nqtot,
    939      .             debut_split,
    940      .             lafin_split,
    941      .             jD_cur,
    942      .             jH_cur_split,
    943      .             zdt_split,
    944      .             zplev_omp,
    945      .             zplay_omp,
    946      .             zpk_omp,
    947      .             zphi_omp,
    948      .             zphis_omp,
    949      .             presnivs_omp,
    950      .             zufi_omp,
    951      .             zvfi_omp,
    952      .             ztfi_omp,
    953      .             zqfi_omp,
    954      .             flxwfi_omp,
    955      .             zdufi_omp,
    956      .             zdvfi_omp,
    957      .             zdtfi_omp,
    958      .             zdqfi_omp,
    959      .             zdpsrf_omp)
     935      else if ( planet_type=="mars" ) then
     936
     937        CALL physiq (klon,       ! ngrid
     938     .             llm,          ! nlayer
     939     .             nqtot,        ! nq
     940     .             debut_split,  ! firstcall
     941     .             lafin_split,  ! lastcall
     942     .             jD_cur,       ! pday
     943     .             jH_cur_split, ! ptime
     944     .             zdt_split,    ! ptimestep
     945     .             zplev_omp,    ! pplev
     946     .             zplay_omp,    ! pplay
     947     .             zphi_omp,     ! pphi
     948     .             zufi_omp,     ! pu
     949     .             zvfi_omp,     ! pv
     950     .             ztfi_omp,     ! pt
     951     .             zqfi_omp,     ! pq
     952     .             flxwfi_omp,   ! pw
     953     .             zdufi_omp,    ! pdu
     954     .             zdvfi_omp,    ! pdv
     955     .             zdtfi_omp,    ! pdt
     956     .             zdqfi_omp,    ! pdq
     957     .             zdpsrf_omp,   ! pdpsrf
     958     .             tracerdyn)    ! tracerdyn (somewhat obsolete)
     959
     960      else ! unknown "planet_type"
     961
     962        write(lunout,*) "calfis_p: error, unknown planet_type: ",
     963     &                  trim(planet_type)
     964        stop
     965
    960966      endif ! planet_type
    961967         zufi_omp(:,:)=zufi_omp(:,:)+zdufi_omp(:,:)*zdt_split
  • trunk/LMDZ.COMMON/libf/dyn3dpar/control_mod.F90

    r1022 r1107  
    1010  IMPLICIT NONE
    1111
    12   REAL    :: periodav, starttime
    13   INTEGER :: nday,day_step,iperiod,iapp_tracvl,nsplit_phys
    14   INTEGER :: iconser,iecri,dissip_period,iphysiq,iecrimoy
    15   INTEGER :: dayref,anneeref, raz_date, ip_ebil_dyn
    16   LOGICAL :: offline
    17   CHARACTER (len=4)  :: config_inca
    18   CHARACTER (len=10) :: planet_type ! planet type ('earth','mars',...)
    19   LOGICAL output_grads_dyn ! output dynamics diagnostics in
    20                            ! binary grads file 'dyn.dat' (y/n)
    21   LOGICAL ok_dynzon  ! output zonal transports in dynzon.nc file
    22   LOGICAL ok_dyn_ins ! output instantaneous values of fields
    23                      ! in the dynamics in NetCDF files dyn_hist*nc
    24   LOGICAL ok_dyn_ave ! output averaged values of fields in the dynamics
    25                      ! in NetCDF files dyn_hist*ave.nc
    26   LOGICAL :: resetvarc  ! allows to reset the variables in sortvarc
    27   LOGICAL :: less1day   ! allows to run less than 1 day (for Venus)
    28   REAL    :: fractday   ! fraction of the day to run in this case
     12  real,save :: periodav
     13  real,save :: starttime
     14  integer,save :: nday
     15  integer,save :: day_step ! # of dynamical time steps per day
     16  integer,save :: iperiod ! make a Matsuno step before avery iperiod-1 LF steps
     17  integer,save :: iapp_tracvl ! apply (cumulated) traceur advection every
     18                              ! iapp_tracvl dynamical steps
     19  integer,save :: nsplit_phys ! number of sub-cycle steps in call to physics
     20  integer,save :: iconser
     21  integer,save :: iecri
     22  integer,save :: dissip_period ! apply dissipation every dissip_period
     23                                ! dynamical step
     24  integer,save :: iphysiq ! call physics every iphysiq dynamical steps
     25  integer,save :: iecrimoy
     26  integer,save :: dayref
     27  integer,save :: anneeref ! reference year #
     28  integer,save :: raz_date
     29  integer,save :: ip_ebil_dyn
     30  logical,save :: offline
     31  character(len=4),save :: config_inca
     32  character(len=10),save :: planet_type ! planet type ('earth','mars',...)
     33  logical,save :: output_grads_dyn ! output dynamics diagnostics in
     34                                   ! binary grads file 'dyn.dat' (y/n)
     35  logical,save :: ok_dynzon  ! output zonal transports in dynzon.nc file
     36  logical,save :: ok_dyn_ins ! output instantaneous values of fields
     37                             ! in the dynamics in NetCDF files dyn_hist*nc
     38  logical,save :: ok_dyn_ave ! output averaged values of fields in the dynamics
     39                             ! in NetCDF files dyn_hist*ave.nc
     40  logical,save :: resetvarc  ! allows to reset the variables in sortvarc
     41  logical,save :: less1day   ! allows to run less than 1 day (for Venus)
     42  real,save :: fractday   ! fraction of the day to run in this case
    2943 
    30   integer :: ndynstep ! Alternative to using less1day&fractday; user may
    31                       ! specify number of dynamical steps to run
     44  integer,save :: ndynstep ! Alternative to using less1day&fractday; user may
     45                           ! specify number of dynamical steps to run
     46
     47  integer,save :: ecritphy ! (Mars/generic) output (writediagfi) every
     48                           ! ecritphy dynamical steps
     49  integer,save :: ecritstart ! (Mars) output data in "start.nc" every
     50                             !ecritstart dynamical steps
     51  real,save :: timestart ! (Mars) time start for run in "start.nc"
    3252
    3353END MODULE
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dynetat0.F

    r907 r1107  
    33!
    44      SUBROUTINE dynetat0(fichnom,vcov,ucov,
    5      .                    teta,q,masse,ps,phis,time)
    6 
    7       USE infotrac
    8       use netcdf, only: nf90_get_var
    9 
    10       use control_mod, only : planet_type
     5     .                    teta,q,masse,ps,phis,time0)
     6
     7      USE infotrac, only: tname, nqtot
     8      use netcdf, only: nf90_open,NF90_NOWRITE,nf90_noerr,nf90_strerror,
     9     &                  nf90_get_var, nf90_inq_varid, nf90_inq_dimid,
     10     &                  nf90_inquire_dimension,nf90_close
     11
     12      use control_mod, only : planet_type, timestart
    1113
    1214      IMPLICIT NONE
     
    4345c   ----------
    4446
    45       CHARACTER*(*) fichnom
    46       REAL vcov(iip1, jjm,llm),ucov(iip1, jjp1,llm),teta(iip1, jjp1,llm)
    47       REAL q(iip1,jjp1,llm,nqtot),masse(iip1, jjp1,llm)
    48       REAL ps(iip1, jjp1),phis(iip1, jjp1)
    49 
    50       REAL time
     47      CHARACTER(len=*),INTENT(IN) :: fichnom
     48      REAL,INTENT(OUT) :: vcov(iip1,jjm,llm)
     49      REAL,INTENT(OUT) :: ucov(iip1,jjp1,llm)
     50      REAL,INTENT(OUT) :: teta(iip1,jjp1,llm)
     51      REAL,INTENT(OUT) :: q(iip1,jjp1,llm,nqtot)
     52      REAL,INTENT(OUT) :: masse(iip1,jjp1,llm)
     53      REAL,INTENT(OUT) :: ps(iip1,jjp1)
     54      REAL,INTENT(OUT) :: phis(iip1,jjp1)
     55      REAL,INTENT(OUT) :: time0
    5156
    5257c   Variables
     
    6065      INTEGER idecal
    6166
     67
     68      REAL,ALLOCATABLE :: time(:) ! times stored in start
     69      INTEGER timelen ! number of times stored in the file
     70      INTEGER indextime ! index of selected time
     71      !REAL  hour_ini ! fraction of day of stored date. Equivalent of day_ini, but 0=<hour_ini<1
     72
     73      INTEGER edges(4),corner(4)
     74      integer :: i
     75
    6276c-----------------------------------------------------------------------
    6377
    6478c  Ouverture NetCDF du fichier etat initial
    6579
    66       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid)
    67       IF (ierr.NE.NF_NOERR) THEN
     80      ierr=nf90_open(fichnom,NF90_NOWRITE,nid)
     81      IF (ierr.NE.nf90_noerr) THEN
    6882        write(lunout,*)'dynetat0: Pb d''ouverture du fichier start.nc'
    69         write(lunout,*)' ierr = ', ierr
     83        write(lunout,*)trim(nf90_strerror(ierr))
    7084        CALL ABORT
    7185      ENDIF
    7286
    7387c
    74       ierr = NF_INQ_VARID (nid, "controle", nvarid)
    75       IF (ierr .NE. NF_NOERR) THEN
     88      ierr = nf90_inq_varid (nid, "controle", nvarid)
     89      IF (ierr .NE. nf90_noerr) THEN
    7690         write(lunout,*)"dynetat0: Le champ <controle> est absent"
     91         write(lunout,*)trim(nf90_strerror(ierr))
    7792         CALL abort
    7893      ENDIF
    7994      ierr = nf90_get_var(nid, nvarid, tab_cntrl)
    80       IF (ierr .NE. NF_NOERR) THEN
     95      IF (ierr .NE. nf90_noerr) THEN
    8196         write(lunout,*)"dynetat0: Lecture echoue pour <controle>"
     97         write(lunout,*)trim(nf90_strerror(ierr))
    8298         CALL abort
    8399      ENDIF
     
    138154      ENDIF
    139155
     156      if (planet_type=="mars") then ! so far this is only for Mars
     157        hour_ini = tab_cntrl(29)
     158      else
     159        hour_ini=0
     160      endif
     161
    140162      if (start_file_type.eq."earth") then
    141163        day_ini = tab_cntrl(30)
     
    150172c
    151173c
    152       write(lunout,*)'dynetat0: rad,omeg,g,cpp,kappa',
     174      write(lunout,*)'dynetat0: rad,omeg,g,cpp,kappa ',
    153175     &               rad,omeg,g,cpp,kappa
    154176
     
    164186      ENDIF
    165187
    166       ierr = NF_INQ_VARID (nid, "rlonu", nvarid)
    167       IF (ierr .NE. NF_NOERR) THEN
     188      ierr=nf90_inq_varid(nid, "rlonu", nvarid)
     189      IF (ierr .NE. nf90_noerr) THEN
    168190         write(lunout,*)"dynetat0: Le champ <rlonu> est absent"
     191         write(lunout,*)trim(nf90_strerror(ierr))
    169192         CALL abort
    170193      ENDIF
    171194      ierr = nf90_get_var(nid, nvarid, rlonu)
    172       IF (ierr .NE. NF_NOERR) THEN
     195      IF (ierr .NE. nf90_noerr) THEN
    173196         write(lunout,*)"dynetat0: Lecture echouee pour <rlonu>"
    174          CALL abort
    175       ENDIF
    176 
    177       ierr = NF_INQ_VARID (nid, "rlatu", nvarid)
    178       IF (ierr .NE. NF_NOERR) THEN
     197         write(lunout,*)trim(nf90_strerror(ierr))
     198         CALL abort
     199      ENDIF
     200
     201      ierr = nf90_inq_varid (nid, "rlatu", nvarid)
     202      IF (ierr .NE. nf90_noerr) THEN
    179203         write(lunout,*)"dynetat0: Le champ <rlatu> est absent"
     204         write(lunout,*)trim(nf90_strerror(ierr))
    180205         CALL abort
    181206      ENDIF
    182207      ierr = nf90_get_var(nid, nvarid, rlatu)
    183       IF (ierr .NE. NF_NOERR) THEN
     208      IF (ierr .NE. nf90_noerr) THEN
    184209         write(lunout,*)"dynetat0: Lecture echouee pour <rlatu>"
    185          CALL abort
    186       ENDIF
    187 
    188       ierr = NF_INQ_VARID (nid, "rlonv", nvarid)
    189       IF (ierr .NE. NF_NOERR) THEN
     210         write(lunout,*)trim(nf90_strerror(ierr))
     211         CALL abort
     212      ENDIF
     213
     214      ierr = nf90_inq_varid (nid, "rlonv", nvarid)
     215      IF (ierr .NE. nf90_noerr) THEN
    190216         write(lunout,*)"dynetat0: Le champ <rlonv> est absent"
     217         write(lunout,*)trim(nf90_strerror(ierr))
    191218         CALL abort
    192219      ENDIF
    193220      ierr = nf90_get_var(nid, nvarid, rlonv)
    194       IF (ierr .NE. NF_NOERR) THEN
     221      IF (ierr .NE. nf90_noerr) THEN
    195222         write(lunout,*)"dynetat0: Lecture echouee pour <rlonv>"
    196          CALL abort
    197       ENDIF
    198 
    199       ierr = NF_INQ_VARID (nid, "rlatv", nvarid)
    200       IF (ierr .NE. NF_NOERR) THEN
     223         write(lunout,*)trim(nf90_strerror(ierr))
     224         CALL abort
     225      ENDIF
     226
     227      ierr = nf90_inq_varid (nid, "rlatv", nvarid)
     228      IF (ierr .NE. nf90_noerr) THEN
    201229         write(lunout,*)"dynetat0: Le champ <rlatv> est absent"
     230         write(lunout,*)trim(nf90_strerror(ierr))
    202231         CALL abort
    203232      ENDIF
    204233      ierr = nf90_get_var(nid, nvarid, rlatv)
    205       IF (ierr .NE. NF_NOERR) THEN
     234      IF (ierr .NE. nf90_noerr) THEN
    206235         write(lunout,*)"dynetat0: Lecture echouee pour rlatv"
    207          CALL abort
    208       ENDIF
    209 
    210       ierr = NF_INQ_VARID (nid, "cu", nvarid)
    211       IF (ierr .NE. NF_NOERR) THEN
     236         write(lunout,*)trim(nf90_strerror(ierr))
     237         CALL abort
     238      ENDIF
     239
     240      ierr = nf90_inq_varid (nid, "cu", nvarid)
     241      IF (ierr .NE. nf90_noerr) THEN
    212242         write(lunout,*)"dynetat0: Le champ <cu> est absent"
     243         write(lunout,*)trim(nf90_strerror(ierr))
    213244         CALL abort
    214245      ENDIF
    215246      ierr = nf90_get_var(nid, nvarid, cu)
    216       IF (ierr .NE. NF_NOERR) THEN
     247      IF (ierr .NE. nf90_noerr) THEN
    217248         write(lunout,*)"dynetat0: Lecture echouee pour <cu>"
    218          CALL abort
    219       ENDIF
    220 
    221       ierr = NF_INQ_VARID (nid, "cv", nvarid)
    222       IF (ierr .NE. NF_NOERR) THEN
     249         write(lunout,*)trim(nf90_strerror(ierr))
     250         CALL abort
     251      ENDIF
     252
     253      ierr = nf90_inq_varid (nid, "cv", nvarid)
     254      IF (ierr .NE. nf90_noerr) THEN
    223255         write(lunout,*)"dynetat0: Le champ <cv> est absent"
     256         write(lunout,*)trim(nf90_strerror(ierr))
    224257         CALL abort
    225258      ENDIF
    226259      ierr = nf90_get_var(nid, nvarid, cv)
    227       IF (ierr .NE. NF_NOERR) THEN
     260      IF (ierr .NE. nf90_noerr) THEN
    228261         write(lunout,*)"dynetat0: Lecture echouee pour <cv>"
    229          CALL abort
    230       ENDIF
    231 
    232       ierr = NF_INQ_VARID (nid, "aire", nvarid)
    233       IF (ierr .NE. NF_NOERR) THEN
     262         write(lunout,*)trim(nf90_strerror(ierr))
     263         CALL abort
     264      ENDIF
     265
     266      ierr = nf90_inq_varid (nid, "aire", nvarid)
     267      IF (ierr .NE. nf90_noerr) THEN
    234268         write(lunout,*)"dynetat0: Le champ <aire> est absent"
     269         write(lunout,*)trim(nf90_strerror(ierr))
    235270         CALL abort
    236271      ENDIF
    237272      ierr = nf90_get_var(nid, nvarid, aire)
    238       IF (ierr .NE. NF_NOERR) THEN
     273      IF (ierr .NE. nf90_noerr) THEN
    239274         write(lunout,*)"dynetat0: Lecture echouee pour <aire>"
    240          CALL abort
    241       ENDIF
    242 
    243       ierr = NF_INQ_VARID (nid, "phisinit", nvarid)
    244       IF (ierr .NE. NF_NOERR) THEN
     275         write(lunout,*)trim(nf90_strerror(ierr))
     276         CALL abort
     277      ENDIF
     278
     279      ierr = nf90_inq_varid (nid, "phisinit", nvarid)
     280      IF (ierr .NE. nf90_noerr) THEN
    245281         write(lunout,*)"dynetat0: Le champ <phisinit> est absent"
     282         write(lunout,*)trim(nf90_strerror(ierr))
    246283         CALL abort
    247284      ENDIF
    248285      ierr = nf90_get_var(nid, nvarid, phis)
    249       IF (ierr .NE. NF_NOERR) THEN
     286      IF (ierr .NE. nf90_noerr) THEN
    250287         write(lunout,*)"dynetat0: Lecture echouee pour <phisinit>"
    251          CALL abort
    252       ENDIF
    253 
    254       ierr = NF_INQ_VARID (nid, "temps", nvarid)
    255       IF (ierr .NE. NF_NOERR) THEN
    256          write(lunout,*)"dynetat0: Le champ <temps> est absent"
    257          write(lunout,*)"dynetat0: J essaie <Time>"
    258          ierr = NF_INQ_VARID (nid, "Time", nvarid)
    259          IF (ierr .NE. NF_NOERR) THEN
    260             write(lunout,*)"dynetat0: Le champ <Time> est absent"
    261             CALL abort
    262          ENDIF
    263       ENDIF
    264       ierr = nf90_get_var(nid, nvarid, time)
    265       IF (ierr .NE. NF_NOERR) THEN
    266          write(lunout,*)"dynetat0: Lecture echouee <temps>"
    267          CALL abort
    268       ENDIF
    269 
    270       ierr = NF_INQ_VARID (nid, "ucov", nvarid)
    271       IF (ierr .NE. NF_NOERR) THEN
     288         write(lunout,*)trim(nf90_strerror(ierr))
     289         CALL abort
     290      ENDIF
     291
     292! read time axis
     293      ierr = nf90_inq_varid (nid, "temps", nvarid)
     294      IF (ierr .NE. nf90_noerr) THEN
     295        write(lunout,*)"dynetat0: Le champ <temps> est absent"
     296        write(lunout,*)"dynetat0: J essaie <Time>"
     297        ierr = nf90_inq_varid (nid, "Time", nvarid)
     298        IF (ierr .NE. nf90_noerr) THEN
     299           write(lunout,*)"dynetat0: Le champ <Time> est absent"
     300           write(lunout,*)trim(nf90_strerror(ierr))
     301           CALL abort
     302        ENDIF
     303        ! Get the length of the "Time" dimension
     304        ierr = nf90_inq_dimid(nid,"Time",nvarid)
     305        ierr = nf90_inquire_dimension(nid,nvarid,len=timelen)
     306        allocate(time(timelen))
     307        ! Then look for the "Time" variable
     308        ierr  =nf90_inq_varid(nid,"Time",nvarid)
     309        ierr = nf90_get_var(nid, nvarid, time)
     310        IF (ierr .NE. nf90_noerr) THEN
     311           write(lunout,*)"dynetat0: Lecture echouee <Time>"
     312           write(lunout,*)trim(nf90_strerror(ierr))
     313           CALL abort
     314        ENDIF
     315      ELSE   
     316        ! Get the length of the "temps" dimension
     317        ierr = nf90_inq_dimid(nid,"temps",nvarid)
     318        ierr = nf90_inquire_dimension(nid,nvarid,len=timelen)
     319        allocate(time(timelen))
     320        ! Then look for the "temps" variable
     321        ierr = nf90_inq_varid (nid, "temps", nvarid)
     322        ierr = nf90_get_var(nid, nvarid, time)
     323        IF (ierr .NE. nf90_noerr) THEN
     324           write(lunout,*)"dynetat0: Lecture echouee <temps>"
     325           write(lunout,*)trim(nf90_strerror(ierr))
     326           CALL abort
     327        ENDIF
     328      ENDIF
     329
     330! select the desired time
     331      IF (timestart .lt. 0) THEN  ! default: we use the last time value
     332        indextime = timelen
     333      ELSE  ! else we look for the desired value in the time axis
     334       indextime = 0
     335        DO i=1,timelen
     336          IF (abs(time(i) - timestart) .lt. 0.01) THEN
     337             indextime = i
     338             EXIT
     339          ENDIF
     340        ENDDO
     341        IF (indextime .eq. 0) THEN
     342          write(lunout,*)"Time", timestart," is not in "
     343     &                                      //trim(fichnom)//"!!"
     344          write(lunout,*)"Stored times are:"
     345          DO i=1,timelen
     346             PRINT*, time(i)
     347          ENDDO
     348          CALL abort
     349        ENDIF
     350      ENDIF
     351
     352      if (planet_type=="mars") then
     353        ! In start the absolute date is day_ini + hour_ini + time
     354        ! For now on, in the GCM dynamics, it is day_ini + time0
     355        time0 = time(indextime) + hour_ini
     356        day_ini = day_ini + INT(time0)
     357        time0 = time0 - INT(time0) ! time0 devient le nouveau hour_ini
     358        hour_ini = time0
     359      else
     360        time0 = time(indextime)
     361      endif
     362     
     363      PRINT*, "dynetat0: Selected time ",time(indextime),
     364     .        " at index ",indextime
     365     
     366      DEALLOCATE(time)
     367
     368! read vcov
     369      corner(1)=1
     370      corner(2)=1
     371      corner(3)=1
     372      corner(4)=indextime
     373      edges(1)=iip1
     374      edges(2)=jjm
     375      edges(3)=llm
     376      edges(4)=1
     377      ierr=nf90_inq_varid(nid,"vcov",nvarid)
     378      IF (ierr .NE. nf90_noerr) THEN
     379         write(lunout,*)"dynetat0: Le champ <vcov> est absent"
     380         write(lunout,*)trim(nf90_strerror(ierr))
     381         CALL abort
     382      ENDIF
     383      ierr=nf90_get_var(nid,nvarid,vcov,corner,edges)
     384      IF (ierr .NE. nf90_noerr) THEN
     385         write(lunout,*)"dynetat0: Lecture echouee pour <vcov>"
     386         write(lunout,*)trim(nf90_strerror(ierr))
     387         CALL abort
     388      ENDIF
     389
     390! read ucov
     391      corner(1)=1
     392      corner(2)=1
     393      corner(3)=1
     394      corner(4)=indextime
     395      edges(1)=iip1
     396      edges(2)=jjp1
     397      edges(3)=llm
     398      edges(4)=1
     399      ierr=nf90_inq_varid(nid,"ucov",nvarid)
     400      IF (ierr .NE. nf90_noerr) THEN
    272401         write(lunout,*)"dynetat0: Le champ <ucov> est absent"
    273          CALL abort
    274       ENDIF
    275       ierr = nf90_get_var(nid, nvarid, ucov)
    276       IF (ierr .NE. NF_NOERR) THEN
     402         write(lunout,*)trim(nf90_strerror(ierr))
     403         CALL abort
     404      ENDIF
     405      ierr=nf90_get_var(nid,nvarid,ucov,corner,edges)
     406      IF (ierr .NE. nf90_noerr) THEN
    277407         write(lunout,*)"dynetat0: Lecture echouee pour <ucov>"
     408         write(lunout,*)trim(nf90_strerror(ierr))
    278409         CALL abort
    279410      ENDIF
    280411 
    281       ierr = NF_INQ_VARID (nid, "vcov", nvarid)
    282       IF (ierr .NE. NF_NOERR) THEN
    283          write(lunout,*)"dynetat0: Le champ <vcov> est absent"
    284          CALL abort
    285       ENDIF
    286       ierr = nf90_get_var(nid, nvarid, vcov)
    287       IF (ierr .NE. NF_NOERR) THEN
    288          write(lunout,*)"dynetat0: Lecture echouee pour <vcov>"
    289          CALL abort
    290       ENDIF
    291 
    292       ierr = NF_INQ_VARID (nid, "teta", nvarid)
    293       IF (ierr .NE. NF_NOERR) THEN
     412! read teta (same corner/edges as ucov)
     413      ierr=nf90_inq_varid(nid,"teta",nvarid)
     414      IF (ierr .NE. nf90_noerr) THEN
    294415         write(lunout,*)"dynetat0: Le champ <teta> est absent"
    295          CALL abort
    296       ENDIF
    297       ierr = nf90_get_var(nid, nvarid, teta)
    298       IF (ierr .NE. NF_NOERR) THEN
     416         write(lunout,*)trim(nf90_strerror(ierr))
     417         CALL abort
     418      ENDIF
     419      ierr=nf90_get_var(nid,nvarid,teta,corner,edges)
     420      IF (ierr .NE. nf90_noerr) THEN
    299421         write(lunout,*)"dynetat0: Lecture echouee pour <teta>"
    300          CALL abort
    301       ENDIF
    302 
    303 
     422         write(lunout,*)trim(nf90_strerror(ierr))
     423         CALL abort
     424      ENDIF
     425
     426! read tracers (same corner/edges as ucov)
    304427      IF(nqtot.GE.1) THEN
    305428      DO iq=1,nqtot
    306         ierr =  NF_INQ_VARID (nid, tname(iq), nvarid)
    307         IF (ierr .NE. NF_NOERR) THEN
     429        ierr= nf90_inq_varid(nid,tname(iq),nvarid)
     430        IF (ierr .NE. nf90_noerr) THEN
    308431           write(lunout,*)"dynetat0: Le traceur <"//trim(tname(iq))//
    309432     &                    "> est absent"
     
    311434           q(:,:,:,iq)=0.
    312435        ELSE
    313            ierr = NF90_GET_VAR(nid, nvarid, q(:,:,:,iq))
    314           IF (ierr .NE. NF_NOERR) THEN
    315             write(lunout,*)"dynetat0: Lecture echouee pour "//tname(iq)
     436           ierr=nf90_get_var(nid,nvarid,q(:,:,:,iq),corner,edges)
     437          IF (ierr .NE. nf90_noerr) THEN
     438            write(lunout,*)"dynetat0: Lecture echouee pour "
     439     &                                //trim(tname(iq))
     440            write(lunout,*)trim(nf90_strerror(ierr))
    316441            CALL abort
    317442          ENDIF
     
    320445      ENDIF
    321446
    322       ierr = NF_INQ_VARID (nid, "masse", nvarid)
    323       IF (ierr .NE. NF_NOERR) THEN
     447!read masse (same corner/edges as ucov)
     448      ierr=nf90_inq_varid(nid,"masse",nvarid)
     449      IF (ierr .NE. nf90_noerr) THEN
    324450         write(lunout,*)"dynetat0: Le champ <masse> est absent"
    325          CALL abort
    326       ENDIF
    327       ierr = nf90_get_var(nid, nvarid, masse)
    328       IF (ierr .NE. NF_NOERR) THEN
     451         write(lunout,*)trim(nf90_strerror(ierr))
     452         CALL abort
     453      ENDIF
     454      ierr=nf90_get_var(nid,nvarid,masse,corner,edges)
     455      IF (ierr .NE. nf90_noerr) THEN
    329456         write(lunout,*)"dynetat0: Lecture echouee pour <masse>"
    330          CALL abort
    331       ENDIF
    332 
    333       ierr = NF_INQ_VARID (nid, "ps", nvarid)
    334       IF (ierr .NE. NF_NOERR) THEN
     457         write(lunout,*)trim(nf90_strerror(ierr))
     458         CALL abort
     459      ENDIF
     460
     461! read ps
     462      corner(1)=1
     463      corner(2)=1
     464      corner(3)=indextime
     465      edges(1)=iip1
     466      edges(2)=jjp1
     467      edges(3)=1
     468      ierr=nf90_inq_varid(nid,"ps",nvarid)
     469      IF (ierr .NE. nf90_noerr) THEN
    335470         write(lunout,*)"dynetat0: Le champ <ps> est absent"
    336          CALL abort
    337       ENDIF
    338       ierr = nf90_get_var(nid, nvarid, ps)
    339       IF (ierr .NE. NF_NOERR) THEN
     471         write(lunout,*)trim(nf90_strerror(ierr))
     472         CALL abort
     473      ENDIF
     474      ierr=nf90_get_var(nid,nvarid,ps,corner,edges)
     475      IF (ierr .NE. nf90_noerr) THEN
    340476         write(lunout,*)"dynetat0: Lecture echouee pour <ps>"
    341          CALL abort
    342       ENDIF
    343 
    344       ierr = NF_CLOSE(nid)
    345 
    346        day_ini=day_ini+INT(time)
    347        time=time-INT(time)
     477         write(lunout,*)trim(nf90_strerror(ierr))
     478         CALL abort
     479      ENDIF
     480
     481      ierr=nf90_close(nid)
     482
     483      if (planet_type/="mars") then
     484       day_ini=day_ini+INT(time0) ! obsolete stuff ; 0<time<1 anyways
     485       time0=time0-INT(time0)
     486      endif
    348487
    349488  1   FORMAT(//10x,'la valeur de im =',i4,2x,'lue sur le fichier de dem
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem.F

    r907 r1107  
    9595         tab_cntrl(4)=REAL(day_ref)
    9696       else
    97          tab_cntrl(4)=REAL(day_end)
     97         !tab_cntrl(4)=REAL(day_end)
     98         tab_cntrl(4)=REAL(iday_end)
    9899       endif
    99100       tab_cntrl(5)  = REAL(annee_ref)
     
    142143c start_time: start_time of simulation (not necessarily 0.)
    143144       tab_cntrl(idecal+27) = start_time
     145      endif
     146
     147      if (planet_type=="mars") then ! For Mars only
     148        tab_cntrl(29)=hour_ini
    144149      endif
    145150c
     
    680685         CALL abort_gcm(modname,abort_message,ierr)
    681686      ENDIF
    682       call NF95_PUT_VAR(nid,nvarid,ucov)
     687      call NF95_PUT_VAR(nid,nvarid,ucov,start=(/1,1,1,nb/))
    683688
    684689      ierr = NF_INQ_VARID(nid, "vcov", nvarid)
     
    688693         CALL abort_gcm(modname,abort_message,ierr)
    689694      ENDIF
    690       call NF95_PUT_VAR(nid,nvarid,vcov)
     695      call NF95_PUT_VAR(nid,nvarid,vcov,start=(/1,1,1,nb/))
    691696
    692697      ierr = NF_INQ_VARID(nid, "teta", nvarid)
     
    696701         CALL abort_gcm(modname,abort_message,ierr)
    697702      ENDIF
    698       call NF95_PUT_VAR(nid,nvarid,teta)
     703      call NF95_PUT_VAR(nid,nvarid,teta,start=(/1,1,1,nb/))
    699704
    700705      IF (type_trac == 'inca') THEN
     
    718723               CALL abort_gcm(modname,abort_message,ierr)
    719724            ENDIF
    720             call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq))
     725            call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq),start=(/1,1,1,nb/))
    721726        ELSE ! type_trac = inca
    722727! lecture de la valeur du traceur dans start_trac.nc
     
    765770                   CALL abort_gcm(modname,abort_message,ierr)
    766771             ENDIF
    767              call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq))
     772             call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq),
     773     &                  start=(/1,1,1,nb/))
    768774          ENDIF ! (ierr_file .ne. 2)
    769775       END IF   !type_trac
     
    778784         CALL abort_gcm(modname,abort_message,ierr)
    779785      ENDIF
    780       call NF95_PUT_VAR(nid,nvarid,masse)
     786      call NF95_PUT_VAR(nid,nvarid,masse,start=(/1,1,1,nb/))
    781787c
    782788      ierr = NF_INQ_VARID(nid, "ps", nvarid)
     
    786792         CALL abort_gcm(modname,abort_message,ierr)
    787793      ENDIF
    788       call NF95_PUT_VAR(nid,nvarid,ps)
     794      call NF95_PUT_VAR(nid,nvarid,ps,start=(/1,1,nb/))
    789795
    790796      ierr = NF_CLOSE(nid)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem_p.F

    r1019 r1107  
    9898         tab_cntrl(4)=REAL(day_ref)
    9999       else
    100          tab_cntrl(4)=REAL(day_end)
     100         !tab_cntrl(4)=REAL(day_end)
     101         tab_cntrl(4)=REAL(iday_end)
    101102       endif
    102103       tab_cntrl(5)  = REAL(annee_ref)
     
    145146c start_time: start_time of simulation (not necessarily 0.)
    146147       tab_cntrl(idecal+27) = start_time
     148      endif
     149
     150      if (planet_type=="mars") then ! For Mars only
     151        tab_cntrl(29)=hour_ini
    147152      endif
    148153c
     
    695700         CALL abort
    696701      ENDIF
    697       call NF95_PUT_VAR(nid,nvarid,ucov)
     702      call NF95_PUT_VAR(nid,nvarid,ucov,start=(/1,1,1,nb/))
    698703
    699704      ierr = NF_INQ_VARID(nid, "vcov", nvarid)
     
    702707         CALL abort
    703708      ENDIF
    704       call NF95_PUT_VAR(nid,nvarid,vcov)
     709      call NF95_PUT_VAR(nid,nvarid,vcov,start=(/1,1,1,nb/))
    705710
    706711      ierr = NF_INQ_VARID(nid, "teta", nvarid)
     
    709714         CALL abort
    710715      ENDIF
    711       call NF95_PUT_VAR(nid,nvarid,teta)
     716      call NF95_PUT_VAR(nid,nvarid,teta,start=(/1,1,1,nb/))
    712717
    713718      IF (type_trac == 'inca') THEN
     
    734739               CALL abort
    735740            ENDIF
    736             call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq))
     741            call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq),start=(/1,1,1,nb/))
    737742        ELSE ! type_trac = inca
    738743! lecture de la valeur du traceur dans start_trac.nc
     
    771776                CALL abort
    772777             ENDIF
    773              call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq))
     778             call NF95_PUT_VAR(nid,nvarid,q(:,:,:,iq),
     779     &                  start=(/1,1,1,nb/))
    774780          ENDIF ! (ierr_file .ne. 2)
    775781       END IF   !type_trac
     
    785791         CALL abort
    786792      ENDIF
    787       call NF95_PUT_VAR(nid,nvarid,masse)
     793      call NF95_PUT_VAR(nid,nvarid,masse,start=(/1,1,1,nb/))
    788794c
    789795      ierr = NF_INQ_VARID(nid, "ps", nvarid)
     
    792798         CALL abort
    793799      ENDIF
    794       call NF95_PUT_VAR(nid,nvarid,ps)
     800      call NF95_PUT_VAR(nid,nvarid,ps,start=(/1,1,nb/))
    795801
    796802      ierr = NF_CLOSE(nid)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F

    r1086 r1107  
    302302        endif
    303303
    304         if (planet_type.eq."mars") then
    305 ! POUR MARS, METTRE UNE FONCTION A PART, genre dynetat0_mars
    306          abort_message = 'dynetat0_mars A FAIRE'
    307          call abort_gcm(modname,abort_message,0)
    308         else
    309          CALL dynetat0("start.nc",vcov,ucov,
     304        CALL dynetat0("start.nc",vcov,ucov,
    310305     &              teta,q,masse,ps,phis, time_0)
    311         endif ! of if (planet_type.eq."mars")
    312306       
    313307        ! Load relaxation fields (simple nudging). AS 09/2013
     
    558552#endif
    559553
    560       if (planet_type.eq."mars") then
    561 ! POUR MARS, METTRE UNE FONCTION A PART, genre dynredem0_mars
    562          abort_message = 'dynredem0_mars A FAIRE'
    563          call abort_gcm(modname,abort_message,0)
     554      if (planet_type=="mars") then
     555         ! For Mars we transmit day_ini
     556        CALL dynredem0_p("restart.nc", day_ini, phis)
    564557      else
    565558        CALL dynredem0_p("restart.nc", day_end, phis)
    566       endif ! of if (planet_type.eq."mars")
    567 
     559      endif
    568560      ecripar = .TRUE.
    569561
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r1086 r1107  
    844844     $        + itau/day_step
    845845
    846            IF (planet_type .eq."generic") THEN
     846           IF ((planet_type .eq."generic").or.
     847     &         (planet_type.eq."mars")) THEN
    847848              ! AS: we make jD_cur to be pday
    848849              jD_cur = int(day_ini + itau/day_step)
     
    17271728c$OMP MASTER
    17281729
    1729               if (planet_type.eq."mars") then
    1730 ! POUR MARS, METTRE UNE FONCTION A PART, genre dynredem1_mars
    1731                 abort_message = 'dynredem1_mars A FAIRE'
    1732                 call abort_gcm(modname,abort_message,0)
     1730              if (planet_type=="mars") then
     1731                CALL dynredem1_p("restart.nc",REAL(itau)/REAL(day_step),
     1732     &                           vcov,ucov,teta,q,masse,ps)
    17331733              else
    1734 ! Write an Earth-format restart file
    1735                 CALL dynredem1_p("restart.nc",0.0,
     1734                CALL dynredem1_p("restart.nc",start_time,
    17361735     &                           vcov,ucov,teta,q,masse,ps)
    1737               endif ! of if (planet_type.eq."mars")
    1738 
     1736              endif
    17391737!              CLOSE(99)
    17401738c$OMP END MASTER
     
    19421940
    19431941              IF(itau.EQ.itaufin) THEN
    1944                 if (planet_type.eq."mars") then
    1945 ! POUR MARS, METTRE UNE FONCTION A PART, genre dynredem1_mars
    1946                   abort_message = 'dynredem1_mars A FAIRE'
    1947                   call abort_gcm(modname,abort_message,0)
     1942c$OMP MASTER
     1943                if (planet_type=="mars") then
     1944                  CALL dynredem1_p("restart.nc",
     1945     &                              REAL(itau)/REAL(day_step),
     1946     &                               vcov,ucov,teta,q,masse,ps)
    19481947                else
    1949 c$OMP MASTER
    1950                    CALL dynredem1_p("restart.nc",0.0,
    1951      .                               vcov,ucov,teta,q,masse,ps)
    1952 c$OMP END MASTER
    1953                 endif ! of if (planet_type.eq."mars")
     1948                  CALL dynredem1_p("restart.nc",start_time,
     1949     &                               vcov,ucov,teta,q,masse,ps)
     1950                
     1951                endif
     1952c$OMP END MASTER
    19541953              ENDIF ! of IF(itau.EQ.itaufin)
    19551954
  • trunk/LMDZ.COMMON/libf/dyn3dpar/moyzon_mod.F90

    r1056 r1107  
    3131!======================================================================
    3232SUBROUTINE moyzon_init
    33 
     33#ifdef CPP_PHYS
     34! This routine needs physics
    3435USE dimphy
    3536USE infotrac, only: nqtot
     
    4142      ALLOCATE(ztfibar_mpi(klon,llm),zqfibar_mpi(klon,llm,nqtot))
    4243      ALLOCATE(zpkbar_mpi(klon,llm),ztetabar_mpi(klon,llm))
    43 
     44#endif
    4445END SUBROUTINE moyzon_init
    4546
    4647!======================================================================
    4748SUBROUTINE moyzon_init_omp(nlon)
    48 
     49#ifdef CPP_PHYS
     50! This routine needs physics
    4951USE dimphy
    5052USE infotrac, only: nqtot
     
    5860      ALLOCATE(ztfibar(nlon,llm),zqfibar(nlon,llm,nqtot))
    5961      ALLOCATE(zzlevbar(nlon,llm+1),zzlaybar(nlon,llm))
    60 
     62#endif
    6163END SUBROUTINE moyzon_init_omp
    6264
  • trunk/LMDZ.COMMON/libf/dyn3dpar/temps.h

    r974 r1107  
    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
     
    1313! INCLUDE 'temps.h'
    1414
    15       COMMON/temps/ dt, jD_ref, jH_ref, start_time,                     &
    16      &             day_ini, day_end, annee_ref, day_ref,                &
    17      &             itau_dyn, itau_phy, itaufin, calend
     15      COMMON/temps_r/dt,jD_ref,jH_ref,start_time,hour_ini
     16      COMMON/temps_i/day_ini,day_end,annee_ref,day_ref,                 &
     17     &             itau_dyn,itau_phy,itaufin
     18      COMMON/temps_c/calend
    1819
    1920
    20       INTEGER   itaufin
     21      INTEGER   itaufin ! total number of dynamical steps for the run
    2122      INTEGER   itau_dyn, itau_phy
    22       INTEGER   day_ini, day_end, annee_ref, day_ref
    23       REAL      dt, jD_ref, jH_ref, start_time
     23      INTEGER   day_ini ! initial day # of simulation sequence
     24      INTEGER   day_end ! final day # ; i.e. day # when this simulation ends
     25      INTEGER   annee_ref
     26      INTEGER   day_ref
     27      REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
     28      REAL      jD_ref, jH_ref, start_time
    2429      CHARACTER (len=10) :: calend
    2530
    26 !$OMP THREADPRIVATE(/temps/)
     31      ! Additionnal Mars stuff:
     32      real hour_ini ! initial fraction of day of simulation sequence (0=<hour_ini<1)
     33
    2734!-----------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.