New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
restcom.f90 in utils/tools/DOMAINcfg/src – NEMO

source: utils/tools/DOMAINcfg/src/restcom.f90 @ 14623

Last change on this file since 14623 was 14623, checked in by ldebreu, 3 years ago

AGFdomcfg: 1) Update DOMAINcfg to be compliant with the removal of halo cells 2) Update most of the LBC ... subroutines to a recent NEMO 4 version #2638

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