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

Last change on this file since 4 was 4, checked in by rblod, 18 years ago

First import of IOIPSL sources

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