source: IOIPSL/tags/v2_2_3/src/restcom.f90 @ 2313

Last change on this file since 2313 was 2020, checked in by jgipsl, 11 years ago

Added NF90_64BIT_OFFSET for creation of restart file. Needed for ORCHIDEE high resolution.

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