source: IOIPSL/trunk/src/restcom.f90 @ 239

Last change on this file since 239 was 236, checked in by bellier, 16 years ago

calendar :

  • modification of tests to get rid of a truncation error in the determination of the date change.
  • addition in "itau2ymds" of a message to inform usage of undefined elements (call with "ioconf_startdate" not done)

restcom :

  • some orthographic correction

JB

  • Property svn:keywords set to Id
File size: 77.3 KB
Line 
1MODULE restcom
2!-
3!$Id$
4!-
5USE netcdf
6!-
7USE errioipsl, ONLY : ipslerr
8USE stringop 
9USE calendar
10USE mathelp
11USE fliocom,   ONLY : flio_dom_file,flio_dom_att
12!-
13IMPLICIT NONE
14!-
15PRIVATE
16!-
17PUBLIC :: &
18 &  restini, restget, restput, restclo, &
19 &  ioconf_setatt, ioget_vname, ioconf_expval, &
20 &  ioget_expval, ioget_vdim
21!-
22INTERFACE restput 
23  MODULE PROCEDURE &
24 &  restput_r3d, restput_r2d, restput_r1d, &
25 &  restput_opp_r2d, restput_opp_r1d
26END INTERFACE
27!-
28INTERFACE restget
29  MODULE PROCEDURE &
30 &  restget_r3d, restget_r2d, restget_r1d, &
31 &  restget_opp_r2d, restget_opp_r1d
32END INTERFACE
33!-
34! We do not use allocatable arrays because these sizes are safe
35! and we do not know from start how many variables will be in
36! the out file.
37!-
38  INTEGER,PARAMETER :: &
39 &  max_var=500, max_file=50, max_dim=NF90_MAX_VAR_DIMS
40!-
41  CHARACTER(LEN=9),SAVE :: calend_str='unknown'
42!-
43! The IDs of the netCDF files are going in pairs.
44! The input one (netcdf_id(?,1)) and the output one (netcdf_id(?,2))
45!-
46  INTEGER,SAVE :: nbfiles = 0 
47  INTEGER,DIMENSION(max_file,2),SAVE :: netcdf_id = -1
48!-
49! Description of the content of the 'in' files and the 'out' files.
50!   Number of variables   : nbvar_*
51!   Number of dimensions  : nbdim_*
52!   ID of the time axis   : tdimid_*
53!-
54  INTEGER,SAVE :: nbvar_in(max_file), nbvar_out(max_file)
55  INTEGER,SAVE :: tdimid_in(max_file), tdimid_out(max_file)
56!-
57! Variables for one or the other file
58!-
59! Number of dimensions in the input file               : nbdim_in
60! Number of variables read so far from the input file  : nbvar_read
61! Type of variable read from the input file            : vartyp_in
62!   (Could be used later to test if we have a restart file)
63!-
64  INTEGER,SAVE :: nbdim_in(max_file), nbvar_read(max_file)
65  INTEGER,SAVE :: vartyp_in(max_file, max_var)
66!-
67! Time step and time origine in the input file.
68!-
69  REAL,DIMENSION(max_file),SAVE :: deltat,timeorig
70!-
71! Description of the axes in the output file
72!-
73!   tstp_out  : Index on the tie axis currently beeing written
74!   itau_out  : Time step which is written on this index of the file
75!-
76  INTEGER,DIMENSION(max_file),SAVE :: tstp_out,itau_out
77!-
78! Description of the axes in the output file
79!-
80! For the ?ax_infs variable the following order is used :
81!   ?ax_infs (if,in,1) = size of axis
82!   ?ax_infs (if,in,2) = id of dimension
83! Number of x,y and z axes in the output file :
84!   ?ax_nb(if)
85!-
86  INTEGER,DIMENSION(max_file,max_dim,2),SAVE :: &
87 &  xax_infs,yax_infs,zax_infs
88  INTEGER,DIMENSION(max_file),SAVE :: &
89 &  xax_nb=0,yax_nb=0,zax_nb=0
90!-
91! Description of the time axes in the input and output files
92!-
93!   ID of the variable which contains the itaus :
94!     tind_varid_*
95!   ID of the variables which contains the seconds since date :
96!     tax_varid_*
97!   Size of the time axis in the input file :
98!     tax_size_in
99!-
100  INTEGER,SAVE :: tind_varid_in(max_file),  tax_varid_in(max_file), &
101 &                tind_varid_out(max_file), tax_varid_out(max_file)
102  INTEGER,SAVE :: tax_size_in(max_file)=1
103!-
104! The two time axes we have in the input file :
105!   t_index   : dates in itaus
106!               (thus the variable has a tstep_sec attribute)
107!   t_julian  : Julian days of the time axis
108!-
109  INTEGER,SAVE,ALLOCATABLE :: t_index(:,:)
110  REAL,SAVE,ALLOCATABLE :: t_julian(:,:)
111!-
112! Here we save a number of informations on the variables
113! in the files we are handling
114!-
115! Name of variables :                                    varname_*
116! ID of the variables :                                  varid_*
117! Number of dimensions of the variable :                 varnbdim_*
118! Dimensions which are used for the variable :           vardims_*
119! Number of attributes for a variables :                 varatt_*
120! A flag which markes the variables we have worked on :  touched_*
121!-
122  CHARACTER(LEN=20),DIMENSION(max_file,max_var),SAVE :: &
123 &  varname_in,varname_out
124  INTEGER,DIMENSION(max_file,max_var),SAVE :: &
125 &  varid_in,varid_out,varnbdim_in,varatt_in
126  INTEGER,DIMENSION(max_file,max_var,max_dim),SAVE :: &
127 &  vardims_in
128  LOGICAL,DIMENSION(max_file,max_var),SAVE :: &
129 &  touched_in,touched_out
130!-
131  CHARACTER(LEN=120),SAVE :: indchfun= 'scatter, fill, gather, coll'
132  REAL,PARAMETER :: missing_val=1.e20
133!                or HUGE(1.0) (maximum real number)
134!-
135! The default value we will use for variables
136! which are not present in the restart file
137!-
138  REAL,SAVE :: val_exp =  999999.
139  LOGICAL,SAVE :: lock_valexp = .FALSE.
140!-
141!- Temporary variables in which we store the attributed
142!- which are going to be given to
143!- a new variable which is going to be defined.
144!-
145  CHARACTER(LEN=80),SAVE :: rest_units='XXXXX',rest_lname='XXXXX'
146!-
147!===
148!-
149CONTAINS
150!-
151SUBROUTINE restini &
152 & (fnamein,iim,jjm,lon,lat,llm,lev, &
153 &  fnameout,itau,date0,dt,fid,owrite_time_in,domain_id)
154!---------------------------------------------------------------------
155!- This subroutine sets up all the restart process.
156!- It will call the subroutine which opens the input
157!- and output files.
158!- The time step (itau), date of origine (date0) and time step are
159!- READ from the input file.
160!- A file ID, which is common to the input and output file is returned
161!-
162!- If fnamein = fnameout then the same file is used for the reading
163!- the restart conditions and writing the new restart.
164!-
165!- A special mode can be switched in with filename='NONE'.
166!- This means that no restart file is present.
167!- Usefull for creating the first restart file
168!- or to get elements in a file without creating an output file.
169!-
170!- A mode needs to be written in which itau, date0 and dt
171!- are given to the restart process and thus
172!- written into the output restart file.
173!-
174!- INPUT
175!-
176!- fnamein  : name of the file for the restart
177!- iim      : Dimension in x
178!- jjm      : Dimension in y
179!- lon      : Longitude in the x,y domain
180!- lat      : Latitude in the x,y domain
181!- llm      : Dimension in the vertical
182!- lev      : Positions of the levels
183!- fnameout :
184!-
185!- OUTPUT
186!-
187!- itau     : Time step of the restart file and at which the model
188!-            should restart
189!- date0    : Time at which itau = 0
190!- dt       : time step in seconds between two succesiv itaus
191!- fid      : File identification of the restart file
192!-
193!- Optional INPUT arguments
194!-
195!- owrite_time_in : logical  argument which allows to
196!-                  overwrite the time in the restart file
197!- domain_id      : Domain identifier
198!---------------------------------------------------------------------
199  IMPLICIT NONE
200!-
201  CHARACTER(LEN=*),INTENT(IN) :: fnamein,fnameout
202  INTEGER :: iim,jjm,llm,fid,itau
203  REAL :: lon(iim,jjm),lat(iim,jjm),lev(llm)
204  REAL :: date0,dt
205  LOGICAL,OPTIONAL :: owrite_time_in
206  INTEGER,INTENT(IN),OPTIONAL :: domain_id
207!-
208! LOCAL
209!-
210  INTEGER :: ncfid
211  REAL :: dt_tmp,date0_tmp
212  INTEGER,ALLOCATABLE :: tmp_index(:,:)
213  REAL,ALLOCATABLE :: tmp_julian(:,:)
214  LOGICAL :: l_fi,l_fo,l_rw
215  LOGICAL :: overwrite_time
216  CHARACTER(LEN=120) :: fname
217  LOGICAL :: check = .FALSE.
218!---------------------------------------------------------------------
219!-
220! 0.0 Prepare the configuration before opening any files
221!-
222  IF (.NOT.PRESENT(owrite_time_in)) THEN
223    overwrite_time = .FALSE.
224  ELSE
225    overwrite_time = owrite_time_in
226  ENDIF
227!-
228  IF (check) THEN
229    WRITE(*,*) 'restini 0.0 : ',TRIM(fnamein),' , ',TRIM(fnameout)
230  ENDIF
231!-
232  nbfiles = nbfiles+1
233!-
234  IF (nbfiles > max_file) THEN
235    CALL ipslerr (3,'restini',&
236 &   'Too many restart files are used. The problem can be',&
237 &   'solved by increasing max_file in restcom.f90 ',&
238 &   'and recompiling ioipsl.')
239  ENDIF
240!-
241! 0.1 Define the open flags
242!-
243  l_fi = (TRIM(fnamein)  /= 'NONE')
244  l_fo = (TRIM(fnameout) /= 'NONE')
245  IF ((.NOT.l_fi).AND.(.NOT.l_fo)) THEN
246    CALL ipslerr (3,'restini',&
247 &   'Input and output file names are both to NONE.',&
248 &   'It is probably an error.','Verify your logic.')
249  ENDIF
250  l_rw = l_fi.AND.l_fo.AND.(TRIM(fnamein) == TRIM(fnameout))
251!-
252  IF (check) THEN
253    WRITE(*,*) 'restini 0.1 l_fi, l_fo, l_rw : ',l_fi,l_fo,l_rw
254  ENDIF
255!-
256! 1.0 Open the input file. 
257!-
258  IF (l_fi) THEN
259!---
260    IF (check) WRITE(*,*) 'restini 1.0 : Open input file' 
261!-- Add DOMAIN number and ".nc" suffix in file names if needed
262    fname = fnamein
263    CALL flio_dom_file (fname,domain_id)
264!-- Open the file
265    CALL restopenin &
266      (nbfiles,fname,l_rw,iim,jjm, &
267       lon,lat,llm,lev,ncfid)
268    netcdf_id(nbfiles,1) = ncfid
269!---
270!-- 1.3 Extract the time information
271!---
272    CALL restsett (nbfiles,dt_tmp,date0_tmp)
273    IF (.NOT.overwrite_time) THEN
274      dt = dt_tmp
275      date0 = date0_tmp
276    ENDIF
277!---
278  ELSE
279!---
280!-- 2.0 The case of a missing restart file is dealt with
281!---         
282    IF (check) WRITE(*,*) 'restini 2.0'
283!---
284    IF (     (ALL(MINLOC(lon(:iim,:jjm)) == MAXLOC(lon(:iim,:jjm)))) &
285        .AND.(iim > 1) ) THEN
286      CALL ipslerr (3,'restini',&
287        & 'For creating a restart file the longitudes of the',&
288        & 'grid need to be provided to restini. This ',&
289        & 'information is needed for the restart files')
290    ENDIF
291    IF (     (ALL(MINLOC(lat(:iim,:jjm)) == MAXLOC(lat(:iim,:jjm)))) &
292        .AND.(jjm > 1) ) THEN
293      CALL ipslerr (3,'restini',&
294        & 'For creating a restart file the latitudes of the',&
295        & 'grid need to be provided to restini. This ',&
296        & 'information is needed for the restart files')
297    ENDIF
298    IF (     (ALL(MINLOC(lev(:llm)) == MAXLOC(lev(:llm)))) &
299        .AND.(llm > 1) ) THEN
300      CALL ipslerr (3,'restini',&
301        & 'For creating a restart file the levels of the',&
302        & 'grid need to be provided to restini. This',&
303        & 'information is needed for the restart files')
304    ENDIF
305!---
306!-- 2.2 Allocate the time axes and write the inputed variables
307!---
308    tax_size_in(nbfiles) = 1
309    IF ( .NOT.ALLOCATED(t_index) .AND. .NOT.ALLOCATED(t_julian) ) THEN
310      IF (check) THEN
311        WRITE(*,*) 'restini : Allocate times axes at :', &
312                   max_file,tax_size_in(nbfiles)
313      ENDIF
314      ALLOCATE(t_index(max_file,tax_size_in(nbfiles)))
315      t_index (:,:) = 0
316      ALLOCATE(t_julian(max_file,tax_size_in(nbfiles)))
317      t_julian (:,:) = 0.0
318    ELSE
319      IF (    (SIZE(t_index,DIM=2)  < tax_size_in(nbfiles)) &
320          .OR.(SIZE(t_julian,DIM=2) < tax_size_in(nbfiles)) ) THEN
321        IF (check) THEN
322          WRITE(*,*) 'restini : Reallocate times axes at :', &
323                     max_file,tax_size_in(nbfiles)
324        ENDIF
325        ALLOCATE(tmp_index(max_file,tax_size_in(nbfiles)))
326        ALLOCATE(tmp_julian(max_file,tax_size_in(nbfiles)))
327        tmp_index(:,:) = t_index(:,:)
328        tmp_julian(:,:) = t_julian(:,:)
329        DEALLOCATE(t_index)
330        DEALLOCATE(t_julian)
331        ALLOCATE(t_index(max_file,tax_size_in(nbfiles)))
332        ALLOCATE(t_julian(max_file,tax_size_in(nbfiles)))
333        t_index(:,:) = tmp_index(:,:)
334        t_julian(:,:) = tmp_julian(:,:)
335      ENDIF
336    ENDIF
337!---
338    t_index(nbfiles,1) = itau
339    t_julian(nbfiles,1) = date0
340!---
341  ENDIF
342!-
343  IF (l_fo.AND.(.NOT.l_rw)) THEN
344!-- Add DOMAIN number and ".nc" suffix in file names if needed
345    fname = fnameout
346    CALL flio_dom_file (fname,domain_id)
347!-- Open the file
348    CALL restopenout &
349      (nbfiles,fname,iim,jjm, &
350       lon,lat,llm,lev,dt,date0,ncfid,domain_id)
351    netcdf_id(nbfiles,2) = ncfid
352  ELSE IF (l_fi.AND.l_fo) THEN
353    netcdf_id(nbfiles,2) = netcdf_id(nbfiles,1)
354    varname_out(nbfiles,:) = varname_in(nbfiles,:) 
355    nbvar_out(nbfiles) = nbvar_in(nbfiles) 
356    tind_varid_out(nbfiles) = tind_varid_in(nbfiles) 
357    tax_varid_out(nbfiles) = tax_varid_in(nbfiles) 
358    varid_out(nbfiles,:) = varid_in(nbfiles,:) 
359    touched_out(nbfiles,:) = .TRUE.
360  ENDIF
361!-
362! 2.3 Set the calendar for the run.
363!     This should not produce any error message if
364!     This does not mean any change in calendar
365!     (to be modified in ioconf_calendar)
366!-
367  IF (check) THEN
368    WRITE(*,*) 'restini 2.3 : Configure calendar if needed : ', &
369                calend_str
370  ENDIF
371!-
372  IF (INDEX(calend_str,'unknown') < 1) THEN
373    CALL ioconf_calendar (calend_str)
374  ENDIF
375!-
376  IF (check) WRITE(*,*) 'After possible calendar configuration'
377!-
378! Save some data in the module
379!-
380  deltat(nbfiles) = dt
381!-
382! Prepare the variables which will be returned
383!-
384  fid = nbfiles
385  IF (check) THEN
386    WRITE(*,*) 'SIZE of t_index :',SIZE(t_index), &
387               SIZE(t_index,dim=1),SIZE(t_index,dim=2)
388  ENDIF
389  itau = t_index(fid,1)
390!-
391  IF (check) WRITE(*,*) 'restini END' 
392!---------------------
393END SUBROUTINE restini
394!-
395!===
396!-
397SUBROUTINE restopenin &
398  (fid,fname,l_rw,iim,jjm,lon,lat,llm,lev,ncfid)
399!---------------------------------------------------------------------
400!- Opens the restart file and checks that it belongsd to the model.
401!- This means that the coordinates of the model are compared to the
402!- ones in the file.
403!-
404!- The number and name of variable in the file are exctracted. Also
405!- the time details.
406!---------------------------------------------------------------------
407  IMPLICIT NONE
408!-
409  INTEGER,INTENT(IN) :: fid,iim,jjm,llm
410  CHARACTER(LEN=*),INTENT(IN) :: fname
411  REAL :: lon(iim,jjm),lat(iim,jjm),lev(llm)
412  LOGICAL,INTENT(IN) :: l_rw
413  INTEGER,INTENT(OUT) :: ncfid
414!-
415! LOCAL
416!-
417  INTEGER :: var_dims(max_dim),dimlen(max_dim)
418  INTEGER :: nb_dim,nb_var,id_unl,id,iv
419  INTEGER :: iread,jread,lread,iret,idi
420  INTEGER :: lon_vid,lat_vid
421  REAL :: lon_read(iim,jjm),lat_read(iim,jjm)
422  REAL :: lev_read(llm)
423  REAL :: mdlon,mdlat
424  CHARACTER(LEN=80) :: units,dimname
425  LOGICAL :: check = .FALSE.
426!---------------------------------------------------------------------
427!-
428! If we reuse the same file for input and output
429! then we open it in write mode
430!-
431  IF (l_rw) THEN; id = NF90_WRITE; ELSE; id = NF90_NOWRITE; ENDIF
432  iret = NF90_OPEN(fname,id,ncfid)
433  IF (iret /= NF90_NOERR) THEN
434    CALL ipslerr (3,'restopenin','Could not open file :',fname,' ')
435  ENDIF
436!-
437  IF (check) WRITE (*,*) "restopenin 0.0 ",TRIM(fname)
438  iret = NF90_INQUIRE(ncfid,nDimensions=nb_dim, &
439 &         nVariables=nb_var,unlimitedDimId=id_unl)
440  tdimid_in(fid) = id_unl
441!-
442  IF (nb_dim > max_dim) THEN
443    CALL ipslerr (3,'restopenin',&
444      & 'More dimensions present in file that can be store',&
445      & 'Please increase max_dim in the global variables ',&
446      & ' in restcom.F90')
447  ENDIF
448  IF (nb_var > max_var) THEN
449    CALL ipslerr (3,'restopenin',&
450      & 'More variables present in file that can be store',&
451      & 'Please increase max_var in the global variables ',&
452      & 'in restcom.F90')
453  ENDIF
454!-
455  nbvar_in(fid) = nb_var
456  nbdim_in(fid) = nb_dim
457  DO idi=1,nb_dim
458    iret = NF90_INQUIRE_DIMENSION(ncfid,idi,len=dimlen(idi))
459  ENDDO
460  iread = dimlen(1)
461  jread = dimlen(2)
462  lread = dimlen(3)
463!-
464  IF (id_unl > 0) THEN
465!---
466!-- 0.1 If we are going to add values to this file
467!--     we need to know where it ends
468!--     We also need to have all the dimensions in the file
469!---
470    IF (l_rw) THEN
471      iret = NF90_INQUIRE_DIMENSION(ncfid,id_unl,len=tstp_out(fid))
472      itau_out(fid) = -1
473      tdimid_out(fid) =  tdimid_in(fid) 
474!-----
475      xax_nb(fid) = 0
476      yax_nb(fid) = 0
477      zax_nb(fid) = 0
478!-----
479      DO id=1,nb_dim
480        iret = NF90_INQUIRE_DIMENSION(ncfid,id,name=dimname)
481        IF      (dimname(1:1) == 'x') THEN
482          xax_nb(fid) = xax_nb(fid)+1
483          iret = NF90_INQUIRE_DIMENSION &
484 &                 (ncfid,id,len=xax_infs(fid,xax_nb(fid),1))
485          xax_infs(fid,xax_nb(fid),2) = id
486        ELSE IF (dimname(1:1) == 'y') THEN
487          yax_nb(fid) = yax_nb(fid)+1
488          iret = NF90_INQUIRE_DIMENSION &
489 &                 (ncfid,id,len=yax_infs(fid,yax_nb(fid),1))
490          yax_infs(fid,yax_nb(fid),2) = id
491        ELSE IF (dimname(1:1) == 'z') THEN
492          zax_nb(fid) = zax_nb(fid)+1
493          iret = NF90_INQUIRE_DIMENSION &
494 &                 (ncfid,id,len=zax_infs(fid,zax_nb(fid),1))
495          zax_infs(fid,zax_nb(fid),2) = id
496        ENDIF
497      ENDDO
498    ENDIF
499  ELSE
500!---
501!-- Still need to find a method for dealing with this
502!---
503!  CALL ipslerr (3,'restopenin',&
504!    & ' We do not deal yet with files without time axis.',' ',' ')
505  ENDIF
506!-
507! 1.0 First let us check that we have the righ restart file
508!-
509  IF (iread /= iim .OR. jread /= jjm .OR. lread /= llm) THEN
510    CALL ipslerr (3,'restopenin',&
511 &    'The grid of the restart file does not correspond',&
512 &    'to that of the model',' ')
513  ENDIF
514!-
515! We know that we have a time axis. Thus the 4th dimension needs
516! to be the levels.
517!-
518  IF (nb_dim > 3 .AND. dimlen(3) /= llm) THEN
519    CALL ipslerr (3,'restopenin',&
520 &    'The grid of the restart file does not correspond',&
521 &    'to that of the model',' ')
522  ENDIF
523!-
524! 2.0 Get the list of variables
525!-
526  IF (check) WRITE(*,*) 'restopenin 1.2'
527!-
528  lat_vid = -1
529  lon_vid = -1
530  tind_varid_in(fid) = -1
531  tax_varid_in(fid) = -1
532!-
533  DO iv=1,nb_var
534!---
535    varid_in(fid,iv) = iv
536    var_dims(:) = 0
537    iret = NF90_INQUIRE_VARIABLE(ncfid,iv, &
538 &           name=varname_in(fid,iv),xtype=vartyp_in(fid,iv), &
539 &           ndims=varnbdim_in(fid,iv),dimids=var_dims, &
540 &           nAtts=varatt_in(fid,iv))
541!---
542    DO id=1,varnbdim_in(fid,iv)
543      iret = NF90_INQUIRE_DIMENSION &
544 &             (ncfid,var_dims(id),len=vardims_in(fid,iv,id))
545    ENDDO
546!---
547!-- 2.1 Read the units of the variable
548!---
549    units=''
550    iret = NF90_GET_ATT(ncfid,iv,'units',units)
551    CALL strlowercase (units)
552    CALL cmpblank (units)
553!---
554!-- 2.2 Catch the time variables
555!---
556    IF (varnbdim_in(fid,iv) == 1) THEN
557      IF (     (INDEX(units,'timesteps since') > 0) &
558          .AND.(tind_varid_in(fid) < 0) ) THEN
559        tind_varid_in(fid) = iv
560        tax_size_in(fid) = vardims_in(fid,iv,1)
561      ENDIF
562      IF (     (INDEX(units,'seconds since') > 0) &
563          .AND.(tax_varid_in(fid) < 0) ) THEN   
564        tax_varid_in(fid) = iv
565        tax_size_in(fid) = vardims_in(fid,iv,1)
566      ENDIF
567    ENDIF
568!---
569!-- 2.3 Catch longitude and latitude variables
570!---
571    IF (INDEX(units,'degrees_nort') >= 1) THEN
572      lat_vid = iv
573    ENDIF
574    IF (INDEX(units,'degrees_east') >= 1) THEN
575      lon_vid = iv
576    ENDIF
577!---
578  ENDDO
579!-
580! 2.4 None of the variables was yet read
581!-
582  nbvar_read(fid) = 0
583  touched_in(fid,:) = .FALSE.
584!-
585! 3.0 Reading the coordinates from the input restart file
586!-
587  lon_read = missing_val
588  lat_read = missing_val
589!-
590  IF (lon_vid < 0 .OR. lat_vid < 0) THEN
591    CALL ipslerr (3,'restopenin',&
592      & ' No variables containing longitude or latitude were ',&
593      & ' found in the restart file.',' ')
594  ELSE
595    iret = NF90_GET_VAR(ncfid,lon_vid,lon_read)
596    iret = NF90_GET_VAR(ncfid,lat_vid,lat_read)
597!---
598    IF (  (ABS( MAXVAL(lon(:,:)) &
599 &             -MINVAL(lon(:,:))) < EPSILON(MAXVAL(lon(:,:)))) &
600 &   .AND.(ABS( MAXVAL(lat(:,:)) &
601 &             -MINVAL(lat(:,:))) < EPSILON(MAXVAL(lat(:,:)))) ) THEN
602!-----
603!---- 3.1 No longitude nor latitude are provided thus
604!---- they are taken from the restart file
605!-----
606      lon(:,:) = lon_read(:,:)
607      lat(:,:) = lat_read(:,:)
608    ELSE
609!-----
610!---- 3.2 We check that the longitudes and latitudes
611!----     in the file and the model are the same
612!-----
613      mdlon = MAXVAL(ABS(lon_read-lon))
614      mdlat = MAXVAL(ABS(lat_read-lat))
615!-----
616!---- We can not test against epsilon here as the longitude
617!---- can be stored at another precision in the netCDF file.
618!---- The test here does not need to be very precise.           
619!-----
620      IF (mdlon > 1.e-4 .OR. mdlat > 1.e-4) THEN
621        CALL ipslerr (3,'restopenin',&
622          & ' The longitude or latitude found in the restart ',&
623          & ' file are not the same as the ones used in the model.',&
624          & ' ')
625      ENDIF
626    ENDIF
627  ENDIF
628!------------------------
629END SUBROUTINE restopenin
630!-
631!===
632!-
633SUBROUTINE restsett (fid,timestep,date0)
634!---------------------------------------------------------------------
635!- Here we get all the time information from the file.
636!-
637!- The time information can come in three forms :
638!- -global attributes which give the time origine and the
639!-  time step is taken from the input to restinit
640!- -A physical time exists and thus the julian date from the
641!-  input is used for positioning using the itau as input
642!- -A time-step axis exists and itau is positioned on it.
643!-
644!- What takes precedence ? No idea yet !
645!---------------------------------------------------------------------
646  IMPLICIT NONE
647!-
648  INTEGER :: fid
649  REAL :: date0,timestep
650!-
651! LOCAL
652!-
653  INTEGER :: ncfid,iret,it,iax,iv,tszij
654  INTEGER,ALLOCATABLE :: tmp_index(:,:)
655  REAL,ALLOCATABLE :: tmp_julian(:,:)
656  CHARACTER(LEN=80) :: itau_orig,tax_orig,calendar
657  CHARACTER(LEN=9) :: tmp_cal
658  INTEGER :: year0,month0,day0,hours0,minutes0,seci
659  REAL :: sec0,un_jour,un_an,date0_ju,ttmp
660  CHARACTER :: strc
661!-
662  LOGICAL :: check = .FALSE.
663!---------------------------------------------------------------------
664!-
665  ncfid = netcdf_id(fid,1)
666!-
667!  Allocate the space we need for the time axes
668!-
669  IF (.NOT.ALLOCATED(t_index) .AND. .NOT.ALLOCATED(t_julian) ) THEN
670    IF (check) THEN
671      WRITE(*,*) 'restsett : Allocate times axes at :', &
672                 max_file,tax_size_in(fid)
673    ENDIF
674    ALLOCATE(t_index(max_file,tax_size_in(fid)))
675    ALLOCATE(t_julian(max_file,tax_size_in(fid)))
676  ELSE
677    tszij = SIZE(t_index,DIM=2)
678    IF (tszij < tax_size_in(fid)) THEN
679      IF (check) THEN
680        WRITE(*,*) 'restsett : Reallocate times axes at :', &
681                   max_file,tax_size_in(fid)
682      ENDIF
683      ALLOCATE(tmp_index(max_file,tax_size_in(fid)))
684      ALLOCATE(tmp_julian(max_file,tax_size_in(fid)))
685      tmp_index(:,1:tszij) = t_index(:,1:tszij)
686      tmp_julian(:,1:tszij) = t_julian(:,1:tszij)
687      DEALLOCATE(t_index)
688      DEALLOCATE(t_julian)
689      ALLOCATE(t_index(max_file,tax_size_in(fid)))
690      ALLOCATE(t_julian(max_file,tax_size_in(fid)))
691      t_index(:,:) = tmp_index(:,:)
692      t_julian(:,:) = tmp_julian(:,:)
693    ENDIF
694  ENDIF
695!-
696! Get the calendar if possible. Else it will be gregorian.
697!-
698  IF (tax_size_in(fid) > 0 ) THEN
699     calendar = 'XXXXX'
700     iret = NF90_GET_ATT(ncfid,tax_varid_in(fid),'calendar',calendar)
701     IF ( INDEX(calendar,'XXXXX') < 0 ) THEN
702       CALL ioconf_calendar (calendar)
703     ENDIF
704  ENDIF
705  CALL ioget_calendar (un_an,un_jour)
706!-
707  itau_orig = 'XXXXX'
708  tax_orig  = 'XXXXX'
709!-
710! Get the time steps of the time axis if available on the restart file
711!-
712  IF (tind_varid_in(fid) > 0) THEN
713    iret = NF90_GET_VAR(ncfid,tind_varid_in(fid),t_index(fid,:))
714    iret = NF90_GET_ATT(ncfid,tind_varid_in(fid),'units',itau_orig)
715    itau_orig = &
716      itau_orig(INDEX(itau_orig,'since')+6:LEN_TRIM(itau_orig))
717    iret = &
718 &    NF90_GET_ATT(ncfid,tind_varid_in(fid),'tstep_sec',timestep)
719!---
720!-- This time origin will dominate as it is linked to the time steps.
721!---
722    READ (UNIT=itau_orig,FMT='(I4.4,5(a,I2.2))') &
723 &    year0,strc,month0,strc,day0,strc, &
724 &    hours0,strc,minutes0,strc,seci
725    sec0 = REAL(seci)
726    sec0 = hours0*3600.+minutes0*60.+sec0
727    CALL ymds2ju (year0,month0,day0,sec0,date0)
728  ENDIF
729!-
730! If a julian day time axis is available then we get it
731!-
732  IF (tax_varid_in(fid) > 0) THEN
733    iret = NF90_GET_VAR(ncfid,tax_varid_in(fid),t_julian(fid,:))
734    iret = NF90_GET_ATT(ncfid,tax_varid_in(fid),'units',tax_orig)
735    tax_orig = tax_orig(INDEX(tax_orig,'since')+6:LEN_TRIM(tax_orig))
736    iret = NF90_GET_ATT(ncfid,tax_varid_in(fid),'calendar',tmp_cal)
737!---
738    CALL strlowercase (tmp_cal)
739    IF (INDEX(calend_str,tmp_cal) < 0) THEN
740      IF (INDEX(calend_str,'unknown') > 0) THEN
741        calend_str = tmp_cal
742      ELSE
743        CALL ipslerr (3,'restsett', &
744 &       ' In the restart files two different calendars were found.', &
745 &       ' Please check the files you have used',' ')
746      ENDIF
747    ENDIF
748!---
749!-- We need to transform that into julian days
750!-- to get ride of the intial date.
751!---
752    IF (check) WRITE(*,*) 'tax_orig : ',TRIM(tax_orig)
753    READ (UNIT=tax_orig,FMT='(I4.4,5(a,I2.2))') &
754      year0,strc,month0,strc,day0,strc, &
755      hours0,strc,minutes0,strc,seci
756    sec0 = REAL(seci)
757    sec0 = hours0*3600.+minutes0*60.+sec0
758    CALL ymds2ju (year0,month0,day0,sec0,date0_ju)
759    t_julian(fid,:) = t_julian(fid,:)/un_jour+date0_ju
760  ENDIF
761!-
762  IF (     (INDEX(itau_orig,'XXXXX') > 0) &
763      .AND.(INDEX(tax_orig,'XXXXX')  < 0) ) THEN
764!!- Compute the t_itau from the date read and the timestep in the input
765  ENDIF
766!-
767  IF (     (INDEX(tax_orig,'XXXXX')  > 0) &
768      .AND.(INDEX(itau_orig,'XXXXX') < 0) ) THEN
769    DO it=1,tax_size_in(fid)
770      t_julian(fid,it) = itau2date(t_index(fid,it),date0,timestep)
771    ENDDO
772  ENDIF
773!-
774! If neither the indices or time is present then get global attributes
775! This is for compatibility reasons and should not be used.
776!-
777  IF ( (tax_varid_in(fid) < 0) .AND. (tind_varid_in(fid) < 0) ) THEN
778    iax = -1
779    DO iv=1,nbvar_in(fid)
780      IF (INDEX(varname_in(fid,iv),'tsteps') > 0) THEN
781        iax = iv
782      ENDIF
783    ENDDO
784!---
785    IF (iax < 0) THEN
786      CALL ipslerr (3,'restsett',&
787        & 'No time axis was found in the restart file. Please check',&
788        & 'that it corresponds to the convention used in restsett',&
789        & ' ')
790    ELSE
791      iret = NF90_GET_VAR(ncfid,tind_varid_in(fid),t_index(fid,:))
792!---
793      iret = NF90_GET_ATT(ncfid,NF90_GLOBAL,'delta_tstep_sec',timestep)
794      iret = NF90_GET_ATT(ncfid,NF90_GLOBAL,'year0',ttmp)
795      year0 = NINT(ttmp)
796      iret = NF90_GET_ATT(ncfid,NF90_GLOBAL,'month0',ttmp)
797      month0 = NINT(ttmp)
798      iret = NF90_GET_ATT(ncfid,NF90_GLOBAL,'day0',ttmp)
799      day0 = NINT(ttmp) 
800      iret = NF90_GET_ATT(ncfid,NF90_GLOBAL,'sec0',sec0)
801!---
802      CALL ymds2ju (year0,month0,day0,sec0,date0)
803      t_julian(fid,1) = itau2date(t_index(fid,1),date0,timestep)
804    ENDIF
805  ENDIF
806!----------------------
807END SUBROUTINE restsett
808!-
809!===
810!-
811SUBROUTINE restopenout &
812  (fid,fname,iim,jjm, &
813   lon,lat,llm,lev,timestep,date,ncfid,domain_id)
814!---------------------------------------------------------------------
815!- Opens the restart file for output.
816!- The longitude and time variables are written.
817!---------------------------------------------------------------------
818  IMPLICIT NONE
819!-
820  INTEGER,INTENT(IN) :: fid,iim,jjm,llm
821  CHARACTER(LEN=*) :: fname
822  REAL :: date,timestep
823  REAL :: lon(iim,jjm),lat(iim,jjm),lev(llm)
824  INTEGER,INTENT(OUT) :: ncfid
825  INTEGER,INTENT(IN),OPTIONAL :: domain_id
826!-
827! LOCAL
828!-
829  INTEGER :: iret
830  CHARACTER(LEN=70) :: str_t
831  INTEGER :: x_id,y_id,z_id,itauid
832  INTEGER :: nlonid,nlatid,nlevid,timeid
833  INTEGER :: year,month,day,hours,minutes
834  REAL :: sec
835  CHARACTER(LEN=3),DIMENSION(12) :: &
836    cal = (/'JAN','FEB','MAR','APR','MAY','JUN', &
837            'JUL','AUG','SEP','OCT','NOV','DEC'/)
838  CHARACTER(LEN=30) :: timenow,conv
839  LOGICAL :: check = .FALSE.
840!---------------------------------------------------------------------
841  IF (check) WRITE(*,*) "restopenout 0.0 ",TRIM(fname)
842!-
843!  If we use the same file for input and output
844!- we will not even call restopenout
845!-
846  iret = NF90_CREATE(fname,NF90_NOCLOBBER,ncfid)
847  IF (iret == -35) THEN
848    CALL ipslerr (3,'restopenout',&
849      & ' The restart file aready exists on the disc. IOIPSL ',&
850      & ' will not overwrite it. You should remove the old one or ',&
851      & ' generate the new one with another name')
852  ENDIF
853!-
854  iret = NF90_DEF_DIM(ncfid,'x',iim,x_id)
855  xax_nb(fid) = xax_nb(fid)+1
856  xax_infs(fid,xax_nb(fid),1) = iim
857  xax_infs(fid,xax_nb(fid),2) = x_id
858!-
859  iret = NF90_DEF_DIM(ncfid,'y',jjm,y_id)
860  yax_nb(fid)  = yax_nb(fid)+1
861  yax_infs(fid,yax_nb(fid),1) = jjm
862  yax_infs(fid,yax_nb(fid),2) = y_id
863!-
864  iret = NF90_DEF_DIM(ncfid,'z',llm,z_id)
865  zax_nb(fid) = zax_nb(fid)+1
866  zax_infs(fid,zax_nb(fid),1) = llm
867  zax_infs(fid,zax_nb(fid),2) = z_id
868!-
869  iret = NF90_DEF_DIM(ncfid,'time',NF90_UNLIMITED,tdimid_out(fid))
870!-
871! 1.0 Longitude
872!-
873  IF (check) WRITE(*,*) "restopenout 1.0"
874!-
875  iret = NF90_DEF_VAR(ncfid,"nav_lon",NF90_FLOAT, &
876 &                     (/ x_id, y_id /),nlonid)
877  iret = NF90_PUT_ATT(ncfid,nlonid,'units',"degrees_east")
878  iret = NF90_PUT_ATT(ncfid,nlonid,'valid_min',REAL(-180.,KIND=4))
879  iret = NF90_PUT_ATT(ncfid,nlonid,'valid_max',REAL( 180.,KIND=4))
880  iret = NF90_PUT_ATT(ncfid,nlonid,'long_name',"Longitude")
881!-
882! 2.0 Latitude
883!-
884  IF (check) WRITE(*,*) "restopenout 2.0"
885!-
886  iret = NF90_DEF_VAR(ncfid,"nav_lat",NF90_FLOAT, &
887 &                     (/ x_id, y_id /),nlatid)
888  iret = NF90_PUT_ATT(ncfid,nlatid,'units',"degrees_north")
889  iret = NF90_PUT_ATT(ncfid,nlatid,'valid_min',REAL(-90.,KIND=4))
890  iret = NF90_PUT_ATT(ncfid,nlatid,'valid_max',REAL( 90.,KIND=4))
891  iret = NF90_PUT_ATT(ncfid,nlatid,'long_name',"Latitude")
892!-
893! 3.0 Levels
894!-
895  IF (check) WRITE(*,*) "restopenout 3.0"
896!-
897  iret = NF90_DEF_VAR(ncfid,"nav_lev",NF90_FLOAT,z_id,nlevid)
898  iret = NF90_PUT_ATT(ncfid,nlevid,'units',"model_levels")
899  iret = NF90_PUT_ATT(ncfid,nlevid,'valid_min', &
900 &                     REAL(MINVAL(lev),KIND=4))
901  iret = NF90_PUT_ATT(ncfid,nlevid,'valid_max', &
902 &                     REAL(MAXVAL(lev),KIND=4))
903  iret = NF90_PUT_ATT(ncfid,nlevid,'long_name',"Model levels")
904!-
905! 4.0 Time axis, this is the seconds since axis
906!-
907  IF (check) WRITE(*,*) "restopenout 4.0"
908!-
909  iret = NF90_DEF_VAR(ncfid,"time",NF90_FLOAT, &
910                       tdimid_out(fid),timeid)
911  tax_varid_out(fid) = timeid
912!-
913  timeorig(fid) = date
914  CALL ju2ymds (date,year,month,day,sec)
915  hours   = INT(sec/(60.*60.))
916  minutes = INT((sec-hours*60.*60.)/60.)
917  sec     = sec-(hours*60.*60.+minutes*60.)
918  WRITE (UNIT=str_t, &
919   FMT='("seconds since ",I4.4,2("-",I2.2)," ",I2.2,2(":",I2.2))') &
920 &  year,month,day,hours,minutes,INT(sec)
921  iret = NF90_PUT_ATT(ncfid,timeid,'units',TRIM(str_t))
922!-
923  CALL ioget_calendar (str_t)
924  iret = NF90_PUT_ATT(ncfid,timeid,'calendar',TRIM(str_t))
925  iret = NF90_PUT_ATT(ncfid,timeid,'title','Time')
926  iret = NF90_PUT_ATT(ncfid,timeid,'long_name','Time axis')
927!-
928  WRITE(UNIT=str_t, &
929   FMT='(" ",I4.4,"-",A3,"-",I2.2," ",I2.2,2(":",I2.2))') &
930 &  year,cal(month),day,hours,minutes,INT(sec)
931  iret = NF90_PUT_ATT(ncfid,timeid,'time_origin',TRIM(str_t))
932!-
933! 5.0 Time axis, this is the time steps since axis
934!-
935  IF (check) WRITE(*,*) "restopenout 5.0"
936!-
937  iret = NF90_DEF_VAR(ncfid,"time_steps",NF90_INT, &
938 &                    tdimid_out(fid),itauid)
939  tind_varid_out(fid) = itauid
940!-
941  CALL ju2ymds (date,year,month,day,sec)
942!-
943  hours   = INT(sec/(60.*60.))
944  minutes = INT((sec-hours*60.*60.)/60.)
945  sec     = sec-(hours*60.*60.+minutes*60.)
946!-
947  WRITE (UNIT=str_t, &
948   FMT='("timesteps since ",I4.4,2("-",I2.2)," ",I2.2,2(":",I2.2))') &
949 &  year,month,day,hours,minutes,INT(sec)
950!-
951  iret = NF90_PUT_ATT(ncfid,itauid,'units',TRIM(str_t))
952  iret = NF90_PUT_ATT(ncfid,itauid,'title','Time steps')
953  iret = NF90_PUT_ATT(ncfid,itauid,'tstep_sec',REAL(timestep,KIND=4))
954  iret = NF90_PUT_ATT(ncfid,itauid,'long_name','Time step axis')
955!-
956  WRITE(UNIT=str_t, &
957   FMT='(" ",I4.4,"-",A3,"-",I2.2," ",I2.2,2(":",I2.2))') &
958 &  year,cal(month),day,hours,minutes,INT(sec)
959  iret = NF90_PUT_ATT(ncfid,itauid,'time_origin',TRIM(str_t))
960!-
961!  5.2 Write global attributes
962!-
963  conv='GDT 1.2'
964  iret = NF90_PUT_ATT(ncfid,NF90_GLOBAL,'Conventions',TRIM(conv))
965  iret = NF90_PUT_ATT(ncfid,NF90_GLOBAL,'file_name',TRIM(fname))
966!!  TO BE DONE LATER
967!!   iret = NF90_PUT_ATT(ncfid,NF90_GLOBAL, &
968!!                       'production',TRIM(model_name))
969!!   lock_modname = .TRUE.
970  CALL ioget_timestamp (timenow)
971  iret = NF90_PUT_ATT(ncfid,NF90_GLOBAL,'TimeStamp',TRIM(timenow))
972!-
973! Add DOMAIN attributes if needed
974!-
975  CALL flio_dom_att (ncfid,domain_id)
976!-
977! 6.0 The coordinates are written to the file
978!-
979  iret = NF90_ENDDEF(ncfid)
980!-
981  iret = NF90_PUT_VAR(ncfid,nlonid,lon)
982  iret = NF90_PUT_VAR(ncfid,nlatid,lat)
983  iret = NF90_PUT_VAR(ncfid,nlevid,lev)
984!-
985! 7.0 Set a few variables related to the out file
986!-
987  nbvar_out(fid) = 0
988  itau_out(fid) = -1
989  tstp_out(fid) = 0
990  touched_out(fid,:) = .FALSE.
991!-
992! 7.1 The file is put back in define mode.
993!     This will last until itau_out >= 0
994!-
995  iret = NF90_REDEF(ncfid)
996!-
997  IF (check) WRITE(*,*) "restopenout END"
998!-------------------------
999END SUBROUTINE restopenout
1000!-
1001!===
1002!-
1003SUBROUTINE restget_opp_r1d &
1004  (fid,vname_q,iim,jjm,llm,itau,def_beha, &
1005   var,OPERATOR,nbindex,ijndex)
1006!---------------------------------------------------------------------
1007!- This subroutine serves as an interface to restget_real
1008!-
1009!- Should work as restput_opp_r1d but the other way around !
1010!---------------------------------------------------------------------
1011  IMPLICIT NONE
1012!-
1013  INTEGER :: fid
1014  CHARACTER(LEN=*) :: vname_q
1015  INTEGER :: iim,jjm,llm,itau
1016  LOGICAL def_beha
1017  REAL :: var(:)
1018  CHARACTER(LEN=*) :: OPERATOR
1019  INTEGER :: nbindex,ijndex(nbindex)
1020!-
1021!- LOCAL
1022!-
1023  INTEGER :: req_sz
1024  REAL,ALLOCATABLE,SAVE :: buff_tmp(:),buff_tmp2(:)
1025  REAL :: scal
1026  CHARACTER(LEN=7) :: topp
1027  LOGICAL :: check = .FALSE.
1028!---------------------------------------------------------------------
1029!-
1030!  0.0 What size should be the data in the file
1031!-
1032  req_sz = 1
1033  IF (nbindex == iim .AND. jjm <= 1 .AND. llm <= 1) THEN
1034    IF (xax_infs(fid,1,1) > 0) req_sz = req_sz*xax_infs(fid,1,1)
1035    IF (yax_infs(fid,1,1) > 0) req_sz = req_sz*yax_infs(fid,1,1)
1036    IF (zax_infs(fid,1,1) > 0) req_sz = req_sz*zax_infs(fid,1,1)
1037  ELSE
1038    CALL ipslerr (3,'resget_opp_r1d', &
1039      'Unable to performe an operation on this variable as it has',&
1040      'a second and third dimension',vname_q)
1041  ENDIF
1042!-
1043!  1.0 Allocate the temporary buffer we need
1044!      to put the variable in right dimension
1045!-
1046  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1047    IF (check) THEN
1048      WRITE(*,*) "restget_opp_r1d : allocate buff_tmp = ",SIZE(var)
1049    ENDIF
1050    ALLOCATE(buff_tmp(SIZE(var)))
1051  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
1052    IF (check) THEN
1053      WRITE(*,*) "restget_opp_r1d : re-allocate buff_tmp= ",SIZE(var)
1054    ENDIF
1055    DEALLOCATE(buff_tmp)
1056    ALLOCATE(buff_tmp(SIZE(var)))
1057  ENDIF
1058!-
1059  IF (.NOT.ALLOCATED(buff_tmp2)) THEN
1060    IF (check) THEN
1061      WRITE(*,*) "restget_opp_r1d : allocate buff_tmp2 = ",req_sz
1062    ENDIF
1063    ALLOCATE(buff_tmp2(req_sz))
1064  ELSE IF (req_sz > SIZE(buff_tmp2)) THEN
1065    IF (check) THEN
1066      WRITE(*,*) "restget_opp_r1d : re-allocate buff_tmp2= ",req_sz
1067    ENDIF
1068    DEALLOCATE(buff_tmp2)
1069    ALLOCATE(buff_tmp2(req_sz))
1070  ENDIF
1071!-
1072! 2.0 Here we get the variable from the restart file
1073!-
1074  CALL restget_real &
1075    (fid,vname_q,xax_infs(fid,1,1),yax_infs(fid,1,1), &
1076     zax_infs(fid,1,1),itau,def_beha,buff_tmp2)
1077!-
1078!  4.0 Transfer the buffer obtained from the restart file
1079!      into the variable the model expects
1080!-
1081  topp = OPERATOR(1:MIN(LEN_TRIM(OPERATOR),7))
1082!-
1083  IF (INDEX(indchfun,topp(:LEN_TRIM(topp))) > 0) THEN
1084    scal = missing_val
1085!---
1086    CALL mathop (topp,req_sz,buff_tmp2,missing_val, &
1087                 nbindex,ijndex,scal,SIZE(var),buff_tmp)
1088!---
1089    var(:) = buff_tmp(:) 
1090  ELSE
1091    CALL ipslerr (3,'resget_opp_r1d', &
1092      'The operation you wish to do on the variable for the ',&
1093      'restart file is not allowed.',topp)
1094  ENDIF
1095!-----------------------------
1096END SUBROUTINE restget_opp_r1d
1097!-
1098!===
1099!-
1100SUBROUTINE restget_opp_r2d &
1101  (fid,vname_q,iim,jjm,llm,itau,def_beha, &
1102   var,OPERATOR,nbindex,ijndex)
1103!---------------------------------------------------------------------
1104!- This subroutine serves as an interface to restget_real
1105!-
1106!- Should work as restput_opp_r2d but the other way around !
1107!---------------------------------------------------------------------
1108  IMPLICIT NONE
1109!-
1110  INTEGER :: fid
1111  CHARACTER(LEN=*) :: vname_q
1112  INTEGER :: iim,jjm,llm,itau
1113  LOGICAL def_beha
1114  REAL :: var(:,:)
1115  CHARACTER(LEN=*) :: OPERATOR
1116  INTEGER :: nbindex,ijndex(nbindex)
1117!-
1118!- LOCAL
1119!-
1120  INTEGER :: jj,req_sz,ist,var_sz
1121  REAL,ALLOCATABLE,SAVE :: buff_tmp(:),buff_tmp2(:)
1122  REAL :: scal
1123  CHARACTER(LEN=7) :: topp
1124  LOGICAL :: check = .FALSE.
1125!---------------------------------------------------------------------
1126!-
1127!  0.0 What size should be the data in the file
1128!-
1129  req_sz = 1
1130  IF (nbindex == iim  .AND. llm <= 1) THEN
1131    IF (xax_infs(fid,1,1) > 0) req_sz = req_sz*xax_infs(fid,1,1)
1132    IF (yax_infs(fid,1,1) > 0) req_sz = req_sz*yax_infs(fid,1,1)
1133  ELSE
1134    CALL ipslerr (3,'resget_opp_r2d', &
1135      'Unable to performe an operation on this variable as it has', &
1136      'a second and third dimension',vname_q)
1137  ENDIF
1138!-
1139  IF (jjm < 1) THEN
1140    CALL ipslerr (3,'resget_opp_r2d', &
1141      'Please specify a second dimension which is the', &
1142      'layer on which the operations are performed',vname_q)
1143  ENDIF
1144!-
1145! 1.0 Allocate the temporary buffer we need
1146!     to put the variable in right dimension
1147!-
1148  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1149    IF (check) THEN
1150      WRITE(*,*) "restget_opp_r2d : allocate buff_tmp = ",SIZE(var,1)
1151    ENDIF
1152    ALLOCATE(buff_tmp(SIZE(var,1)))
1153  ELSE IF (SIZE(var,1) > SIZE(buff_tmp)) THEN
1154    IF (check) THEN
1155      WRITE(*,*) "restget_opp_r2d : re-allocate buff_tmp= ",SIZE(var,1)
1156    ENDIF
1157    DEALLOCATE(buff_tmp)
1158    ALLOCATE(buff_tmp(SIZE(var,1)))
1159  ENDIF
1160!-
1161  IF (.NOT.ALLOCATED(buff_tmp2)) THEN
1162    IF (check) THEN
1163      WRITE(*,*) "restget_opp_r2d : allocate buff_tmp2 = ",req_sz*jjm
1164    ENDIF
1165    ALLOCATE(buff_tmp2(req_sz*jjm))
1166  ELSE IF (req_sz*jjm > SIZE(buff_tmp2)) THEN
1167    IF (check) THEN
1168      WRITE(*,*) "restget_opp_r2d : re-allocate buff_tmp2= ",req_sz*jjm
1169    ENDIF
1170    DEALLOCATE(buff_tmp2)
1171    ALLOCATE(buff_tmp2(req_sz*jjm))
1172  ENDIF
1173!-
1174! 2.0 Here we get the full variable from the restart file
1175!-
1176  CALL restget_real &
1177    (fid,vname_q,xax_infs(fid,1,1),yax_infs(fid,1,1), &
1178     jjm,itau,def_beha,buff_tmp2)
1179!-
1180!  4.0 Transfer the buffer obtained from the restart file
1181!      into the variable the model expects
1182!-
1183  topp = OPERATOR(1:MIN(LEN_TRIM(OPERATOR),7))
1184!-
1185  IF (INDEX(indchfun,topp(:LEN_TRIM(topp))) > 0) THEN
1186    scal = missing_val
1187    var_sz = SIZE(var,1)
1188!---
1189    DO jj = 1,jjm
1190      ist = (jj-1)*req_sz+1
1191      CALL mathop (topp,req_sz,buff_tmp2(ist:ist+req_sz-1), &
1192 &      missing_val,nbindex,ijndex,scal,var_sz,buff_tmp)
1193!-----
1194      var(:,jj) = buff_tmp(:) 
1195    ENDDO
1196  ELSE
1197    CALL ipslerr (3,'resget_opp_r2d', &
1198      'The operation you wish to do on the variable for the ',&
1199      'restart file is not allowed.',topp)
1200  ENDIF
1201!-----------------------------
1202END SUBROUTINE restget_opp_r2d
1203!-
1204!===
1205!-
1206SUBROUTINE restget_r1d &
1207  (fid,vname_q,iim,jjm,llm,itau,def_beha,var)
1208!---------------------------------------------------------------------
1209!- This subroutine serves as an interface to restget_real
1210!---------------------------------------------------------------------
1211  IMPLICIT NONE
1212!-
1213  INTEGER :: fid
1214  CHARACTER(LEN=*) :: vname_q
1215  INTEGER :: iim,jjm,llm,itau
1216  LOGICAL :: def_beha
1217  REAL :: var(:)
1218!-
1219!- LOCAL
1220!-
1221  INTEGER :: ji,jl,req_sz,var_sz
1222  REAL,ALLOCATABLE,SAVE :: buff_tmp(:)
1223  CHARACTER(LEN=70) :: str,str2
1224  LOGICAL :: check = .FALSE.
1225!---------------------------------------------------------------------
1226!-
1227! 1.0 Allocate the temporary buffer we need
1228!     to put the variable in right dimension
1229!-
1230  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1231    IF (check) WRITE(*,*) "restget_r1d : allocate buff_tmp = ",SIZE(var)
1232    ALLOCATE(buff_tmp(SIZE(var)))
1233  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
1234    IF (check) THEN
1235      WRITE(*,*) "restget_r1d : re-allocate buff_tmp= ",SIZE(var)
1236    ENDIF
1237    DEALLOCATE(buff_tmp)
1238    ALLOCATE(buff_tmp(SIZE(var)))
1239  ENDIF
1240!-
1241! 2.0 Here we could check if the sizes specified agree
1242!     with the size of the variable provided
1243!-
1244  req_sz = 1
1245  IF (iim > 0) req_sz = req_sz*iim
1246  IF (jjm > 0) req_sz = req_sz*jjm
1247  IF (llm > 0) req_sz = req_sz*llm
1248  var_sz = SIZE(var,1)
1249  IF (req_sz > var_sz) THEN
1250    WRITE(str, &
1251 &    '("Size of variable requested from file should be ",I6)') req_sz
1252    WRITE(str2, &
1253 &    '("but the provided variable can only hold ",I6)') var_sz
1254    CALL ipslerr (3,'restget_r1d',str,str2,' ')
1255  ENDIF
1256  IF (req_sz < var_sz) THEN
1257    WRITE(str, &
1258 &    '("the size of variable requested from file is ",I6)') req_sz
1259    WRITE(str2, &
1260 &    '("but the provided variable can hold ",I6)') var_sz
1261    CALL ipslerr (2,'restget_r1d', &
1262      'There could be a problem here :',str,str2)
1263  ENDIF
1264!-
1265  CALL restget_real &
1266    (fid,vname_q,iim,jjm,llm,itau,def_beha,buff_tmp)
1267!-
1268! 4.0 Transfer the buffer obtained from the restart file
1269!     into the variable the model expects
1270!-
1271  jl=0
1272  DO ji=1,SIZE(var,1)
1273    jl=jl+1
1274    var(ji) = buff_tmp(jl)
1275  ENDDO
1276!-------------------------
1277END SUBROUTINE restget_r1d
1278!-
1279!===
1280!-
1281SUBROUTINE restget_r2d &
1282  (fid,vname_q,iim,jjm,llm,itau,def_beha,var)
1283!---------------------------------------------------------------------
1284!- This subroutine serves as an interface to restget_real
1285!---------------------------------------------------------------------
1286  IMPLICIT NONE
1287!-
1288  INTEGER :: fid
1289  CHARACTER(LEN=*) :: vname_q
1290  INTEGER :: iim,jjm,llm,itau
1291  LOGICAL :: def_beha
1292  REAL :: var(:,:)
1293!-
1294!- LOCAL
1295!-
1296  INTEGER :: ji,jj,jl,req_sz,var_sz
1297  REAL,ALLOCATABLE,SAVE :: buff_tmp(:)
1298  CHARACTER(LEN=70) :: str,str2
1299  LOGICAL :: check = .FALSE.
1300!---------------------------------------------------------------------
1301!-
1302!  1.0 Allocate the temporary buffer we need
1303!      to put the variable in right dimension
1304!-
1305  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1306    IF (check) THEN
1307      WRITE(*,*) "restget_r2d : allocate buff_tmp = ",SIZE(var)
1308    ENDIF
1309    ALLOCATE(buff_tmp(SIZE(var)))
1310  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
1311    IF (check) THEN
1312      WRITE(*,*) "restget_r2d : re-allocate buff_tmp= ",SIZE(var)
1313    ENDIF
1314    DEALLOCATE(buff_tmp)
1315    ALLOCATE(buff_tmp(SIZE(var)))
1316  ENDIF
1317!-
1318! 2.0 Here we check if the sizes specified agree
1319!-    with the size of the variable provided
1320!-
1321  req_sz = 1
1322  IF (iim > 0) req_sz = req_sz*iim
1323  IF (jjm > 0) req_sz = req_sz*jjm
1324  IF (llm > 0) req_sz = req_sz*llm
1325  var_sz = SIZE(var,2)*SIZE(var,1)
1326  IF (req_sz > var_sz) THEN
1327    WRITE(*,*) "RESGET_r2d :",vname_q
1328    WRITE(str, &
1329 &    '("Size of variable requested from file should be ",I6)') req_sz
1330    WRITE(str2, &
1331 &    '("but the provided variable can only hold ",I6)')  var_sz
1332    CALL ipslerr (3,'restget_r2d',str,str2,' ')
1333  ENDIF
1334  IF (req_sz < var_sz) THEN
1335    WRITE(str, &
1336 &    '("the size of variable requested from file is ",I6)') req_sz
1337    WRITE(str2,'("but the provided variable can hold ",I6)')  var_sz
1338    CALL ipslerr (2,'restget_r2d', &
1339      'There could be a problem here :',str,str2)
1340  ENDIF
1341!-
1342  CALL restget_real &
1343    (fid,vname_q,iim,jjm,llm,itau,def_beha,buff_tmp)
1344!-
1345! 4.0 Transfer the buffer obtained from the restart file
1346!     into the variable the model expects
1347!-
1348  jl=0
1349  DO jj=1,SIZE(var,2)
1350    DO ji=1,SIZE(var,1)
1351      jl=jl+1
1352      var(ji,jj) = buff_tmp(jl)
1353    ENDDO
1354  ENDDO
1355!-------------------------
1356END SUBROUTINE restget_r2d
1357!-
1358!===
1359!-
1360SUBROUTINE restget_r3d &
1361  (fid,vname_q,iim,jjm,llm,itau,def_beha,var)
1362!---------------------------------------------------------------------
1363!- This subroutine serves as an interface to restget_real
1364!---------------------------------------------------------------------
1365  IMPLICIT NONE
1366!-
1367  INTEGER :: fid
1368  CHARACTER(LEN=*) :: vname_q
1369  INTEGER :: iim,jjm,llm,itau
1370  LOGICAL def_beha
1371  REAL :: var(:,:,:)
1372!-
1373! LOCAL
1374!-
1375  INTEGER :: ji,jj,jk,jl,req_sz,var_sz
1376  REAL,ALLOCATABLE,SAVE :: buff_tmp(:)
1377  CHARACTER(LEN=70) :: str,str2
1378  LOGICAL :: check = .FALSE.
1379!---------------------------------------------------------------------
1380!-
1381! 1.0 Allocate the temporary buffer we need
1382!      to put the variable in right dimension
1383!-
1384  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1385    IF (check) WRITE(*,*) "restget_r3d : allocate buff_tmp = ",SIZE(var)
1386    ALLOCATE(buff_tmp(SIZE(var)))
1387  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
1388    IF (check) THEN
1389      WRITE(*,*) "restget_r3d : re-allocate buff_tmp= ",SIZE(var)
1390    ENDIF
1391    DEALLOCATE(buff_tmp)
1392    ALLOCATE(buff_tmp(SIZE(var)))
1393  ENDIF
1394!-
1395! 2.0 Here we check if the sizes specified agree
1396!-    with the size of the variable provided
1397!-
1398  req_sz = 1
1399  IF (iim > 0) req_sz = req_sz*iim
1400  IF (jjm > 0) req_sz = req_sz*jjm
1401  IF (llm > 0) req_sz = req_sz*llm
1402  var_sz = SIZE(var,3)*SIZE(var,2)*SIZE(var,1)
1403  IF (req_sz > var_sz) THEN
1404    WRITE(str, &
1405 &    '("Size of variable requested from file should be ",I6)') req_sz
1406    WRITE(str2, &
1407 &    '("but the provided variable can only hold ",I6)')  var_sz
1408    CALL ipslerr (3,'restget_r3d',str,str2,' ')
1409  ENDIF
1410  IF (req_sz < var_sz) THEN
1411    WRITE(str, &
1412 &    '("the size of variable requested from file is ",I6)') req_sz
1413    WRITE(str2,'("but the provided variable can hold ",I6)')  var_sz
1414    CALL ipslerr (2,'restget_r3d', &
1415      'There could be a problem here :',str,str2)
1416  ENDIF
1417!-
1418  CALL restget_real &
1419    (fid,vname_q,iim,jjm,llm,itau,def_beha,buff_tmp)
1420!-
1421! 4.0 Transfer the buffer obtained from the restart file
1422!     into the variable the model expects
1423!-
1424  jl=0
1425  DO jk=1,SIZE(var,3)
1426    DO jj=1,SIZE(var,2)
1427      DO ji=1,SIZE(var,1)
1428        jl=jl+1
1429        var(ji,jj,jk) = buff_tmp(jl)
1430      ENDDO
1431    ENDDO
1432  ENDDO
1433!-------------------------
1434END SUBROUTINE restget_r3d
1435!-
1436!===
1437!-
1438SUBROUTINE restget_real &
1439  (fid,vname_q,iim,jjm,llm,itau,def_beha,var)
1440!---------------------------------------------------------------------
1441!- This subroutine is for getting a variable from the restart file.
1442!- A number of verifications will be made :
1443!- - Is this the first time we read this variable ?
1444!- - Are the dimensions correct ?
1445!- - Is the correct time step present in the file
1446!- - is a default behaviour possible. If not the model is stoped.
1447!- Default procedure is to write the content of val_exp on all values.
1448!-
1449!- INPUT
1450!-
1451!- fid            : Identification of the file
1452!- vname_q        : Name of the variable to be read
1453!- iim, jjm ,llm  : Dimensions of the variable that should be read
1454!- itau           : Time step at whcih we are when we want
1455!-                  to read the variable
1456!- def_beha       : If the model can restart without this variable
1457!-                  then some strange value is given.
1458!-
1459!- OUTPUT
1460!-
1461!- var            : Variable in which the data is put
1462!---------------------------------------------------------------------
1463  IMPLICIT NONE
1464!-
1465  INTEGER :: fid
1466  CHARACTER(LEN=*) :: vname_q
1467  INTEGER :: iim,jjm,llm,itau
1468  LOGICAL :: def_beha
1469  REAL :: var(:)
1470!-
1471! LOCAL
1472!-
1473  INTEGER :: vid,vnb,ncfid
1474  INTEGER :: iret,index,it,ndim,ia
1475  CHARACTER(LEN=70) str,str2
1476  CHARACTER(LEN=80) attname
1477  INTEGER,DIMENSION(4) :: corner,edge
1478!---------------------------------------------------------------------
1479!-
1480  ncfid = netcdf_id(fid,1)
1481!-
1482  CALL find_str (varname_in(fid,1:nbvar_in(fid)),vname_q,vnb)
1483!-
1484! 1.0 If the variable is not present then ERROR or filled up
1485!     by default values if allowed
1486!-
1487  IF (vnb < 0) THEN
1488    IF (def_beha) THEN
1489!-----
1490      lock_valexp = .TRUE.
1491      var(:) = val_exp
1492!----
1493      str = 'Variable '//TRIM(vname_q) &
1494          //' is not present in the restart file'
1495      CALL ipslerr (1,'restget', &
1496 &      str,'but default values are used to fill in',' ')
1497!----
1498      IF (nbvar_in(fid) >= max_var) THEN
1499        CALL ipslerr (3,'restget', &
1500         'Too many variables for the restcom module', &
1501         'Please increase the value of max_var',' ')
1502      ENDIF
1503      nbvar_in(fid) = nbvar_in(fid)+1
1504      vnb = nbvar_in(fid)
1505      varname_in(fid,vnb) = vname_q
1506      touched_in(fid,vnb) = .TRUE.
1507!-----
1508      CALL restdefv (fid,vname_q,iim,jjm,llm,.TRUE.) 
1509!-----
1510    ELSE
1511      str = 'Variable '//TRIM(vname_q) &
1512          //' is not present in the restart file'
1513      CALL ipslerr (3,'restget', &
1514 &      str,'but it is need to restart the model',' ')
1515    ENDIF
1516!---
1517  ELSE
1518!---
1519!--  2.0 Check if the variable has not yet been read
1520!--      and that the time is OK
1521!---
1522    vid = varid_in(fid,vnb)
1523!---
1524    nbvar_read(fid) = nbvar_read(fid)+1
1525!---
1526    IF (touched_in(fid,vnb)) THEN
1527      str = 'Variable '//TRIM(vname_q) &
1528          //' has already been read from file'
1529      CALL ipslerr (3,'restget',str,' ',' ')
1530    ENDIF
1531!---
1532!-- 3.0 get the time step of the restart file
1533!--     and check if it is correct
1534!---
1535    index = -1
1536    DO it=1,tax_size_in(fid)
1537          IF (t_index(fid,it) == itau) index = it
1538    ENDDO
1539!---
1540    IF (index < 0) THEN
1541      str = 'The time step requested for variable '//TRIM(vname_q)
1542      CALL ipslerr (3,'restget', &
1543 &      str,'is not available in the current file',' ')
1544    ENDIF
1545!---     
1546!-- 4.0 Read the data. Note that the variables in the restart files
1547!--     have no time axis is and thus we write -1
1548!---
1549    str='Incorrect dimension for '//TRIM(vname_q)
1550    ndim = 0
1551    IF (iim > 0) THEN
1552      ndim = ndim+1
1553      IF (vardims_in(fid,vnb,ndim) == iim) THEN
1554        corner(ndim) = 1
1555        edge(ndim) = iim
1556      ELSE
1557        WRITE (str2,'("Incompatibility for iim : ",I6,I6)') &
1558             iim,vardims_in(fid,vnb,ndim) 
1559        CALL ipslerr (3,'restget',str,str2,' ')
1560      ENDIF
1561    ENDIF
1562!---
1563    IF (jjm > 0) THEN
1564      ndim = ndim+1
1565      IF (vardims_in(fid,vnb,ndim) == jjm) THEN
1566        corner(ndim) = 1
1567        edge(ndim) = jjm
1568      ELSE
1569        WRITE (str2,'("Incompatibility for jjm : ",I6,I6)') &
1570             jjm,vardims_in(fid,vnb,ndim) 
1571        CALL ipslerr (3,'restget',str,str2,' ')
1572      ENDIF
1573    ENDIF
1574!---
1575    IF (llm > 0) THEN
1576      ndim = ndim+1
1577      IF (vardims_in(fid,vnb,ndim) == llm) THEN
1578        corner(ndim) = 1
1579        edge(ndim) = llm
1580      ELSE
1581        WRITE (str2,'("Incompatibility for llm : ",I6,I6)') &
1582             llm,vardims_in(fid,vnb,ndim) 
1583        CALL ipslerr (3,'restget',str,str2,' ')
1584      ENDIF
1585    ENDIF
1586!---
1587!-- Time
1588!---
1589    ndim = ndim+1
1590    corner(ndim) = index
1591!!????? edge(ndim) = index
1592    edge(ndim) = 1
1593!---
1594    iret = NF90_GET_VAR(ncfid,vid,var, &
1595 &                      start=corner(1:ndim),count=edge(1:ndim))
1596!---
1597!-- 5.0 The variable we have just read is created
1598!--      in the next restart file
1599!---
1600    IF (     (netcdf_id(fid,1) /= netcdf_id(fid,2))  &
1601 &      .AND.(netcdf_id(fid,2) > 0) ) THEN
1602!-----
1603      CALL restdefv (fid,vname_q,iim,jjm,llm,.FALSE.)
1604!-----
1605      DO ia = 1,varatt_in(fid,vnb)
1606        iret = NF90_INQ_ATTNAME(ncfid,vid,ia,attname)
1607        iret = NF90_COPY_ATT(ncfid,vid,attname, &
1608 &               netcdf_id(fid,2),varid_out(fid,nbvar_out(fid)))
1609      ENDDO
1610!-----
1611      IF (itau_out(fid) >= 0) THEN
1612        iret = NF90_ENDDEF(netcdf_id(fid,2))
1613      ENDIF
1614    ENDIF
1615!---
1616  ENDIF
1617!--------------------------
1618END SUBROUTINE restget_real
1619!-
1620!===
1621!-
1622SUBROUTINE restput_opp_r1d &
1623  (fid,vname_q,iim,jjm,llm,itau,var,OPERATOR,nbindex,ijndex)
1624!---------------------------------------------------------------------
1625!- This subroutine is the interface to restput_real which allows
1626!- to re-index data onto the original grid of the restart file.
1627!- The logic we use is still fuzzy in my mind but that is probably
1628!- only because I have not yet though through everything.
1629!-
1630!- In the case iim = nbindex it means that the user attempts
1631!- to project a vector back onto the original 2D or 3D field.
1632!- This requires that jjm and llm be equal to 1 or 0,
1633!- else I would not know what it means.
1634!---------------------------------------------------------------------
1635  IMPLICIT NONE
1636!-
1637  INTEGER :: fid
1638  CHARACTER(LEN=*) :: vname_q
1639  INTEGER :: iim,jjm,llm,itau
1640  REAL :: var(:)
1641  CHARACTER(LEN=*) :: OPERATOR
1642  INTEGER :: nbindex,ijndex(nbindex)
1643!-
1644! LOCAL
1645!-
1646  INTEGER :: req_sz
1647  REAL,ALLOCATABLE,SAVE :: buff_tmp(:),buff_tmp2(:)
1648  REAL :: scal
1649  CHARACTER(LEN=7) :: topp
1650  LOGICAL :: check = .FALSE.
1651!---------------------------------------------------------------------
1652!-
1653! 0.0 What size should be the data in the file
1654!-
1655  req_sz = 1
1656  IF ( nbindex == iim .AND. jjm <= 1 .AND. llm <= 1) THEN
1657    IF (xax_infs(fid,1,1) > 0) req_sz = req_sz*xax_infs(fid,1,1)
1658    IF (yax_infs(fid,1,1) > 0) req_sz = req_sz*yax_infs(fid,1,1)
1659    IF (zax_infs(fid,1,1) > 0) req_sz = req_sz*zax_infs(fid,1,1)
1660  ELSE
1661    CALL ipslerr (3,'restput_opp_r1d', &
1662      'Unable to performe an operation on this variable as it has', &
1663      'a second and third dimension',vname_q)
1664  ENDIF
1665!-
1666! 1.0 Allocate the temporary buffer we need
1667!     to put the variable in right dimension
1668!-
1669  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1670    IF (check) THEN
1671      WRITE(*,*) "restput_opp_r1d : allocate buff_tmp = ",SIZE(var)
1672    ENDIF
1673    ALLOCATE(buff_tmp(SIZE(var)))
1674  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
1675    IF (check) THEN
1676      WRITE(*,*) "restput_opp_r1d : re-allocate buff_tmp= ",SIZE(var)
1677    ENDIF
1678    DEALLOCATE(buff_tmp)
1679    ALLOCATE(buff_tmp(SIZE(var)))
1680  ENDIF
1681!-
1682  IF (.NOT.ALLOCATED(buff_tmp2)) THEN
1683    IF (check) THEN
1684      WRITE(*,*) "restput_opp_r1d : allocate buff_tmp2 = ",req_sz
1685    ENDIF
1686    ALLOCATE(buff_tmp2(req_sz))
1687  ELSE IF (req_sz > SIZE(buff_tmp2)) THEN
1688    IF (check) THEN
1689      WRITE(*,*) "restput_opp_r1d : re-allocate buff_tmp2= ",req_sz
1690    ENDIF
1691    DEALLOCATE(buff_tmp2)
1692    ALLOCATE(buff_tmp2(req_sz))
1693  ENDIF
1694!-
1695! 2.0 We do the operation needed.
1696!     It can only be a re-indexing operation.
1697!     You would not want to change the values in a restart file or ?
1698!-
1699  topp = OPERATOR(1:MIN(LEN_TRIM(OPERATOR),7))
1700!-
1701  IF (INDEX(indchfun,topp(:LEN_TRIM(topp))) > 0) THEN
1702    scal = missing_val
1703!---
1704    buff_tmp(:) = var(:)
1705!---
1706    CALL mathop &
1707      (topp,SIZE(var),buff_tmp,missing_val,nbindex,ijndex, &
1708       scal,req_sz,buff_tmp2)
1709  ELSE
1710    CALL ipslerr (3,'restput_opp_r1d', &
1711      'The operation you wish to do on the variable for the ', &
1712       & 'restart file is not allowed.',topp)
1713  ENDIF
1714!-
1715  CALL restput_real &
1716    (fid,vname_q,xax_infs(fid,1,1),yax_infs(fid,1,1), &
1717     zax_infs(fid,1,1),itau,buff_tmp2)
1718!-----------------------------
1719END SUBROUTINE restput_opp_r1d
1720!-
1721!===
1722!-
1723SUBROUTINE restput_opp_r2d &
1724  (fid,vname_q,iim,jjm,llm,itau,var,OPERATOR,nbindex,ijndex)
1725!---------------------------------------------------------------------
1726!- This subroutine is the interface to restput_real which allows
1727!- to re-index data onto the original grid of the restart file.
1728!- The logic we use is still fuzzy in my mind but that is probably
1729!- only because I have not yet though through everything.
1730!-
1731!- In the case iim = nbindex it means that the user attempts
1732!- to project the first dimension of the matrix back onto a 3D field
1733!- where jjm will be the third dimension.
1734!- Here we do not allow for 4D data, thus we will take the first
1735!- two dimensions in the file and require that llm = 1.
1736!- These are pretty heavy constraints but I do not know how
1737!- to make it more general. I need to think about it some more.
1738!---------------------------------------------------------------------
1739  IMPLICIT NONE
1740!-
1741  INTEGER :: fid
1742  CHARACTER(LEN=*) :: vname_q
1743  INTEGER :: iim,jjm,llm,itau
1744  REAL :: var(:,:)
1745  CHARACTER(LEN=*) :: OPERATOR
1746  INTEGER :: nbindex,ijndex(nbindex)
1747!-
1748! LOCAL
1749!-
1750  INTEGER :: jj,req_sz,var_sz,ist
1751  REAL,ALLOCATABLE,SAVE :: buff_tmp(:),buff_tmp2(:)
1752  REAL :: scal
1753  CHARACTER(LEN=7) :: topp
1754  LOGICAL :: check = .FALSE.
1755!---------------------------------------------------------------------
1756!-
1757! 0.0 What size should be the data in the file
1758!-
1759  req_sz = 1
1760  IF ( nbindex == iim .AND. llm <= 1) THEN
1761    IF (xax_infs(fid,1,1) > 0) req_sz = req_sz*xax_infs(fid,1,1)
1762    IF (yax_infs(fid,1,1) > 0) req_sz = req_sz*yax_infs(fid,1,1)
1763  ELSE
1764    CALL ipslerr (3,'restput_opp_r2d', &
1765      'Unable to performe an operation on this variable as it has', &
1766      'a second and third dimension',vname_q)
1767  ENDIF
1768!-
1769  IF (jjm < 1) THEN
1770    CALL ipslerr (3,'restput_opp_r2d', &
1771      'Please specify a second dimension which is the', &
1772      'layer on which the operations are performed',vname_q)
1773  ENDIF
1774!-
1775! 1.0 Allocate the temporary buffer we need
1776!     to put the variable in right dimension
1777!-
1778  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1779    IF (check) THEN
1780      WRITE(*,*) "restput_opp_r2d : allocate buff_tmp = ",SIZE(var,1)
1781    ENDIF
1782    ALLOCATE(buff_tmp(SIZE(var,1)))
1783  ELSE IF (SIZE(var,1) > SIZE(buff_tmp)) THEN
1784    IF (check) THEN
1785      WRITE(*,*) "restput_opp_r2d : re-allocate buff_tmp= ",SIZE(var,1)
1786    ENDIF
1787    DEALLOCATE(buff_tmp)
1788    ALLOCATE(buff_tmp(SIZE(var,1)))
1789  ENDIF
1790!-
1791  IF (.NOT.ALLOCATED(buff_tmp2)) THEN
1792    IF (check) THEN
1793      WRITE(*,*) "restput_opp_r2d : allocate buff_tmp2 = ",req_sz*jjm
1794    ENDIF
1795    ALLOCATE(buff_tmp2(req_sz*jjm))
1796  ELSE IF (req_sz*jjm > SIZE(buff_tmp2)) THEN
1797    IF (check) THEN
1798      WRITE(*,*) "restput_opp_r2d : re-allocate buff_tmp2= ",req_sz*jjm
1799    ENDIF
1800    DEALLOCATE(buff_tmp2)
1801    ALLOCATE(buff_tmp2(req_sz*jjm))
1802  ENDIF
1803!-
1804! 2.0 We do the operation needed.
1805!     It can only be a re-indexing operation.
1806!     You would not want to change the values in a restart file or ?
1807!-
1808  topp = OPERATOR(1:MIN(LEN_TRIM(OPERATOR),7))
1809!-
1810  IF (INDEX(indchfun,topp(:LEN_TRIM(topp))) > 0) THEN
1811    scal = missing_val
1812    var_sz = SIZE(var,1)
1813!---
1814    DO jj = 1,jjm
1815      buff_tmp(:) = var(:,jj)
1816!-----
1817      ist = (jj-1)*req_sz+1
1818      CALL mathop &
1819        (topp,var_sz,buff_tmp,missing_val,nbindex,ijndex, &
1820         scal,req_sz,buff_tmp2(ist:ist+req_sz-1))
1821    ENDDO
1822  ELSE
1823    CALL ipslerr (3,'restput_opp_r2d', &
1824      'The operation you wish to do on the variable for the ', &
1825      'restart file is not allowed.',topp)
1826  ENDIF
1827!-
1828  CALL restput_real &
1829    (fid,vname_q,xax_infs(fid,1,1),yax_infs(fid,1,1), &
1830     jjm,itau,buff_tmp2)
1831!-----------------------------
1832END SUBROUTINE restput_opp_r2d
1833!-
1834!===
1835!-
1836SUBROUTINE restput_r1d (fid,vname_q,iim,jjm,llm,itau,var)
1837!---------------------------------------------------------------------
1838!- This subroutine serves as an interface to restput_real
1839!---------------------------------------------------------------------
1840  IMPLICIT NONE
1841!-
1842  INTEGER :: fid
1843  CHARACTER(LEN=*) :: vname_q
1844  INTEGER :: iim,jjm,llm,itau
1845  REAL :: var(:)
1846!-
1847! LOCAL
1848!-
1849  INTEGER :: ji,jl,req_sz,var_sz
1850  REAL,ALLOCATABLE,SAVE :: buff_tmp(:)
1851  CHARACTER(LEN=70) :: str,str2
1852  LOGICAL :: check = .FALSE.
1853!---------------------------------------------------------------------
1854!-
1855! 1.0 Allocate the temporary buffer we need
1856!      to put the variable in right dimension
1857!-
1858  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1859    IF (check) THEN
1860      WRITE(*,*) "restput_r1d : allocate buff_tmp = ",SIZE(var)
1861    ENDIF
1862    ALLOCATE(buff_tmp(SIZE(var)))
1863  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
1864    IF (check) THEN
1865      WRITE(*,*) "restput_r1d : re-allocate buff_tmp= ",SIZE(var)
1866    ENDIF
1867    DEALLOCATE(buff_tmp)
1868    ALLOCATE(buff_tmp(SIZE(var)))
1869  ENDIF
1870!-
1871! 2.0 Here we could check if the sizes specified agree
1872!     with the size of the variable provided
1873!-
1874  req_sz = 1
1875  IF (iim > 0) req_sz = req_sz*iim
1876  IF (jjm > 0) req_sz = req_sz*jjm
1877  IF (llm > 0) req_sz = req_sz*llm
1878  var_sz = SIZE(var,1)
1879  IF (req_sz > var_sz) THEN
1880    WRITE(str, &
1881 &    '("Size of variable put to the file should be ",I6)') req_sz
1882    WRITE(str2, &
1883 &    '("but the provided variable is of size  ",I6)')  var_sz
1884    CALL ipslerr (3,'restput_r1d',str,str2,' ')
1885  ENDIF
1886  IF (req_sz < var_sz) THEN
1887    WRITE(str,'("the size of variable put to the file is ",I6)') req_sz
1888    WRITE(str2,'("but the provided variable is larger ",I6)')  var_sz
1889    CALL ipslerr (2,'restput_r1d', &
1890      'There could be a problem here :',str,str2)
1891  ENDIF
1892!-
1893! 4.0 Transfer the buffer obtained from the restart file
1894!     into the variable the model expects
1895!-
1896  jl=0
1897  DO ji=1,SIZE(var,1)
1898    jl=jl+1
1899    buff_tmp(jl) = var(ji)
1900  ENDDO
1901!-
1902  CALL restput_real (fid,vname_q,iim,jjm,llm,itau,buff_tmp)
1903!-------------------------
1904END SUBROUTINE restput_r1d
1905!-
1906!===
1907!-
1908SUBROUTINE restput_r2d (fid,vname_q,iim,jjm,llm,itau,var)
1909!---------------------------------------------------------------------
1910!- This subroutine serves as an interface to restput_real
1911!---------------------------------------------------------------------
1912  IMPLICIT NONE
1913!-
1914  INTEGER :: fid
1915  CHARACTER(LEN=*) :: vname_q
1916  INTEGER :: iim,jjm,llm,itau
1917  REAL :: var(:,:)
1918!-
1919! LOCAL
1920!-
1921  INTEGER :: ji,jj,jl,req_sz,var_sz
1922  REAL,ALLOCATABLE,SAVE :: buff_tmp(:)
1923  CHARACTER(LEN=70) :: str,str2
1924  LOGICAL :: check = .FALSE.
1925!---------------------------------------------------------------------
1926!-
1927! 1.0 Allocate the temporary buffer we need
1928!     to put the variable in right dimension
1929!-
1930  IF (.NOT.ALLOCATED(buff_tmp)) THEN
1931    IF (check) WRITE(*,*) "restput_r2d : allocate buff_tmp = ",SIZE(var)
1932    ALLOCATE(buff_tmp(SIZE(var)))
1933  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
1934    IF (check) THEN
1935      WRITE(*,*) "restput_r2d : re-allocate buff_tmp= ",SIZE(var)
1936    ENDIF
1937    DEALLOCATE(buff_tmp)
1938    ALLOCATE(buff_tmp(SIZE(var)))
1939  ENDIF
1940!-
1941! 2.0 Here we could check if the sizes specified agree
1942!     with the size of the variable provided
1943!-
1944  req_sz = 1
1945  IF (iim > 0) req_sz = req_sz*iim
1946  IF (jjm > 0) req_sz = req_sz*jjm
1947  IF (llm > 0) req_sz = req_sz*llm
1948  var_sz = SIZE(var,2)*SIZE(var,1)
1949  IF (req_sz > var_sz) THEN
1950    WRITE(str, &
1951&         '("Size of variable put to the file should be ",I6)') req_sz
1952    WRITE(str2,'("but the provided variable is of size  ",I6)') var_sz
1953    CALL ipslerr (3,'restput_r2d',str,str2,' ')
1954  ENDIF
1955  IF (req_sz < var_sz) THEN
1956    WRITE(str,'("the size of variable put to the file is ",I6)') req_sz
1957    WRITE(str2,'("but the provided variable is larger ",I6)')  var_sz
1958    CALL ipslerr (2,'restput_r2d', &
1959      'There could be a problem here :',str,str2)
1960  ENDIF
1961!-
1962! 4.0 Transfer the buffer obtained from the restart file
1963!     into the variable the model expects
1964!-
1965  jl=0
1966  DO jj=1,SIZE(var,2)
1967    DO ji=1,SIZE(var,1)
1968      jl=jl+1
1969      buff_tmp(jl) = var(ji,jj)
1970    ENDDO
1971  ENDDO
1972!-
1973  CALL restput_real(fid,vname_q,iim,jjm,llm,itau,buff_tmp)
1974!-------------------------
1975END SUBROUTINE restput_r2d
1976!-
1977!===
1978!-
1979SUBROUTINE restput_r3d (fid,vname_q,iim,jjm,llm,itau,var)
1980!---------------------------------------------------------------------
1981!- This subroutine serves as an interface to restput_real
1982!---------------------------------------------------------------------
1983  IMPLICIT NONE
1984!-
1985  INTEGER :: fid
1986  CHARACTER(LEN=*) :: vname_q
1987  INTEGER :: iim,jjm,llm,itau
1988  REAL :: var(:,:,:)
1989!-
1990! LOCAL
1991!-
1992  INTEGER :: ji,jj,jk,jl,req_sz,var_sz
1993  REAL,ALLOCATABLE,SAVE :: buff_tmp(:)
1994  CHARACTER(LEN=70) :: str,str2
1995  LOGICAL :: check = .FALSE.
1996!---------------------------------------------------------------------
1997!-
1998! 1.0 Allocate the temporary buffer we need
1999!     to put the variable in right dimension
2000!-
2001  IF (.NOT.ALLOCATED(buff_tmp)) THEN
2002    IF (check) THEN
2003      WRITE(*,*) "restput_r3d : allocate buff_tmp = ",SIZE(var)
2004    ENDIF
2005    ALLOCATE(buff_tmp(SIZE(var)))
2006  ELSE IF (SIZE(var) > SIZE(buff_tmp)) THEN
2007    IF (check) THEN
2008      WRITE(*,*) "restput_r3d : re-allocate buff_tmp= ",SIZE(var)
2009    ENDIF
2010    DEALLOCATE(buff_tmp)
2011    ALLOCATE(buff_tmp(SIZE(var)))
2012  ENDIF
2013!-
2014! 2.0 Here we could check if the sizes specified agree
2015!     with the size of the variable provided
2016!-
2017  req_sz = 1
2018  IF (iim > 0) req_sz = req_sz*iim
2019  IF (jjm > 0) req_sz = req_sz*jjm
2020  IF (llm > 0) req_sz = req_sz*llm
2021  var_sz = SIZE(var,3)*SIZE(var,2)*SIZE(var,1)
2022  IF (req_sz > var_sz) THEN
2023    WRITE(str, &
2024 &    '("Size of variable put to the file should be ",I6)') req_sz
2025    WRITE(str2, &
2026 &    '("but the provided variable is of size  ",I6)')  var_sz
2027    CALL ipslerr (3,'restput_r3d',str,str2,' ')
2028  ENDIF
2029  IF (req_sz < var_sz) THEN
2030    WRITE(str,'("the size of variable put to the file is ",I6)') req_sz
2031    WRITE(str2,'("but the provided variable is larger ",I6)')  var_sz
2032    CALL ipslerr (2,'restput_r3d', &
2033      'There could be a problem here :',str,str2)
2034  ENDIF
2035!-
2036! 4.0 Transfer the buffer obtained from the restart file
2037!     into the variable the model expects
2038!-
2039  jl=0
2040  DO jk=1,SIZE(var,3)
2041    DO jj=1,SIZE(var,2)
2042      DO ji=1,SIZE(var,1)
2043        jl=jl+1
2044        buff_tmp(jl) = var(ji,jj,jk)
2045      ENDDO
2046    ENDDO
2047  ENDDO
2048!-
2049  CALL restput_real(fid,vname_q,iim,jjm,llm,itau,buff_tmp)
2050!-------------------------
2051END SUBROUTINE restput_r3d
2052!-
2053!===
2054!-
2055SUBROUTINE restput_real (fid,vname_q,iim,jjm,llm,itau,var)
2056!---------------------------------------------------------------------
2057!- This subroutine will put a variable into the restart file.
2058!- But it will do a lot of other things if needed :
2059!- - Open a file if non is opened for this time-step
2060!-   and all variables were written.
2061!- - Add an axis if needed
2062!- - verify that the variable has the right time step for this file
2063!- - If it is time for a new file then it is opened
2064!-   and the old one closed
2065!- This requires that variables read from the last restart file were all
2066!- written
2067!-
2068!- INPUT
2069!-
2070!- fid         : Id of the file in which we will write the variable
2071!- vname_q     : Name of the variable to be written
2072!- iim,jjm,llm : Size in 3D of the variable
2073!- itau        : Time step at which the variable is written
2074!- var         : Variable
2075!-
2076!- OUTPUT
2077!-
2078!- NONE
2079!---------------------------------------------------------------------
2080  IMPLICIT NONE
2081!-
2082  CHARACTER(LEN=*) :: vname_q
2083  INTEGER :: fid,iim,jjm,llm,itau
2084  REAL :: var(:)
2085!-
2086! LOCAL
2087!-
2088  INTEGER :: iret,vid,ncid,iv,vnb
2089  INTEGER :: ierr
2090  REAL :: secsince,un_jour,un_an
2091  INTEGER :: ndims
2092  INTEGER,DIMENSION(4) :: corner,edge
2093!-
2094  LOGICAL :: check = .FALSE.
2095!---------------------------------------------------------------------
2096!-
2097! 0.0 Get some variables
2098!-
2099  ncid = netcdf_id(fid,2)
2100  IF (netcdf_id(fid,2) < 0) THEN
2101    CALL ipslerr (3,'restput', &
2102 &    'The output restart file is undefined.',' ',' ')
2103  ENDIF
2104  CALL ioget_calendar (un_an,un_jour)
2105!-
2106! 1.0 Check if the variable is already present
2107!-
2108  IF (check) WRITE(*,*) 'RESTPUT 1.0 : ',TRIM(vname_q)
2109!-
2110  CALL find_str (varname_out(fid,1:nbvar_out(fid)),vname_q,vnb)
2111!-
2112  IF (check) THEN
2113    WRITE(*,*) 'RESTPUT 1.1 : ',varname_out(fid,1:nbvar_out(fid)),vnb
2114  ENDIF
2115!-
2116! 2.0 If variable is not present then declare it
2117!     and add extra dimensions if needed.
2118!-
2119  IF (vnb <= 0) THEN
2120    CALL restdefv (fid,vname_q,iim,jjm,llm,.TRUE.)
2121    vnb = nbvar_out(fid)
2122  ENDIF
2123  vid = varid_out(fid,vnb)
2124!-
2125  IF (check) WRITE(*,*) 'RESTPUT 2.0 : ',vnb,vid
2126!-
2127! 2.1 Is this file already in write mode ?
2128!     If itau_out is still negative then we have
2129!     never written to it and we need to go into write mode.
2130!-
2131  IF (itau_out(fid) < 0) THEN
2132    iret = NF90_ENDDEF(ncid)
2133  ENDIF
2134!-     
2135! 3.0 Is this itau already on the axis ?
2136!     If not then check that all variables of previous time is OK.
2137!-
2138  IF (check) WRITE(*,*) 'RESTPUT 3.0 : ',itau,itau_out(fid)
2139!-
2140  IF (itau /= itau_out(fid)) THEN
2141!---
2142!-- If it is the first time step written on the restart
2143!-- then we only check the number
2144!-- Else we see if every variable was written
2145!---
2146    IF (tstp_out(fid) == 0) THEN
2147      IF (nbvar_out(fid) < nbvar_read(fid)) THEN
2148        WRITE(*,*) "ERROR :",tstp_out(fid), &
2149                   nbvar_out(fid),nbvar_read(fid)
2150        CALL ipslerr (1,'restput', &
2151 &        'There are fewer variables read from the output file', &
2152 &        'than written onto the input file.', &
2153 &        'We trust you know what you are doing')
2154      ENDIF
2155    ELSE
2156      ierr = 0
2157      DO iv=1,nbvar_out(fid)
2158        IF (.NOT.touched_out(fid,iv)) ierr = ierr+1
2159      ENDDO
2160      IF (ierr > 0) THEN
2161        WRITE(*,*) "ERROR :",nbvar_out(fid)
2162        CALL ipslerr (1,'restput', &
2163 &        'There are fewer variables in the output file for this', &
2164 &        'time step than for the previous one',' ')
2165      ELSE
2166        touched_out(fid,:) = .FALSE.
2167      ENDIF
2168    ENDIF
2169!---
2170    secsince = itau*deltat(fid)
2171    corner(1) =  tstp_out(fid)+1
2172    edge(1) = 1
2173!---
2174!-- 3.1 Here we add the values to the time axes
2175!---
2176    IF (check) THEN
2177      WRITE(*,*) 'RESTPUT 3.1 : ',itau,secsince,corner(1),edge(1)
2178    ENDIF
2179!---
2180    iret = NF90_PUT_VAR(ncid,tind_varid_out(fid),itau, &
2181 &                      start=corner(1:1))
2182    iret = NF90_PUT_VAR(ncid,tax_varid_out(fid),secsince, &
2183 &                      start=corner(1:1))
2184!---
2185    tstp_out(fid) = tstp_out(fid)+1
2186    itau_out(fid) = itau
2187  ENDIF
2188!-
2189! 4.0 Variable and time step should be present
2190!     now so we can dump variable
2191!-
2192  ndims = 0
2193  IF (iim > 0) THEN
2194    ndims = ndims+1
2195    corner(ndims) = 1
2196    edge(ndims) = iim
2197  ENDIF
2198  IF (jjm > 0) THEN
2199    ndims = ndims+1
2200    corner(ndims) = 1
2201    edge(ndims) = jjm
2202  ENDIF
2203  IF (llm > 0) THEN
2204    ndims = ndims+1
2205    corner(ndims) = 1
2206    edge(ndims) = llm
2207  ENDIF
2208  ndims = ndims+1
2209  corner(ndims) = tstp_out(fid) 
2210  edge(ndims) = 1
2211!-
2212  iret = NF90_PUT_VAR(ncid,vid,var, &
2213 &                    start=corner(1:ndims),count=edge(1:ndims))
2214!-
2215  IF (iret /= NF90_NOERR) THEN
2216    WRITE (*,*) ' restput error ',NF90_STRERROR(iret)
2217  ENDIF
2218!-
2219!  5.0 Note that the variables was treated
2220!-
2221  touched_out(fid,vnb) = .TRUE.
2222!---------------------------
2223END  SUBROUTINE restput_real
2224!-
2225!===
2226!-
2227SUBROUTINE restdefv (fid,varname,iim,jjm,llm,write_att)
2228!---------------------------------------------------------------------
2229! This subroutine adds a variable to the output file.
2230! The attributes are either taken from .
2231!---------------------------------------------------------------------
2232  IMPLICIT NONE
2233!-
2234  INTEGER ::fid
2235  CHARACTER(LEN=*) :: varname
2236  INTEGER :: iim,jjm,llm
2237  LOGICAL :: write_att
2238!-
2239! Local
2240!-
2241  INTEGER :: dims(4),ic,xloc,ndim,ncfid
2242  INTEGER :: iret,ax_id
2243  CHARACTER(LEN=3) :: str
2244!-
2245  LOGICAL :: check = .FALSE.
2246!---------------------------------------------------------------------
2247  ncfid = netcdf_id(fid,2)
2248  IF (nbvar_out(fid) >= max_var) THEN
2249    CALL ipslerr (3,'restdefv', &
2250      'Too many variables for the restcom module', &
2251      'Please increase the value of max_var',' ')
2252  ENDIF
2253  nbvar_out(fid) = nbvar_out(fid)+1
2254  varname_out(fid,nbvar_out(fid)) = varname
2255!-
2256! 0.0 Put the file in define mode if needed
2257!-
2258  IF (itau_out(fid) >= 0) THEN
2259    iret = NF90_REDEF(ncfid)
2260  ENDIF
2261!-
2262! 1.0 Do we have all dimensions and can we go ahead     
2263!-
2264  IF (check) THEN
2265    WRITE(*,*) 'restdefv 1.0 :',TRIM(varname),nbvar_out(fid) 
2266  ENDIF
2267!-
2268  ndim = 0
2269!-
2270! 1.1 Work on x
2271!-
2272  IF (iim > 0) THEN
2273    ndim = ndim+1
2274    xloc = 0
2275    DO ic=1,xax_nb(fid) 
2276      IF (xax_infs(fid,ic,1) == iim) xloc = ic
2277    ENDDO
2278!---
2279    IF (xloc > 0) THEN
2280      dims(ndim) = xax_infs(fid,xloc,2)
2281    ELSE
2282      str='x_'//CHAR(96+xax_nb(fid))
2283      iret = NF90_DEF_DIM(ncfid,str,iim,ax_id)
2284      xax_nb(fid) = xax_nb(fid)+1
2285      xax_infs(fid,xax_nb(fid),1) = iim
2286      xax_infs(fid,xax_nb(fid),2) = ax_id
2287      dims(ndim) = ax_id
2288    ENDIF
2289  ENDIF
2290!-
2291! 1.2 Work on y
2292!-
2293  IF (jjm > 0) THEN
2294    ndim = ndim+1
2295    xloc = 0
2296    DO ic=1,yax_nb(fid) 
2297      IF (yax_infs(fid,ic,1) == jjm) xloc = ic
2298    ENDDO
2299!---
2300    IF (xloc > 0) THEN
2301      dims(ndim) = yax_infs(fid,xloc,2)
2302    ELSE
2303      str='y_'//CHAR(96+yax_nb(fid))
2304      iret = NF90_DEF_DIM(ncfid,str,jjm,ax_id)
2305      yax_nb(fid) = yax_nb(fid)+1
2306      yax_infs(fid,yax_nb(fid),1) = jjm
2307      yax_infs(fid,yax_nb(fid),2) = ax_id
2308      dims(ndim) = ax_id
2309    ENDIF
2310  ENDIF
2311!-
2312! 1.3 Work on z
2313!-
2314  IF (llm > 0) THEN
2315    ndim = ndim+1
2316    xloc = 0
2317    DO ic=1,zax_nb(fid) 
2318      IF (zax_infs(fid,ic,1) == llm) xloc = ic
2319    ENDDO
2320!---
2321    IF (xloc > 0) THEN
2322      dims(ndim) = zax_infs(fid,xloc,2)
2323    ELSE
2324      str='z_'//CHAR(96+zax_nb(fid))
2325      iret = NF90_DEF_DIM(ncfid,str,llm,ax_id)
2326      zax_nb(fid) = zax_nb(fid)+1
2327      zax_infs(fid,zax_nb(fid),1) = llm
2328      zax_infs(fid,zax_nb(fid),2) = ax_id
2329      dims(ndim) = ax_id
2330    ENDIF
2331  ENDIF
2332!-
2333! 1.4  Time needs to be added
2334!-
2335  ndim = ndim+1
2336  dims(ndim) = tdimid_out(fid)
2337!-
2338! 2.0  Declare the variable
2339!-
2340  IF (check) THEN
2341    WRITE(*,*) 'restdefv 2.0 :',ndim,' :: ',dims(1:ndim),tdimid_out(fid)
2342  ENDIF
2343!-
2344  iret = NF90_DEF_VAR(ncfid,varname,NF90_DOUBLE,dims(1:ndim), &
2345 &                    varid_out(fid,nbvar_out(fid)))
2346  IF (iret /= NF90_NOERR) THEN
2347    CALL ipslerr (3,'restdefv', &
2348      'Could not define new variable in file', &
2349      NF90_STRERROR(iret),varname)
2350  ENDIF
2351!-
2352! 3.0 Add the attributes if requested
2353!-
2354  IF (write_att) THEN
2355    IF (rest_units /= 'XXXXX') THEN
2356      iret =  NF90_PUT_ATT(ncfid,varid_out(fid,nbvar_out(fid)), &
2357 &                         'units',TRIM(rest_units))
2358      rest_units = 'XXXXX'
2359    ENDIF
2360!---
2361    IF (rest_lname /= 'XXXXX') THEN
2362      iret =  NF90_PUT_ATT(ncfid,varid_out(fid,nbvar_out(fid)), &
2363 &                         'long_name',TRIM(rest_lname))
2364      rest_lname  = 'XXXXX'
2365    ENDIF
2366!---
2367    iret = NF90_PUT_ATT(ncfid,varid_out(fid,nbvar_out(fid)), &
2368 &                      'missing_value',REAL(missing_val,KIND=4))
2369!---
2370    IF (itau_out(fid) >= 0) THEN
2371      iret = NF90_ENDDEF(ncfid)
2372    ENDIF
2373  ENDIF
2374!-
2375  IF (check) THEN
2376    WRITE(*,*) &
2377 &    'restdefv 3.0 : LIST OF VARS ',varname_out(fid,1:nbvar_out(fid))
2378  ENDIF
2379!----------------------
2380END SUBROUTINE restdefv
2381!-
2382!===
2383!-
2384SUBROUTINE ioconf_setatt (attname,value)
2385!---------------------------------------------------------------------
2386  IMPLICIT NONE
2387!-
2388  CHARACTER(LEN=*) :: attname,value
2389!-
2390! LOCAL
2391!-
2392  CHARACTER(LEN=LEN_TRIM(attname)) :: tmp_str
2393!---------------------------------------------------------------------
2394  tmp_str = attname
2395  CALL strlowercase (tmp_str)
2396!-
2397  SELECT CASE(tmp_str)
2398    CASE('units')
2399      rest_units = value
2400    CASE('long_name')
2401      rest_lname = value
2402    CASE DEFAULT
2403      CALL ipslerr (2,'ioconf_restatt', &
2404        'The attribute name provided is unknown',attname,' ')
2405  END SELECT
2406!---------------------------
2407END SUBROUTINE ioconf_setatt
2408!-
2409!===
2410!-
2411SUBROUTINE ioget_vdim (fid,vname_q,varnbdim_max,varnbdim,vardims)
2412!---------------------------------------------------------------------
2413!- This routine allows the user to get the dimensions
2414!- of a field in the restart file.
2415!- This is the file which is read.
2416!---------------------------------------------------------------------
2417  IMPLICIT NONE
2418!-
2419  INTEGER,INTENT(IN) :: fid
2420  CHARACTER(LEN=*) :: vname_q
2421  INTEGER,INTENT(IN) :: varnbdim_max
2422  INTEGER,INTENT(OUT) ::  varnbdim
2423  INTEGER,DIMENSION(varnbdim_max),INTENT(OUT) :: vardims
2424!-
2425! LOCAL
2426!-
2427  INTEGER :: vnb
2428!---------------------------------------------------------------------
2429! Find the index of the variable
2430  CALL find_str (varname_in(fid,1:nbvar_in(fid)),vname_q,vnb)
2431!-
2432  IF (vnb > 0) THEN
2433    varnbdim = varnbdim_in(fid,vnb)
2434    IF (varnbdim_max < varnbdim) THEN
2435      CALL ipslerr (3,'ioget_vdim', &
2436        'The provided array for the variable dimensions is too small', &
2437        '','')
2438    ELSE
2439      vardims(1:varnbdim) = vardims_in(fid,vnb,1:varnbdim)
2440    ENDIF
2441  ELSE
2442    varnbdim = 0
2443    CALL ipslerr (2,'ioget_vdim', &
2444      'Variable '//TRIM(vname_q)//' not found','','')
2445  ENDIF
2446!------------------------
2447END SUBROUTINE ioget_vdim
2448!-
2449!===
2450!-
2451SUBROUTINE ioget_vname (fid,nbvar,varnames)
2452!---------------------------------------------------------------------
2453!- This routine allows the user to extract the list
2454!- of variables in an opened restart file.
2455!- This is the file which is read
2456!---------------------------------------------------------------------
2457  IMPLICIT NONE
2458!-
2459  INTEGER,INTENT(IN) :: fid
2460  INTEGER,INTENT(OUT) ::  nbvar
2461  CHARACTER(LEN=*),INTENT(OUT) :: varnames(:)
2462!---------------------------------------------------------------------
2463  nbvar = nbvar_in(fid)
2464!-
2465  IF (SIZE(varnames) < nbvar) THEN
2466    CALL ipslerr (3,'ioget_vname', &
2467      'The provided array for the variable names is too small','','')
2468  ELSE
2469    varnames(1:nbvar) = varname_in(fid,1:nbvar)
2470  ENDIF
2471!-------------------------
2472END SUBROUTINE ioget_vname
2473!-
2474!===
2475!-
2476SUBROUTINE ioconf_expval (new_exp_val)
2477!---------------------------------------------------------------------
2478!- The default value written into the variables which are not
2479!- in the restart file can only be changed once.
2480!- This avoids further complications.
2481!---------------------------------------------------------------------
2482  IMPLICIT NONE
2483!-
2484  REAL :: new_exp_val
2485!---------------------------------------------------------------------
2486  IF (.NOT.lock_valexp) THEN
2487    lock_valexp = .TRUE.
2488    val_exp = new_exp_val
2489  ELSE
2490    CALL ipslerr (2,'ioconf_expval', &
2491     'The default value for variable' &
2492   //'not available in the restart file ', &
2493     'has already been locked and can not be changed at this point', &
2494     ' ')
2495  ENDIF
2496!---------------------------
2497END SUBROUTINE ioconf_expval
2498!-
2499!===
2500!-
2501SUBROUTINE ioget_expval (get_exp_val)
2502!---------------------------------------------------------------------
2503!- Once the user has extracted the default value,
2504!- we lock it so that it can not be changed anymore.
2505!---------------------------------------------------------------------
2506  IMPLICIT NONE
2507!-
2508  REAL :: get_exp_val
2509!---------------------------------------------------------------------
2510  get_exp_val = val_exp
2511  lock_valexp = .TRUE.
2512!--------------------------
2513END SUBROUTINE ioget_expval
2514!-
2515!===
2516!-
2517SUBROUTINE restclo (fid)
2518!---------------------------------------------------------------------
2519!- This subroutine closes one or any opened restart file.
2520!-
2521!- INPUT
2522!-
2523!- fid    : File ID in the restcom system (not the netCDF ID)(optional)
2524!-
2525!- OUTPUT
2526!-
2527!- NONE
2528!---------------------------------------------------------------------
2529  IMPLICIT NONE
2530!-
2531  INTEGER,INTENT(in),OPTIONAL :: fid
2532!-
2533!- LOCAL
2534!-
2535  INTEGER :: iret,ifnc
2536  CHARACTER(LEN=6) :: n_e
2537  CHARACTER(LEN=3) :: n_f
2538  LOGICAL :: check = .FALSE.
2539!---------------------------------------------------------------------
2540  IF (PRESENT(fid)) THEN
2541!---
2542    IF (check) THEN
2543      WRITE(*,*) &
2544        'restclo : Closing specified restart file number :', &
2545        fid,netcdf_id(fid,1:2) 
2546    ENDIF
2547!---
2548    IF (netcdf_id(fid,1) > 0) THEN
2549      iret = NF90_CLOSE(netcdf_id(fid,1))
2550      IF (iret /= NF90_NOERR) THEN
2551        WRITE (n_e,'(I6)') iret
2552        WRITE (n_f,'(I3)') netcdf_id(fid,1)
2553        CALL ipslerr (2,'restclo', &
2554          "Error "//n_e//" in closing file : "//n_f,'',' ')
2555      ENDIF
2556      IF (netcdf_id(fid,1) == netcdf_id(fid,2)) THEN
2557        netcdf_id(fid,2) = -1
2558      ENDIF
2559      netcdf_id(fid,1) = -1
2560    ENDIF
2561!---
2562    IF (netcdf_id(fid,2) > 0)  THEN
2563      iret = NF90_CLOSE(netcdf_id(fid,2))
2564      IF (iret /= NF90_NOERR) THEN
2565        WRITE (n_e,'(I6)') iret
2566        WRITE (n_f,'(I3)') netcdf_id(fid,2)
2567        CALL ipslerr (2,'restclo', &
2568          "Error "//n_e//" in closing file : "//n_f,'',' ')
2569      ENDIF
2570      netcdf_id(fid,2) = -1
2571    ENDIF
2572!---
2573  ELSE
2574!---
2575    IF (check) WRITE(*,*) 'restclo : Closing all files'
2576!---
2577    DO ifnc=1,nbfiles
2578      IF (netcdf_id(ifnc,1) > 0) THEN
2579        iret = NF90_CLOSE(netcdf_id(ifnc,1))
2580        IF (iret /= NF90_NOERR) THEN
2581          WRITE (n_e,'(I6)') iret
2582          WRITE (n_f,'(I3)') netcdf_id(ifnc,1)
2583          CALL ipslerr (2,'restclo', &
2584            "Error "//n_e//" in closing file : "//n_f,'',' ')
2585        ENDIF
2586        IF (netcdf_id(ifnc,1) == netcdf_id(ifnc,2)) THEN
2587          netcdf_id(ifnc,2) = -1
2588        ENDIF
2589        netcdf_id(ifnc,1) = -1
2590      ENDIF
2591!-----
2592      IF (netcdf_id(ifnc,2) > 0) THEN
2593        iret = NF90_CLOSE(netcdf_id(ifnc,2))
2594        IF (iret /= NF90_NOERR) THEN
2595          WRITE (n_e,'(I6)') iret
2596          WRITE (n_f,'(I3)') netcdf_id(ifnc,2)
2597          CALL ipslerr (2,'restclo', &
2598            "Error "//n_e//" in closing file : "//n_f,'',' ')
2599        END IF
2600        netcdf_id(ifnc,2) = -1
2601      ENDIF
2602    ENDDO
2603  ENDIF
2604!---------------------
2605END SUBROUTINE restclo
2606!-
2607!===
2608!-
2609END MODULE restcom
Note: See TracBrowser for help on using the repository browser.