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

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

Added an initialization for overwrite_time

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