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

Last change on this file since 125 was 122, checked in by bellier, 17 years ago

JB: some cleaning (-> fortran 90)

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