Ignore:
Timestamp:
Jul 2, 2013, 9:40:28 AM (11 years ago)
Author:
tnavarro
Message:

Possibility to store multiple initial states in one start/startfi. This is RETROCOMPATIBLE. New option ecrithist in run.def to write data in start/startfi every ecrithist dynamical timestep. New option timestart in run.def to initialize the GCM with the time timestart stored in start

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/dyn3d/dynetat0.F

    r791 r999  
    11      SUBROUTINE dynetat0(fichnom,nq,vcov,ucov,
    2      .                    teta,q,masse,ps,phis,time)
     2     .                    teta,q,masse,ps,phis,time0)
    33     
    44      use netcdf
     
    2020c                    r4 or r8 restarts independently of having compiled
    2121c                    the GCM in r4 or r8)
    22 c
     22c           June 2013 TN : Possibility to read files with a time axis.
     23c                          NOW defrun_new MUST BE CALLED BEFORE dynetat0.
    2324c=======================================================================
    2425c-----------------------------------------------------------------------
     
    3637#include "serre.h"
    3738#include "logic.h"
    38 #include"advtrac.h"
     39#include "advtrac.h"
     40#include "control.h"
    3941
    4042c   Arguments:
     
    4850      REAL ps(iip1,jjp1),phis(iip1,jjp1)
    4951
    50       REAL time ! fraction of day the fields correspond to
     52      REAL time0 ! fraction of day the fields correspond to
    5153
    5254c   Variables
     
    5860      INTEGER ierr, nid, nvarid, nqold
    5961      CHARACTER  str3*3,yes*1
     62     
     63      REAL,ALLOCATABLE :: time(:) ! times stored in start
     64      INTEGER timelen ! number of times stored in the file
     65      INTEGER indextime ! index of selected time
     66      !REAL  hour_ini ! fraction of day of stored date. Equivalent of day_ini, but 0=<hour_ini<1
     67
     68      INTEGER edges(4),corner(4)
    6069
    6170c-----------------------------------------------------------------------
     
    102111      pa         = tab_cntrl(17)
    103112      preff      = tab_cntrl(18)
     113     
     114      hour_ini   = tab_cntrl(29)
     115
    104116c
    105117      clon       = tab_cntrl(19)
     
    119131        IF( tab_cntrl(26).EQ.1. ) ysinus = . TRUE.
    120132      ENDIF
     133     
    121134c   .................................................................
    122135c
     
    239252      ENDIF
    240253
     254
     255! read time axis
     256      ierr = nf90_inq_dimid(nid,"Time",nvarid)
     257      ierr = nf90_inquire_dimension(nid,nvarid,len=timelen)
     258
     259      ALLOCATE(time(timelen))
     260
    241261      ierr=nf90_inq_varid(nid,"Time",nvarid)
    242262      IF (ierr .NE. nf90_noerr) THEN
     
    254274         CALL abort
    255275      ENDIF
    256 
     276     
     277! select desired time
     278      IF (timestart .lt. 0) THEN  ! default: we use the last time value
     279        indextime = timelen
     280      ELSE  ! else we look for the desired value in the time axis
     281       indextime = 0
     282        DO i=1,timelen
     283          IF (abs(time(i) - timestart) .lt. 0.01) THEN
     284             indextime = i
     285             EXIT
     286          ENDIF
     287        ENDDO
     288        IF (indextime .eq. 0) THEN
     289          PRINT*, "Time", timestart," is not in "//fichnom//"!!"
     290          PRINT*, "Stored times are:"
     291          DO i=1,timelen
     292             PRINT*, time(i)
     293          ENDDO
     294          CALL abort
     295        ENDIF
     296      ENDIF
     297     
     298      ! In start the absolute date is day_ini + hour_ini + time
     299      ! For now on, in the GCMdynamics, it is day_ini + time0
     300      time0 = time(indextime) + hour_ini
     301      day_ini = day_ini + INT(time0)
     302      time0 = time0 - INT(time0) ! time0 devient le nouveau hour_ini
     303      hour_ini = time0
     304     
     305      PRINT*, "dynetat0: Selected time ",time(indextime),
     306     .        " at index ",indextime
     307     
     308      DEALLOCATE(time)
     309
     310
     311! read vcov
     312      corner(1)=1
     313      corner(2)=1
     314      corner(3)=1
     315      corner(4)=indextime
     316      edges(1)=iip1
     317      edges(2)=jjm
     318      edges(3)=llm
     319      edges(4)=1
     320      ierr=nf90_inq_varid(nid,"vcov",nvarid)
     321      IF (ierr .NE. nf90_noerr) THEN
     322         PRINT*, "dynetat0: Le champ <vcov> est absent"
     323         write(*,*)trim(nf90_strerror(ierr))
     324         CALL abort
     325      ENDIF
     326      !ierr=nf90_get_var(nid,nvarid,vcov)
     327      ierr=nf90_get_var(nid,nvarid,vcov,corner,edges)
     328      IF (ierr .NE. nf90_noerr) THEN
     329         PRINT*, "dynetat0: Lecture echouee pour <vcov>"
     330         write(*,*)trim(nf90_strerror(ierr))
     331         CALL abort
     332      ENDIF
     333     
     334! read ucov
     335      corner(1)=1
     336      corner(2)=1
     337      corner(3)=1
     338      corner(4)=indextime
     339      edges(1)=iip1
     340      edges(2)=jjp1
     341      edges(3)=llm
     342      edges(4)=1
    257343      ierr=nf90_inq_varid(nid,"ucov",nvarid)
    258344      IF (ierr .NE. nf90_noerr) THEN
     
    261347         CALL abort
    262348      ENDIF
    263       ierr=nf90_get_var(nid,nvarid,ucov)
     349      ierr=nf90_get_var(nid,nvarid,ucov,corner,edges)
    264350      IF (ierr .NE. nf90_noerr) THEN
    265351         PRINT*, "dynetat0: Lecture echouee pour <ucov>"
     
    267353         CALL abort
    268354      ENDIF
    269  
    270       ierr=nf90_inq_varid(nid,"vcov",nvarid)
    271       IF (ierr .NE. nf90_noerr) THEN
    272          PRINT*, "dynetat0: Le champ <vcov> est absent"
    273          write(*,*)trim(nf90_strerror(ierr))
    274          CALL abort
    275       ENDIF
    276       ierr=nf90_get_var(nid,nvarid,vcov)
    277       IF (ierr .NE. nf90_noerr) THEN
    278          PRINT*, "dynetat0: Lecture echouee pour <vcov>"
    279          write(*,*)trim(nf90_strerror(ierr))
    280          CALL abort
    281       ENDIF
    282 
     355
     356! read teta
    283357      ierr=nf90_inq_varid(nid,"teta",nvarid)
    284358      IF (ierr .NE. nf90_noerr) THEN
     
    287361         CALL abort
    288362      ENDIF
    289       ierr=nf90_get_var(nid,nvarid,teta)
     363      ierr=nf90_get_var(nid,nvarid,teta,corner,edges)
    290364      IF (ierr .NE. nf90_noerr) THEN
    291365         PRINT*, "dynetat0: Lecture echouee pour <teta>"
     
    294368      ENDIF
    295369
    296 
     370! read tracers
    297371      IF(nq.GE.1) THEN
    298372        write(*,*) 'dynetat0: loading tracers'
     
    318392           ELSE
    319393           !ierr=nf90_get_var(nid,nvarid,q(1,1,1,iq))
    320            ierr=nf90_get_var(nid,nvarid,traceur)
     394           ierr=nf90_get_var(nid,nvarid,traceur,corner,edges)
    321395             IF (ierr .NE. nf90_noerr) THEN
    322396!                 PRINT*, "dynetat0: Lecture echouee pour "//str3
     
    355429      ENDIF
    356430
     431! read masse
    357432      ierr=nf90_inq_varid(nid,"masse",nvarid)
    358433      IF (ierr .NE. nf90_noerr) THEN
     
    361436         CALL abort
    362437      ENDIF
    363       ierr=nf90_get_var(nid,nvarid,masse)
     438      ierr=nf90_get_var(nid,nvarid,masse,corner,edges)
    364439      IF (ierr .NE. nf90_noerr) THEN
    365440         PRINT*, "dynetat0: Lecture echouee pour <masse>"
     
    368443      ENDIF
    369444
     445! read ps
     446      corner(1)=1
     447      corner(2)=1
     448      corner(3)=indextime
     449      edges(1)=iip1
     450      edges(2)=jjp1
     451      edges(3)=1
    370452      ierr=nf90_inq_varid(nid,"ps",nvarid)
    371453      IF (ierr .NE. nf90_noerr) THEN
     
    374456         CALL abort
    375457      ENDIF
    376       ierr=nf90_get_var(nid,nvarid,ps)
     458      ierr=nf90_get_var(nid,nvarid,ps,corner,edges)
    377459      IF (ierr .NE. nf90_noerr) THEN
    378460         PRINT*, "dynetat0: Lecture echouee pour <ps>"
Note: See TracChangeset for help on using the changeset viewer.