source: dynamico_lmdz/aquaplanet/IOIPSL/src/.#histcom.f90.2.2 @ 4052

Last change on this file since 4052 was 3847, checked in by ymipsl, 10 years ago

Add IOIPSL in the configuration.
Temporary configuration.
Makefile is ready for Curie

YM

File size: 86.0 KB
Line 
1#define NF90_FLOAT NF90_DOUBLE
2
3MODULE histcom
4!-
5!$Header: /home/ioipsl/CVSROOT/IOIPSL/src/histcom.f90,v 2.3 2005/10/10 08:02:57 adm Exp $
6!-
7  USE netcdf
8!-
9  USE stringop,  ONLY : nocomma,cmpblank,findpos,find_str,strlowercase
10  USE mathelp,   ONLY : mathop,moycum,trans_buff,buildop
11  USE fliocom,   ONLY : flio_dom_file,flio_dom_att
12  USE calendar
13  USE errioipsl, ONLY : ipslerr
14!-
15  IMPLICIT NONE
16!-
17  PRIVATE
18  PUBLIC :: histbeg, histdef, histhori, histvert, histend, &
19 &          histwrite, histclo, histsync, ioconf_modname
20!---------------------------------------------------------------------
21!- Some confusing vocabulary in this code !
22!- =========================================
23!-
24!- A REGULAR grid is a grid which is i,j indexes
25!- and thus it is stored in a 2D matrix.
26!- This is opposed to a IRREGULAR grid which is only in a vector
27!- and where we do not know which neighbors we have.
28!- As a consequence we need the bounds for each grid-cell.
29!-
30!- A RECTILINEAR grid is a special case of a regular grid
31!- in which all longitudes for i constant are equal
32!- and all latitudes for j constant.
33!- In other words we do not need the full 2D matrix
34!- to describe the grid, just two vectors.
35!---------------------------------------------------------------------
36  INTERFACE histwrite
37!---------------------------------------------------------------------
38!- The "histwrite" routines will give the data to the I/O system.
39!- It will trigger the operations to be performed,
40!- and the writting to the file if needed
41!-
42!- We test for the work to be done at this time here so that at a
43!- later stage we can call different operation and write subroutine
44!- for the REAL and INTEGER interfaces
45!-
46!- INPUT
47!- pfileid  : The ID of the file on which this variable is to be,
48!-            written. The variable should have been defined in
49!-            this file before.
50!- pvarname : The short name of the variable
51!- pitau    : Current timestep
52!- pdata    : The variable, I mean the real data !
53!- nbindex  : The number of indexes provided. If it is equal to
54!-            the size of the full field as provided in histdef
55!-            then nothing is done.
56!- nindex   : The indices used to expand the variable (pdata)
57!-            onto the full field.
58!---------------------------------------------------------------------
59!- histwrite - we have to prepare different type of fields :
60!-             real and integer, 1,2 or 3D
61    MODULE PROCEDURE histwrite_r1d,histwrite_r2d,histwrite_r3d
62  END INTERFACE
63!-
64  INTERFACE histbeg
65!!  MODULE PROCEDURE histbeg_regular,histbeg_irregular
66    MODULE PROCEDURE histbeg_totreg,histbeg_regular,histbeg_irregular
67  END INTERFACE
68!-
69  INTERFACE histhori
70    MODULE PROCEDURE histhori_regular,histhori_irregular
71  END INTERFACE
72!-
73! Fixed parameter
74!-
75  INTEGER,PARAMETER :: nb_files_max=20, nb_var_max=700, &
76 &                     nb_hax_max=5, nb_zax_max=10, nbopp_max=10
77  REAL,PARAMETER :: missing_val=1.e20
78!-                 or HUGE(1.0) maximum real number
79!-
80  INTEGER :: bufftmp_max(nb_files_max) = 1
81!-
82! Time variables
83!-
84  INTEGER,SAVE :: itau0(nb_files_max)=0
85  REAL,DIMENSION(nb_files_max),SAVE ::date0,deltat
86!-
87! Counter of elements
88!-
89  INTEGER,SAVE :: nb_files=0
90  INTEGER,DIMENSION(nb_files_max),SAVE :: nb_var=0, nb_tax=0
91!-
92! NETCDF IDs for files and axes
93!-
94  INTEGER,DIMENSION(nb_files_max),SAVE :: ncdf_ids,xid,yid,tid
95  CHARACTER(LEN=500),SAVE :: assc_file=''
96!-
97! General definitions in the NETCDF file
98!-
99  INTEGER,DIMENSION(nb_files_max,2),SAVE :: &
100 &   full_size=0,slab_ori,slab_sz
101!-
102! The horizontal axes
103!-
104  INTEGER,SAVE :: nb_hax(nb_files_max)=0
105  CHARACTER(LEN=25),SAVE :: hax_name(nb_files_max,nb_hax_max,2)
106!-
107! The vertical axes
108!-
109  INTEGER,SAVE :: nb_zax(nb_files_max)=0
110  INTEGER,DIMENSION(nb_files_max,nb_zax_max),SAVE :: &
111  &  zax_size,zax_ids,zax_name_length
112  CHARACTER(LEN=20),SAVE :: zax_name(nb_files_max,nb_zax_max)
113!-
114! Informations on each variable
115!-
116  INTEGER,DIMENSION(nb_files_max,nb_var_max),SAVE :: &
117 &  name_length,nbopp
118  CHARACTER(LEN=20),DIMENSION(nb_files_max,nb_var_max),SAVE :: &
119 &  name,unit_name
120  CHARACTER(LEN=80),DIMENSION(nb_files_max,nb_var_max),SAVE :: &
121 &  title,fullop
122  CHARACTER(LEN=7),SAVE :: topp(nb_files_max,nb_var_max)
123  CHARACTER(LEN=7),SAVE :: sopps(nb_files_max,nb_var_max,nbopp_max)
124  REAL,SAVE :: scal(nb_files_max,nb_var_max,nbopp_max)
125!- Sizes of the associated grid and zommed area
126  INTEGER,DIMENSION(nb_files_max,nb_var_max,3),SAVE :: &
127 &   scsize,zorig,zsize
128!- Sizes for the data as it goes through the various math operations
129  INTEGER,SAVE :: datasz_in(nb_files_max,nb_var_max,3) = -1
130  INTEGER,SAVE :: datasz_max(nb_files_max,nb_var_max) = -1
131!-
132  INTEGER,DIMENSION(nb_files_max,nb_var_max),SAVE :: &
133 &  var_haxid,var_zaxid,var_axid,ncvar_ids
134!-
135  REAL,SAVE :: minmax(nb_files_max,nb_var_max,2)
136!-
137  REAL,DIMENSION(nb_files_max,nb_var_max),SAVE :: &
138 &  freq_opp,freq_wrt
139  INTEGER,DIMENSION(nb_files_max,nb_var_max),SAVE :: &
140 &  last_opp,last_wrt,last_opp_chk,last_wrt_chk,nb_opp,nb_wrt,point
141!-
142! Book keeping for the buffers
143!-
144  INTEGER,SAVE :: buff_pos=0
145  REAL,ALLOCATABLE,SAVE :: buffer(:)
146  LOGICAL,SAVE :: &
147 &  zoom(nb_files_max)=.FALSE., regular(nb_files_max)=.TRUE.
148!-
149! Book keeping of the axes
150!-
151  INTEGER,DIMENSION(nb_files_max,nb_var_max),SAVE :: &
152 &  tdimid,tax_last,tax_name_length
153  CHARACTER(LEN=40),DIMENSION(nb_files_max,nb_var_max),SAVE :: &
154 &  tax_name
155!-
156! A list of functions which require special action
157! (Needs to be updated when functions are added
158!  but they are well located here)
159!-
160  CHARACTER(LEN=120),SAVE :: &
161 &  indchfun = 'scatter, fill, gather, coll', &
162 &  fuchnbout = 'scatter, fill'
163!- Some configurable variables with locks
164  CHARACTER(LEN=80),SAVE :: model_name='An IPSL model'
165  LOGICAL,SAVE :: lock_modname=.FALSE.
166!-
167!===
168CONTAINS
169!===
170!-
171SUBROUTINE histbeg_totreg                     &
172 & (pfilename, pim, plon, pjm, plat,          &
173 &  par_orix, par_szx, par_oriy, par_szy,     &
174 &  pitau0, pdate0, pdeltat, phoriid, pfileid, domain_id)
175!---------------------------------------------------------------------
176!- This is just an interface for histbeg_regular in case when
177!- the user provides plon and plat as vectors. Obviously this can only
178!- be used for very regular grids.
179!-
180!- INPUT
181!-
182!- pfilename : Name of the netcdf file to be created
183!- pim       : Size of arrays in longitude direction
184!- plon      : Coordinates of points in longitude
185!- pjm       : Size of arrays in latitude direction
186!- plat      : Coordinates of points in latitude
187!-
188!- The next 4 arguments allow to define a horizontal zoom
189!- for this file. It is assumed that all variables to come
190!- have the same index space. This can not be assumed for
191!- the z axis and thus we define the zoom in histdef.
192!-
193!- par_orix  : Origin of the slab of data within the X axis (pim)
194!- par_szx   : Size of the slab of data in X
195!- par_oriy  : Origin of the slab of data within the Y axis (pjm)
196!- par_szy   : Size of the slab of data in Y
197!-
198!- pitau0    : time step at which the history tape starts
199!- pdate0    : The Julian date at which the itau was equal to 0
200!- pdeltat   : Time step in seconds. Time step of the counter itau
201!-             used in histwrt for instance
202!-
203!- OUTPUT
204!-
205!- phoriid   : ID of the horizontal grid
206!- pfileid   : ID of the netcdf file
207!-
208!- Optional INPUT arguments
209!-
210!- domain_id       : Domain identifier
211!-
212!- TO DO
213!-
214!- This package should be written in f90
215!- and use the following features :
216!-    - structures for the meta-data of the files and variables
217!-    - memory allocation as needed
218!-    - Pointers
219!-
220!- VERSION
221!-
222!---------------------------------------------------------------------
223  IMPLICIT NONE
224!-
225  CHARACTER(LEN=*) :: pfilename
226  INTEGER,INTENT(IN) :: pim,pjm
227  REAL,DIMENSION(pim),INTENT(IN) :: plon
228  REAL,DIMENSION(pjm),INTENT(IN) :: plat
229  INTEGER,INTENT(IN):: par_orix,par_szx,par_oriy,par_szy
230  INTEGER,INTENT(IN) :: pitau0
231  REAL,INTENT(IN) :: pdate0,pdeltat
232  INTEGER,INTENT(OUT) :: pfileid,phoriid
233  INTEGER,INTENT(IN),OPTIONAL :: domain_id
234!-
235  LOGICAL :: check = .FALSE.
236!-
237  REAL,ALLOCATABLE,DIMENSION(:,:) :: lon_tmp,lat_tmp
238!---------------------------------------------------------------------
239  IF (check) WRITE(*,*) "histbeg_totreg"
240!-
241  ALLOCATE (lon_tmp(pim,pjm),lat_tmp(pim,pjm))
242!-
243  lon_tmp(:,:) = SPREAD(plon(:),2,pjm)
244  lat_tmp(:,:) = SPREAD(plat(:),1,pim)
245!-
246  CALL histbeg_regular &
247 &  (pfilename,pim,lon_tmp,pjm,lat_tmp, &
248 &   par_orix,par_szx,par_oriy,par_szy, &
249 &   pitau0,pdate0,pdeltat,phoriid,pfileid, &
250 &   .TRUE.,domain_id)
251!-
252  DEALLOCATE (lon_tmp, lat_tmp)
253!----------------------------
254END SUBROUTINE histbeg_totreg
255!===
256SUBROUTINE histbeg_regular &
257 & (pfilename, pim, plon, pjm, plat,         &
258 &  par_orix, par_szx, par_oriy, par_szy,    &
259 &  pitau0, pdate0, pdeltat, phoriid, pfileid, &
260 &  opt_rectilinear, domain_id)
261!---------------------------------------------------------------------
262!- This subroutine initializes a netcdf file and returns the ID.
263!- It will set up the geographical space on which the data will be
264!- stored and offers the possibility of seting a zoom.
265!- It also gets the global parameters into the I/O subsystem.
266!-
267!- INPUT
268!-
269!- pfilename : Name of the netcdf file to be created
270!- pim       : Size of arrays in longitude direction
271!- plon      : Coordinates of points in longitude
272!- pjm       : Size of arrays in latitude direction
273!- plat      : Coordinates of points in latitude
274!-
275!- The next 4 arguments allow to define a horizontal zoom
276!- for this file. It is assumed that all variables to come
277!- have the same index space. This can not be assumed for
278!- the z axis and thus we define the zoom in histdef.
279!-
280!- par_orix  : Origin of the slab of data within the X axis (pim)
281!- par_szx   : Size of the slab of data in X
282!- par_oriy  : Origin of the slab of data within the Y axis (pjm)
283!- par_szy   : Size of the slab of data in Y
284!-
285!- pitau0    : time step at which the history tape starts
286!- pdate0    : The Julian date at which the itau was equal to 0
287!- pdeltat   : Time step in seconds. Time step of the counter itau
288!-             used in histwrt for instance
289!-
290!- OUTPUT
291!-
292!- phoriid   : ID of the horizontal grid
293!- pfileid   : ID of the netcdf file
294!-
295!- Optional INPUT arguments
296!-
297!- opt_rectilinear : If true we know the grid is rectilinear
298!- domain_id       : Domain identifier
299!-
300!- TO DO
301!-
302!- This package should be written in F90 and use the following
303!- feature :
304!-   - structures for the meta-data of the files and variables
305!-   - memory allocation as needed
306!-   - Pointers
307!-
308!- VERSION
309!-
310!---------------------------------------------------------------------
311  IMPLICIT NONE
312!-
313  CHARACTER(LEN=*) :: pfilename
314  INTEGER,INTENT(IN) :: pim,pjm
315  REAL,DIMENSION(pim,pjm),INTENT(IN) :: plon,plat
316  INTEGER,INTENT(IN):: par_orix, par_szx, par_oriy, par_szy
317  INTEGER,INTENT(IN) :: pitau0
318  REAL,INTENT(IN) :: pdate0, pdeltat
319  INTEGER,INTENT(OUT) :: pfileid, phoriid
320  LOGICAL,INTENT(IN),OPTIONAL :: opt_rectilinear
321  INTEGER,INTENT(IN),OPTIONAL :: domain_id
322!-
323  INTEGER :: ncid, iret
324  INTEGER :: lengf, lenga
325  CHARACTER(LEN=120) :: file
326  CHARACTER(LEN=30) :: timenow
327  LOGICAL :: rectilinear
328!-
329  LOGICAL :: check = .FALSE.
330!---------------------------------------------------------------------
331  nb_files = nb_files+1
332  pfileid  = nb_files
333!-
334! 1.0 Transfering into the common for future use
335!-
336  IF (check) WRITE(*,*) "histbeg_regular 1.0"
337!-
338  itau0(pfileid) = pitau0
339  date0(pfileid) = pdate0
340  deltat(pfileid) = pdeltat
341!-
342  IF (PRESENT(opt_rectilinear)) THEN
343    rectilinear = opt_rectilinear
344  ELSE
345    rectilinear = .FALSE.
346  ENDIF
347!-
348! 2.0 Initializes all variables for this file
349!-
350  IF (check) WRITE(*,*) "histbeg_regular 2.0"
351!-
352  IF (nb_files > nb_files_max) THEN
353    CALL ipslerr (3,"histbeg", &
354   &  'Table of files too small. You should increase nb_files_max', &
355   &  'in M_HISTCOM.f90 in order to accomodate all these files', ' ')
356  ENDIF
357!-
358  nb_var(pfileid) = 0
359  nb_tax(pfileid) = 0
360  nb_hax(pfileid) = 0
361  nb_zax(pfileid) = 0
362!-
363  slab_ori(pfileid,1:2) = (/ par_orix, par_oriy /)
364  slab_sz(pfileid,1:2)  = (/ par_szx,  par_szy  /)
365!-
366! 3.0 Opening netcdf file and defining dimensions
367!-
368  IF (check) WRITE(*,*) "histbeg_regular 3.0"
369!-
370! Add DOMAIN number and ".nc" suffix in file name if needed
371!-
372  file  = pfilename
373  CALL flio_dom_file (file,domain_id)
374!-
375! Keep track of the name of the files opened
376!-
377  lengf=LEN_TRIM(file)
378  lenga=LEN_TRIM(assc_file)
379  IF (nb_files == 1) THEN
380    assc_file=file(1:lengf)
381  ELSE IF ( (lenga+lengf) < 500) THEN
382    assc_file = assc_file(1:lenga)//' '//file(1:lengf)
383  ELSE IF (     ((lenga+7) < 500) &
384         & .AND.(INDEX(assc_file(1:lenga),'et.al.') < 1) ) THEN
385    assc_file = assc_file(1:lenga)//' et.al.'
386  ELSE
387    CALL ipslerr (2,"histbeg", &
388   & 'The file names do not fit into the associate_file attribute.', &
389   & 'Use shorter names if you wish to keep the information.',' ')
390  ENDIF
391!-
392  print *,"FILENAME---->",file
393  iret = NF90_CREATE (file, NF90_CLOBBER, ncid)
394!-
395  IF (rectilinear) THEN
396    iret = NF90_DEF_DIM (ncid, 'lon', par_szx, xid(nb_files))
397    iret = NF90_DEF_DIM (ncid, 'lat', par_szy, yid(nb_files))
398  ELSE
399    iret = NF90_DEF_DIM (ncid, 'x', par_szx, xid(nb_files))
400    iret = NF90_DEF_DIM (ncid, 'y', par_szy, yid(nb_files))
401  ENDIF
402!-
403! 4.0 Declaring the geographical coordinates and other attributes
404!-
405  IF (check) WRITE(*,*) "histbeg_regular 4.0"
406!-
407! 4.3 Global attributes
408!-
409  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'Conventions','GDT 1.3')
410  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'file_name',TRIM(file))
411  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'production',TRIM(model_name))
412  lock_modname = .TRUE.
413  CALL ioget_timestamp (timenow)
414  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'TimeStamp',TRIM(timenow))
415!-
416! Add DOMAIN attributes if needed
417!-
418  CALL flio_dom_att (ncid,domain_id)
419!-
420! 5.0 Saving some important information on this file in the common
421!-
422  IF (check) WRITE(*,*) "histbeg_regular 5.0"
423!-
424  ncdf_ids(pfileid) = ncid
425  full_size(pfileid,1:2) = (/ pim, pjm /)
426!-
427! 6.0 storing the geographical coordinates
428!-
429  IF ( (pim /= par_szx).OR.(pjm /= par_szy) )   zoom(pfileid)=.TRUE.
430  regular(pfileid)=.TRUE.
431!-
432  CALL histhori_regular (pfileid, pim, plon, pjm, plat, &
433 &  ' ' , 'Default grid', phoriid, rectilinear)
434!-----------------------------
435END SUBROUTINE histbeg_regular
436!===
437SUBROUTINE histbeg_irregular &
438 &  (pfilename, pim, plon, plon_bounds, plat, plat_bounds,   &
439 &   pitau0, pdate0, pdeltat, phoriid, pfileid, domain_id)
440!---------------------------------------------------------------------
441!- This subroutine initializes a netcdf file and returns the ID.
442!- This version is for totaly irregular grids. In this case all
443!- all the data comes in as vectors and for the grid we have
444!- the coordinates of the 4 corners.
445!- It also gets the global parameters into the I/O subsystem.
446!-
447!- INPUT
448!-
449!- pfilename   : Name of the netcdf file to be created
450!- pim         : Size of arrays in longitude direction
451!- plon        : Coordinates of points in longitude
452!- plon_bounds : The 2 corners of the grid in longitude
453!- plat        : Coordinates of points in latitude
454!- plat_bounds : The 2 corners of the grid in latitude
455!-
456!- pitau0    : time step at which the history tape starts
457!- pdate0    : The Julian date at which the itau was equal to 0
458!- pdeltat   : Time step in seconds. Time step of the counter itau
459!-             used in histwrt for instance
460!-
461!- OUTPUT
462!-
463!- phoriid   : ID of the horizontal grid
464!- pfileid   : ID of the netcdf file
465!-
466!- Optional INPUT arguments
467!-
468!- domain_id       : Domain identifier
469!-
470!- TO DO
471!-
472!- This package should be written in F90 and use the following
473!- feature :
474!-   - structures for the meta-data of the files and variables
475!-   - memory allocation as needed
476!-   - Pointers
477!-
478!- VERSION
479!-
480!---------------------------------------------------------------------
481  IMPLICIT NONE
482!-
483  CHARACTER(LEN=*) :: pfilename
484  INTEGER,INTENT(IN) :: pim
485  REAL,DIMENSION(pim),INTENT(IN) :: plon,plat
486  REAL,DIMENSION(:,:),INTENT(IN) :: plon_bounds,plat_bounds
487  INTEGER,INTENT(IN) :: pitau0
488  REAL,INTENT(IN) :: pdate0, pdeltat
489  INTEGER,INTENT(OUT) :: pfileid, phoriid
490  INTEGER,INTENT(IN),OPTIONAL :: domain_id
491!-
492  INTEGER :: ncid, iret
493  INTEGER :: lengf, lenga
494  CHARACTER(LEN=120) :: file
495  CHARACTER(LEN=30) :: timenow
496!-
497  LOGICAL :: check = .FALSE.
498!---------------------------------------------------------------------
499  nb_files = nb_files+1
500  pfileid  = nb_files
501!-
502! 1.0 Transfering into the common for future use
503!-
504  IF (check) WRITE(*,*) "histbeg_irregular 1.0"
505!-
506  itau0(pfileid) = pitau0
507  date0(pfileid) = pdate0
508  deltat(pfileid) = pdeltat
509!-
510! 2.0 Initializes all variables for this file
511!-
512  IF (check) WRITE(*,*) "histbeg_irregular 2.0"
513!-
514  IF (nb_files > nb_files_max) THEN
515    CALL ipslerr (3,"histbeg", &
516   &  'Table of files too small. You should increase nb_files_max', &
517   &  'in M_HISTCOM.f90 in order to accomodate all these files', ' ')
518  ENDIF
519!-
520  nb_var(pfileid) = 0
521  nb_tax(pfileid) = 0
522  nb_hax(pfileid) = 0
523  nb_zax(pfileid) = 0
524!-
525  slab_ori(pfileid,1:2) = (/ 1, 1 /)
526  slab_sz(pfileid,1:2)  = (/ pim, 1 /)
527!-
528! 3.0 Opening netcdf file and defining dimensions
529!-
530  IF (check) WRITE(*,*) "histbeg_irregular 3.0"
531!-
532! Add DOMAIN number and ".nc" suffix in file name if needed
533!-
534  file  = pfilename
535  CALL flio_dom_file (file,domain_id)
536!-
537! Keep track of the name of the files opened
538!-
539  lengf=LEN_TRIM(file)
540  lenga=LEN_TRIM(assc_file)
541  IF (nb_files == 1) THEN
542    assc_file=file(1:lengf)
543  ELSE IF ( (lenga+lengf) < 500) THEN
544    assc_file = assc_file(1:lenga)//' '//file(1:lengf)
545  ELSE IF (     ((lenga+7) < 500) &
546         & .AND.(INDEX(assc_file(1:lenga),'et.al.') < 1) ) THEN
547    assc_file = assc_file(1:lenga)//' et.al.'
548  ELSE
549    CALL ipslerr (2,"histbeg", &
550   & 'The file names do not fit into the associate_file attribute.', &
551   & 'Use shorter names if you wish to keep the information.',' ')
552  ENDIF
553!-
554  iret = NF90_CREATE (file, NF90_CLOBBER, ncid)
555!-
556  iret = NF90_DEF_DIM (ncid, 'x', pim, xid(nb_files))
557  yid(nb_files) = 0
558!-
559!- 4.0 Declaring the geographical coordinates and other attributes
560!-
561   IF (check) WRITE(*,*) "histbeg_irregular 4.0"
562!-
563! 4.3 Global attributes
564!-
565  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'Conventions','GDT 1.3')
566  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'file_name',TRIM(file))
567  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'production',TRIM(model_name))
568  lock_modname = .TRUE.
569  CALL ioget_timestamp (timenow)
570  iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'TimeStamp',TRIM(timenow))
571!-
572! Add DOMAIN attributes if needed
573!-
574  CALL flio_dom_att (ncid,domain_id)
575!-
576! 5.0 Saving some important information on this file in the common
577!-
578  IF (check) WRITE(*,*) "histbeg_irregular 5.0"
579!-
580  ncdf_ids(pfileid) = ncid
581  full_size(pfileid,1:2) = (/ pim, 1 /)
582!-
583! 6.0 storing the geographical coordinates
584!-
585  zoom(pfileid)=.FALSE.
586  regular(pfileid)=.FALSE.
587!-
588  CALL histhori_irregular &
589 &  (pfileid, pim, plon, plon_bounds, plat, plat_bounds, &
590 &   ' ' , 'Default grid', phoriid)
591!-------------------------------
592END SUBROUTINE histbeg_irregular
593!===
594SUBROUTINE histhori_regular &
595 &  (pfileid,pim,plon,pjm,plat,phname,phtitle,phid,opt_rectilinear)
596!---------------------------------------------------------------------
597!- This subroutine is made to declare a new horizontale grid.
598!- It has to have the same number of points as
599!- the original and thus in this routine we will only
600!- add two variable (longitude and latitude).
601!- Any variable in the file can thus point to this pair
602!- through an attribute. This routine is very usefull
603!- to allow staggered grids.
604!-
605!- INPUT
606!-
607!- pfileid : The id of the file to which the grid should be added
608!- pim     : Size in the longitude direction
609!- plon    : The longitudes
610!- pjm     : Size in the latitude direction
611!- plat    : The latitudes
612!- phname  : The name of grid
613!- phtitle : The title of the grid
614!-
615!- OUTPUT
616!-
617!- phid    : Id of the created grid
618!-
619!- OPTIONAL
620!-
621!- opt_rectilinear : If true we know the grid is rectilinear.
622!-
623!---------------------------------------------------------------------
624  IMPLICIT NONE
625!-
626  INTEGER,INTENT(IN) :: pfileid, pim, pjm
627  REAL,INTENT(IN),DIMENSION(pim,pjm) :: plon, plat
628  CHARACTER(LEN=*),INTENT(IN) :: phname, phtitle
629  INTEGER,INTENT(OUT) :: phid
630  LOGICAL,INTENT(IN),OPTIONAL :: opt_rectilinear
631!-
632  CHARACTER(LEN=25) :: lon_name, lat_name
633  CHARACTER(LEN=80) :: tmp_title, tmp_name
634  INTEGER :: ndim
635  INTEGER,DIMENSION(2) :: dims(2)
636  INTEGER :: nlonid, nlatid
637  INTEGER :: orix, oriy, par_szx, par_szy
638  INTEGER :: iret, ncid
639  LOGICAL :: rectilinear
640!-
641  LOGICAL :: check = .FALSE.
642!---------------------------------------------------------------------
643!-
644! 1.0 Check that all fits in the buffers
645!-
646  IF (    (pim /= full_size(pfileid,1)) &
647    & .OR.(pjm /= full_size(pfileid,2)) ) THEN
648    CALL ipslerr (3,"histhori", &
649   &  'The new horizontal grid does not have the same size', &
650   &  'as the one provided to histbeg. This is not yet ', &
651   &  'possible in the hist package.')
652  ENDIF
653!-
654  IF (PRESENT(opt_rectilinear)) THEN
655    rectilinear = opt_rectilinear
656  ELSE
657    rectilinear = .FALSE.
658  ENDIF
659!-
660! 1.1 Create all the variables needed
661!-
662  IF (check) WRITE(*,*) "histhori_regular 1.0"
663!-
664  ncid = ncdf_ids(pfileid)
665!-
666  ndim = 2
667  dims(1:2) = (/ xid(pfileid), yid(pfileid) /)
668!-
669  tmp_name = phname
670  IF (rectilinear) THEN
671    IF (nb_hax(pfileid) == 0) THEN
672      lon_name = 'lon'
673      lat_name = 'lat'
674    ELSE
675      lon_name = 'lon_'//TRIM(tmp_name)
676      lat_name = 'lat_'//TRIM(tmp_name)
677    ENDIF
678  ELSE
679    IF (nb_hax(pfileid) == 0) THEN
680      lon_name = 'nav_lon'
681      lat_name = 'nav_lat'
682    ELSE
683      lon_name = 'nav_lon_'//TRIM(tmp_name)
684      lat_name = 'nav_lat_'//TRIM(tmp_name)
685    ENDIF
686  ENDIF
687!-
688! 1.2 Save the informations
689!-
690  phid =  nb_hax(pfileid)+1
691  nb_hax(pfileid) = phid
692!-
693  hax_name(pfileid,phid,1:2) = (/ lon_name, lat_name /)
694  tmp_title = phtitle
695!-
696! 2.0 Longitude
697!-
698  IF (check) WRITE(*,*) "histhori_regular 2.0"
699!-
700  IF (rectilinear) THEN
701    ndim = 1
702    dims(1:1) = (/ xid(pfileid) /)
703  ENDIF
704  iret = NF90_DEF_VAR (ncid,lon_name,NF90_FLOAT,dims(1:ndim),nlonid)
705  iret = NF90_PUT_ATT (ncid,nlonid,'units',"degrees_east")
706  iret = NF90_PUT_ATT (ncid,nlonid,'valid_min', &
707 &                     REAL(MINVAL(plon),KIND=4))
708  iret = NF90_PUT_ATT (ncid,nlonid,'valid_max', &
709 &                     REAL(MAXVAL(plon),KIND=4))
710  iret = NF90_PUT_ATT (ncid,nlonid,'long_name',"Longitude")
711  iret = NF90_PUT_ATT (ncid,nlonid,'nav_model',TRIM(tmp_title))
712!-
713! 3.0 Latitude
714!-
715  IF (check) WRITE(*,*) "histhori_regular 3.0"
716!-
717  IF (rectilinear) THEN
718    ndim = 1
719    dims(1:1) = (/ yid(pfileid) /)
720  ENDIF
721  iret = NF90_DEF_VAR (ncid,lat_name,NF90_FLOAT,dims(1:ndim),nlatid)
722  iret = NF90_PUT_ATT (ncid,nlatid,'units',"degrees_north")
723  iret = NF90_PUT_ATT (ncid,nlatid,'valid_min', &
724 &                     REAL(MINVAL(plat),KIND=4))
725  iret = NF90_PUT_ATT (ncid,nlatid,'valid_max', &
726 &                     REAL(MAXVAL(plat),KIND=4))
727  iret = NF90_PUT_ATT (ncid,nlatid,'long_name',"Latitude")
728  iret = NF90_PUT_ATT (ncid,nlatid,'nav_model',TRIM(tmp_title))
729!-
730  iret = NF90_ENDDEF (ncid)
731!-
732! 4.0 storing the geographical coordinates
733!-
734  IF (check) WRITE(*,*) "histhori_regular 4.0"
735!-
736  orix = slab_ori(pfileid,1)
737  oriy = slab_ori(pfileid,2)
738  par_szx = slab_sz(pfileid,1)
739  par_szy = slab_sz(pfileid,2)
740!-
741! Transfer the longitude
742!-
743  IF (rectilinear) THEN
744    iret = NF90_PUT_VAR (ncid,nlonid,plon(1:par_szx,1))
745  ELSE
746    iret = NF90_PUT_VAR (ncid,nlonid,plon, &
747 &           start=(/orix,oriy/),count=(/par_szx,par_szy/))
748  ENDIF
749!-
750! Transfer the latitude
751!-
752  IF ( rectilinear ) THEN
753    iret = NF90_PUT_VAR (ncid,nlatid,plat(1,1:par_szy))
754  ELSE
755    iret = NF90_PUT_VAR (ncid,nlatid,plat, &
756 &           start=(/orix,oriy/),count=(/par_szx,par_szy/))
757  ENDIF
758!-
759  iret = NF90_REDEF (ncid)
760!------------------------------
761END SUBROUTINE histhori_regular
762!===
763SUBROUTINE histhori_irregular &
764 &  (pfileid, pim, plon, plon_bounds, plat, plat_bounds, &
765 &   phname, phtitle, phid)
766!---------------------------------------------------------------------
767!- This subroutine is made to declare a new horizontale grid.
768!- It has to have the same number of points as
769!- the original and thus in this routine we will only
770!- add two variable (longitude and latitude).
771!- Any variable in the file can thus point to this pair
772!- through an attribute. This routine is very usefull
773!- to allow staggered grids.
774!-
775!- INPUT
776!-
777!- pfileid     : The id of the file to which the grid should be added
778!- pim         : Size in the longitude direction
779!- plon        : The longitudes
780!- plon_bounds : The boundaries of the grid in longitude
781!- plat        : The latitudes
782!- plat_bounds : Boundaries of the grid in latitude
783!- phname      : The name of grid
784!- phtitle     : The title of the grid
785!-
786!- OUTPUT
787!-
788!- phid    : Id of the created grid
789!---------------------------------------------------------------------
790  IMPLICIT NONE
791!-
792  INTEGER,INTENT(IN) :: pfileid, pim
793  REAL,DIMENSION(pim),INTENT(IN) :: plon, plat
794  REAL,DIMENSION(:,:),INTENT(IN) :: plon_bounds, plat_bounds
795  CHARACTER(LEN=*), INTENT(IN) :: phname, phtitle
796  INTEGER,INTENT(OUT) :: phid
797!-
798  CHARACTER(LEN=25) :: lon_name, lat_name
799  CHARACTER(LEN=30) :: lonbound_name, latbound_name
800  CHARACTER(LEN=80) :: tmp_title, tmp_name, longname
801  INTEGER :: ndim, dims(2)
802  INTEGER :: ndimb, dimsb(2)
803  INTEGER :: nbbounds
804  INTEGER :: nlonid, nlatid, nlonidb, nlatidb
805  INTEGER :: iret, ncid, twoid
806  LOGICAL :: transp = .FALSE.
807  REAL, ALLOCATABLE, DIMENSION(:,:) :: bounds_trans
808!-
809  LOGICAL :: check = .FALSE.
810!---------------------------------------------------------------------
811!-
812! 1.0 Check that all fits in the buffers
813!-
814  IF (    (pim /= full_size(pfileid,1)) &
815    & .OR.(full_size(pfileid,2) /= 1) ) THEN
816    CALL ipslerr (3,"histhori", &
817   &  'The new horizontal grid does not have the same size', &
818   &  'as the one provided to histbeg. This is not yet ', &
819   &  'possible in the hist package.')
820  ENDIF
821!-
822! 1.1 Create all the variables needed
823!-
824  IF (check) WRITE(*,*) 'histhori_irregular 1.0'
825!-
826  ncid = ncdf_ids(pfileid)
827!-
828  IF ( SIZE(plon_bounds, DIM=1) == pim ) THEN
829    nbbounds = SIZE(plon_bounds, DIM=2)
830    transp = .TRUE.
831  ELSEIF ( SIZE(plon_bounds, DIM=2) == pim ) THEN
832    nbbounds = SIZE(plon_bounds, DIM=1)
833    transp = .FALSE.
834  ELSE
835    CALL ipslerr (3,"histhori", &
836   &  'The boundary variable does not have any axis corresponding', &
837   &  'to the size of the longitude or latitude variable', &
838   &  '.')
839  ENDIF
840!-
841  IF (.NOT.ALLOCATED(bounds_trans)) THEN
842    ALLOCATE(bounds_trans(nbbounds,pim))
843  ENDIF
844!-
845  iret = NF90_DEF_DIM (ncid, 'nbnd', nbbounds, twoid)
846  ndim = 1
847  dims(1) = xid(pfileid)
848  ndimb = 2
849  dimsb(1:2) = (/ twoid, xid(pfileid) /)
850!-
851  tmp_name = phname
852  IF (nb_hax(pfileid) == 0) THEN
853    lon_name = 'nav_lon'
854    lat_name = 'nav_lat'
855  ELSE
856    lon_name = 'nav_lon_'//TRIM(tmp_name)
857    lat_name = 'nav_lat_'//TRIM(tmp_name)
858  ENDIF
859  lonbound_name = TRIM(lon_name)//'_bounds'
860  latbound_name = TRIM(lat_name)//'_bounds'
861!-
862! 1.2 Save the informations
863!-
864  phid =  nb_hax(pfileid)+1
865  nb_hax(pfileid) = phid
866!-
867  hax_name(pfileid,phid,1:2) = (/ lon_name, lat_name /)
868  tmp_title = phtitle
869!-
870! 2.0 Longitude
871!-
872  IF (check) WRITE(*,*) "histhori_irregular 2.0"
873!-
874  iret = NF90_DEF_VAR (ncid,lon_name,NF90_FLOAT,dims(1:ndim),nlonid)
875  iret = NF90_PUT_ATT (ncid,nlonid,'units',"degrees_east")
876  iret = NF90_PUT_ATT (ncid,nlonid,'valid_min', &
877 &                     REAL(MINVAL(plon),KIND=4))
878  iret = NF90_PUT_ATT (ncid,nlonid,'valid_max', &
879 &                     REAL(MAXVAL(plon),KIND=4))
880  iret = NF90_PUT_ATT (ncid,nlonid,'long_name',"Longitude")
881  iret = NF90_PUT_ATT (ncid,nlonid,'nav_model',TRIM(tmp_title))
882!-
883! 2.1 Longitude bounds
884!-
885  iret = NF90_PUT_ATT (ncid,nlonid,'bounds',TRIM(lonbound_name))
886  iret = NF90_DEF_VAR (ncid,lonbound_name,NF90_FLOAT, &
887 &                     dimsb(1:ndimb),nlonidb)
888  longname = 'Boundaries for coordinate variable '//TRIM(lon_name)
889  iret = NF90_PUT_ATT (ncid,nlonidb,'long_name',TRIM(longname))
890!-
891! 3.0 Latitude
892!-
893  IF (check) WRITE(*,*) "histhori_irregular 3.0"
894!-
895  iret = NF90_DEF_VAR (ncid,lat_name,NF90_FLOAT,dims(1:ndim),nlatid)
896  iret = NF90_PUT_ATT (ncid,nlatid,'units',"degrees_north")
897  iret = NF90_PUT_ATT (ncid,nlatid,'valid_min', &
898 &                     REAL(MINVAL(plat),KIND=4))
899  iret = NF90_PUT_ATT (ncid,nlatid,'valid_max', &
900 &                     REAL(MAXVAL(plat),KIND=4))
901  iret = NF90_PUT_ATT (ncid,nlatid,'long_name',"Latitude")
902  iret = NF90_PUT_ATT (ncid,nlatid,'nav_model',TRIM(tmp_title))
903!-
904! 3.1 Latitude bounds
905!-
906  iret = NF90_PUT_ATT (ncid,nlatid,'bounds',TRIM(latbound_name))
907  iret = NF90_DEF_VAR (ncid,latbound_name,NF90_FLOAT, &
908 &                     dimsb(1:ndimb),nlatidb)
909  longname = 'Boundaries for coordinate variable '//TRIM(lat_name)
910  iret = NF90_PUT_ATT (ncid,nlatidb,'long_name',TRIM(longname))
911!-
912  iret = NF90_ENDDEF (ncid)
913!-
914! 4.0 storing the geographical coordinates
915!-
916  IF (check) WRITE(*,*) "histhori_irregular 4.0"
917!-
918! 4.1 Write the longitude
919!-
920  iret = NF90_PUT_VAR (ncid, nlonid, plon(1:pim))
921!-
922! 4.2 Write the longitude bounds
923!-
924  IF (transp) THEN
925    bounds_trans = TRANSPOSE(plon_bounds)
926  ELSE
927    bounds_trans = plon_bounds
928  ENDIF
929  iret = NF90_PUT_VAR (ncid, nlonidb, bounds_trans(1:nbbounds,1:pim))
930!-
931! 4.3 Write the latitude
932!-
933  iret = NF90_PUT_VAR (ncid, nlatid, plat(1:pim))
934!-
935! 4.4 Write the latitude bounds
936!-
937  IF (transp) THEN
938    bounds_trans = TRANSPOSE(plat_bounds)
939  ELSE
940    bounds_trans = plat_bounds
941  ENDIF
942  iret = NF90_PUT_VAR (ncid,nlatidb,bounds_trans(1:nbbounds,1:pim))
943!-
944  iret = NF90_REDEF (ncid)
945!--------------------------------
946END SUBROUTINE histhori_irregular
947!===
948SUBROUTINE histvert (pfileid, pzaxname, pzaxtitle, &
949 &                   pzaxunit, pzsize, pzvalues, pzaxid, pdirect)
950!---------------------------------------------------------------------
951!- This subroutine defines a vertical axis and returns it s id.
952!- It gives the user the possibility to the user to define many
953!- different vertical axes. For each variable defined with histdef a
954!- vertical axis can be specified with by it s ID.
955!-
956!- INPUT
957!-
958!- pfileid  : ID of the file the variable should be archived in
959!- pzaxname : Name of the vertical axis
960!- pzaxtitle: title of the vertical axis
961!- pzaxunit : Units of the vertical axis
962!- pzsize   : size of the vertical axis
963!- pzvalues : Coordinate values of the vetical axis
964!-
965!- pdirect  : is an optional argument which allows to specify the
966!-            the positive direction of the axis : up or down.
967!- OUTPUT
968!-
969!- pzaxid   : Returns the ID of the axis.
970!-            Note that this is not the netCDF ID !
971!-
972!- VERSION
973!-
974!---------------------------------------------------------------------
975  IMPLICIT NONE
976!-
977  INTEGER,INTENT(IN) :: pfileid,pzsize
978  CHARACTER(LEN=*),INTENT(IN) :: pzaxname,pzaxunit,pzaxtitle
979  REAL,INTENT(IN) :: pzvalues(pzsize)
980  INTEGER, INTENT(OUT) :: pzaxid
981  CHARACTER(LEN=*),INTENT(IN), OPTIONAL :: pdirect
982!-
983  INTEGER :: pos, iv, nb, zdimid, zaxid_tmp
984  CHARACTER(LEN=20) :: str20, tab_str20(nb_zax_max)
985  INTEGER tab_str20_length(nb_zax_max)
986  CHARACTER(LEN=70) :: str70, str71, str72
987  CHARACTER(LEN=80) :: str80
988  CHARACTER(LEN=20) :: direction
989  INTEGER :: iret, leng, ncid
990  LOGICAL :: check = .FALSE.
991!---------------------------------------------------------------------
992!-
993! 1.0 Verifications :
994!    Do we have enough space for an extra axis ?
995!    Is the name already in use ?
996!-
997  IF (check) WRITE(*,*) "histvert : 1.0 Verifications", &
998 &                      pzaxname,'---',pzaxunit,'---',pzaxtitle
999!-
1000! - Direction of axis. Can we get if from the user.
1001!   If not we put unknown.
1002!-
1003  IF (PRESENT(pdirect)) THEN
1004    direction = TRIM(pdirect)
1005    CALL strlowercase (direction)
1006  ELSE
1007    direction = 'unknown'
1008  ENDIF
1009!-
1010! Check the consistency of the attribute
1011!-
1012  IF (     (direction /= 'unknown') &
1013 &    .AND.(direction /= 'up')      &
1014 &    .AND.(direction /= 'down')   ) THEN
1015    direction = 'unknown'
1016    str80 = 'The specified axis was : '//TRIM(direction)
1017    CALL ipslerr (2,"histvert",&
1018   & "The specified direction for the vertical axis is not possible.",&
1019   & "it is replaced by : unknown", str80)
1020  ENDIF
1021!-
1022  IF ( nb_zax(pfileid)+1 > nb_zax_max) THEN
1023    CALL ipslerr (3,"histvert", &
1024   &  'Table of vertical axes too small. You should increase ',&
1025   &  'nb_zax_max in M_HISTCOM.f90 in order to accomodate all ', &
1026   &  'these variables ')
1027  ENDIF
1028!-
1029  iv = nb_zax(pfileid)
1030  IF ( iv > 1) THEN
1031    str20 = pzaxname
1032    nb = iv-1
1033    tab_str20(1:nb) = zax_name(pfileid,1:nb)
1034    tab_str20_length(1:nb) = zax_name_length(pfileid,1:nb)
1035    CALL find_str(nb, tab_str20, tab_str20_length, str20, pos)
1036  ELSE
1037    pos = 0
1038  ENDIF
1039!-
1040  IF ( pos > 0) THEN
1041    str70 = "Vertical axis already exists"
1042    WRITE(str71,'("Check variable ",a," in file",I3)') str20,pfileid
1043    str72 = "Can also be a wrong file ID in another declaration"
1044    CALL ipslerr (3,"histvert", str70, str71, str72)
1045  ENDIF
1046!-
1047  iv = nb_zax(pfileid)+1
1048!-
1049! 2.0 Add the information to the file
1050!-
1051  IF (check) &
1052 &  WRITE(*,*) "histvert : 2.0 Add the information to the file"
1053!-
1054  ncid = ncdf_ids(pfileid)
1055!-
1056  leng = MIN(LEN_TRIM(pzaxname),20)
1057  iret = NF90_DEF_DIM (ncid,pzaxname(1:leng),pzsize,zaxid_tmp)
1058  iret = NF90_DEF_VAR (ncid,pzaxname(1:leng),NF90_FLOAT, &
1059 &                     zaxid_tmp,zdimid)
1060!-
1061  leng = MIN(LEN_TRIM(pzaxunit),20)
1062  iret = NF90_PUT_ATT (ncid, zdimid, 'units', pzaxunit(1:leng))
1063  iret = NF90_PUT_ATT (ncid, zdimid, 'positive', TRIM(direction))
1064!-
1065  iret = NF90_PUT_ATT (ncid,zdimid,'valid_min', &
1066 &                     REAL(MINVAL(pzvalues(1:pzsize)),KIND=4))
1067  iret = NF90_PUT_ATT (ncid,zdimid,'valid_max', &
1068 &                     REAL(MAXVAL(pzvalues(1:pzsize)),KIND=4))
1069!-
1070  leng = MIN(LEN_TRIM(pzaxname),20)
1071  iret = NF90_PUT_ATT (ncid, zdimid, 'title', pzaxname(1:leng))
1072  leng = MIN(LEN_TRIM(pzaxtitle),80)
1073  iret = NF90_PUT_ATT (ncid, zdimid, 'long_name', pzaxtitle(1:leng))
1074!-
1075  iret = NF90_ENDDEF (ncid)
1076!-
1077  iret = NF90_PUT_VAR (ncid, zdimid, pzvalues(1:pzsize))
1078!-
1079  iret = NF90_REDEF (ncid)
1080!-
1081!- 3.0 add the information to the common
1082!-
1083  IF ( check) &
1084  &  WRITE(*,*) "histvert : 3.0 add the information to the common"
1085!-
1086  nb_zax(pfileid) = iv
1087  zax_size(pfileid, iv) = pzsize
1088  zax_name(pfileid, iv) = pzaxname
1089  zax_name_length(pfileid, iv) = LEN_TRIM(pzaxname)
1090  zax_ids(pfileid, iv) = zaxid_tmp
1091  pzaxid =  iv
1092!----------------------
1093END SUBROUTINE histvert
1094!===
1095SUBROUTINE histdef (pfileid, pvarname, ptitle, punit, &
1096 &                  pxsize, pysize, phoriid, pzsize,  &
1097 &                  par_oriz, par_szz, pzid,          &
1098 &                  pnbbyt, popp, pfreq_opp, pfreq_wrt)
1099!---------------------------------------------------------------------
1100!- With this subroutine each variable to be archived on the history
1101!- tape should be declared.
1102!-
1103!- It gives the user the choise of operation
1104!- to be performed on the variables, the frequency of this operation
1105!- and finaly the frequency of the archiving.
1106!-
1107!- INPUT
1108!-
1109!- pfileid  : ID of the file the variable should be archived in
1110!- pvarname : Name of the variable, short and easy to remember
1111!- ptitle   : Full name of the variable
1112!- punit    : Units of the variable
1113!-
1114!- The next 3 arguments give the size of that data
1115!- that will be passed to histwrite. The zoom will be
1116!- done there with the horizontal information obtained
1117!- in histbeg and the vertical information to follow.
1118!-
1119!- pxsize   : Size in X direction (size of the data that will be
1120!-            given to histwrite)
1121!- pysize   : Size in Y direction
1122!- phoriid  : ID of the horizontal axis
1123!-
1124!- The next two arguments give the vertical zoom to use.
1125!-
1126!- pzsize   : Size in Z direction (If 1 then no axis is declared
1127!-            for this variable and pzid is not used)
1128!- par_oriz : Off set of the zoom
1129!- par_szz  : Size of the zoom
1130!-
1131!- pzid     : ID of the vertical axis to use. It has to have
1132!-            the size of the zoom.
1133!- pnbbyt   : Number of bytes on which to store in netCDF (Not opp.)
1134!- popp     : Operation to be performed. The following options
1135!-            exist today :
1136!- inst : keeps instantaneous values for writting
1137!- ave  : Computes the average from call between writes
1138!- pfreq_opp: Frequency of this operation (in seconds)
1139!- pfreq_wrt: Frequency at which the variable should be
1140!-            written (in seconds)
1141!-
1142!- VERSION
1143!---------------------------------------------------------------------
1144  IMPLICIT NONE
1145!-
1146  INTEGER,INTENT(IN) :: pfileid, pxsize, pysize, pzsize, pzid
1147  INTEGER,INTENT(IN) :: par_oriz, par_szz, pnbbyt, phoriid
1148  CHARACTER(LEN=*),INTENT(IN) :: pvarname, punit, popp
1149  CHARACTER(LEN=*),INTENT(IN) :: ptitle
1150  REAL,INTENT(IN) :: pfreq_opp, pfreq_wrt
1151!-
1152  INTEGER :: iv, i, nb
1153  CHARACTER(LEN=70) :: str70, str71, str72
1154  CHARACTER(LEN=20) :: tmp_name
1155  CHARACTER(LEN=20) :: str20, tab_str20(nb_var_max)
1156  INTEGER :: tab_str20_length(nb_var_max)
1157  CHARACTER(LEN=40) :: str40, tab_str40(nb_var_max)
1158  INTEGER :: tab_str40_length(nb_var_max)
1159  CHARACTER(LEN=10) :: str10
1160  CHARACTER(LEN=80) :: tmp_str80
1161  CHARACTER(LEN=7) :: tmp_topp, tmp_sopp(nbopp_max)
1162  CHARACTER(LEN=120) :: ex_topps
1163  REAL :: tmp_scal(nbopp_max), un_an, un_jour, test_fopp, test_fwrt
1164  INTEGER :: pos, buff_sz
1165!-
1166  LOGICAL :: check = .FALSE.
1167!---------------------------------------------------------------------
1168  ex_topps = 'ave, inst, t_min, t_max, t_sum, once, never, l_max, l_min'
1169!-
1170  nb_var(pfileid) = nb_var(pfileid)+1
1171  iv = nb_var(pfileid)
1172!-
1173  IF ( iv > nb_var_max) THEN
1174    CALL ipslerr (3,"histdef", &
1175   &  'Table of variables too small. You should increase nb_var_max',&
1176   &  'in M_HISTCOM.f90 in order to accomodate all these variables', &
1177   &  ' ')
1178  ENDIF
1179!-
1180! 1.0 Transfer informations on the variable to the common
1181!     and verify that it does not already exist
1182!-
1183  IF (check) WRITE(*,*) "histdef : 1.0"
1184!-
1185  IF (iv > 1) THEN
1186    str20 = pvarname
1187    nb = iv-1
1188    tab_str20(1:nb) = name(pfileid,1:nb)
1189    tab_str20_length(1:nb) = name_length(pfileid,1:nb)
1190    CALL find_str (nb, tab_str20, tab_str20_length, str20, pos)
1191  ELSE
1192    pos = 0
1193  ENDIF
1194!-
1195  IF (pos > 0) THEN
1196    str70 = "Variable already exists"
1197    WRITE(str71,'("Check variable  ",a," in file",I3)') str20,pfileid
1198    str72 = "Can also be a wrong file ID in another declaration"
1199    CALL ipslerr (3,"histdef", str70, str71, str72)
1200  ENDIF
1201!-
1202  name(pfileid,iv) = pvarname
1203  name_length(pfileid,iv) = LEN_TRIM(name(pfileid,iv))
1204  title(pfileid,iv) = ptitle
1205  unit_name(pfileid,iv) = punit
1206  tmp_name =  name(pfileid,iv)
1207!-
1208! 1.1 decode the operations
1209!-
1210  fullop(pfileid,iv) = popp
1211  tmp_str80 = popp
1212  CALL buildop &
1213 &  (tmp_str80, ex_topps, tmp_topp, nbopp_max, missing_val, &
1214 &   tmp_sopp, tmp_scal, nbopp(pfileid,iv))
1215!-
1216  topp(pfileid,iv) = tmp_topp
1217  DO i=1,nbopp(pfileid,iv)
1218    sopps(pfileid,iv,i) = tmp_sopp(i)
1219    scal(pfileid,iv,i) = tmp_scal(i)
1220  ENDDO
1221!-
1222! 1.2 If we have an even number of operations
1223!     then we need to add identity
1224!-
1225  IF (2*INT(nbopp(pfileid,iv)/2.0) == nbopp(pfileid,iv)) THEN
1226    nbopp(pfileid,iv) = nbopp(pfileid,iv)+1
1227    sopps(pfileid,iv,nbopp(pfileid,iv)) = 'ident'
1228    scal(pfileid,iv,nbopp(pfileid,iv)) = missing_val
1229  ENDIF
1230!-
1231! 2.0 Put the size of the variable in the common and check
1232!-
1233  IF (check) &
1234 &  WRITE(*,*) "histdef : 2.0", pfileid,iv,nbopp(pfileid,iv), &
1235 &    sopps(pfileid,iv,1:nbopp(pfileid,iv)), &
1236 &    scal(pfileid,iv,1:nbopp(pfileid,iv))
1237!-
1238  scsize(pfileid,iv,1:3) = (/ pxsize, pysize, pzsize /)
1239!-
1240  zorig(pfileid,iv,1:3) = &
1241 &  (/ slab_ori(pfileid,1), slab_ori(pfileid,2), par_oriz /)
1242!-
1243  zsize(pfileid,iv,1:3) = &
1244 &  (/ slab_sz(pfileid,1), slab_sz(pfileid,2), par_szz /)
1245!-
1246! Is the size of the full array the same as that of the coordinates  ?
1247!-
1248  IF (    (pxsize > full_size(pfileid,1)) &
1249 &    .OR.(pysize > full_size(pfileid,2)) ) THEN
1250!-
1251    str70 = "The size of the variable is different "// &
1252 &          "from the one of the coordinates"
1253    WRITE(str71,'("Size of coordinates :", 2I4)') &
1254 &   full_size(pfileid,1), full_size(pfileid,2)
1255    WRITE(str72,'("Size declared for variable ",a," :",2I4)') &
1256 &   TRIM(tmp_name), pxsize, pysize
1257    CALL ipslerr (3,"histdef", str70, str71, str72)
1258  ENDIF
1259!-
1260! Is the size of the zoom smaler than the coordinates ?
1261!-
1262  IF (    (full_size(pfileid,1) < slab_sz(pfileid,1)) &
1263 &    .OR.(full_size(pfileid,2) < slab_sz(pfileid,2)) ) THEN
1264    str70 = &
1265 &   "Size of variable should be greater or equal to those of the zoom"
1266    WRITE(str71,'("Size of XY zoom :", 2I4)') &
1267 &   slab_sz(pfileid,1),slab_sz(pfileid,1)
1268    WRITE(str72,'("Size declared for variable ",a," :",2I4)') &
1269 &   TRIM(tmp_name), pxsize, pysize
1270    CALL ipslerr (3,"histdef", str70, str71, str72)
1271  ENDIF
1272!-
1273! 2.1 We store the horizontal grid information with minimal
1274!     and a fall back onto the default grid
1275!-
1276  IF ( phoriid > 0 .AND. phoriid <= nb_hax(pfileid)) THEN
1277    var_haxid(pfileid,iv) = phoriid
1278  ELSE
1279    var_haxid(pfileid,iv) = 1
1280    CALL ipslerr (2,"histdef", &
1281   &  'We use the default grid for variable as an invalide',&
1282   &  'ID was provided for variable : ', pvarname)
1283  ENDIF
1284!-
1285! 2.2 Check the vertical coordinates if needed
1286!-
1287  IF (par_szz > 1) THEN
1288!-
1289!-- Does the vertical coordinate exist ?
1290!-
1291    IF ( pzid > nb_zax(pfileid)) THEN
1292      WRITE(str70, &
1293 &    '("The vertical coordinate chosen for variable ",a)') &
1294 &     TRIM(tmp_name)
1295      str71 = " Does not exist."
1296      CALL ipslerr (3,"histdef",str70,str71, " ")
1297    ENDIF
1298!-
1299!-- Is the vertical size of the variable equal to that of the axis ?
1300!-
1301    IF (par_szz /= zax_size(pfileid,pzid)) THEN
1302      str20 = zax_name(pfileid,pzid)
1303      str70 = "The size of the zoom does not correspond "// &
1304 &            "to the size of the chosen vertical axis"
1305      WRITE(str71,'("Size of zoom in z :", I4)') par_szz
1306      WRITE(str72,'("Size declared for axis ",a," :",I4)') &
1307 &     TRIM(str20), zax_size(pfileid,pzid)
1308      CALL ipslerr (3,"histdef", str70, str71, str72)
1309    ENDIF
1310!-
1311!-- Is the zoom smaler that the total size of the variable ?
1312!-
1313    IF ( pzsize < par_szz ) THEN
1314      str20 = zax_name(pfileid,pzid)
1315      str70 = "The vertical size of variable "// &
1316 &            "is smaller than that of the zoom."
1317      WRITE(str71,'("Declared vertical size of data :", I5)') pzsize
1318      WRITE(str72,'("Size of zoom for variable ",a," = ",I5)') &
1319 &     TRIM(tmp_name),par_szz
1320      CALL ipslerr (3,"histdef", str70, str71, str72)
1321    ENDIF
1322    var_zaxid(pfileid,iv) = pzid
1323  ELSE
1324    var_zaxid(pfileid,iv) = -99
1325  ENDIF
1326!-
1327! 3.0 Determine the position of the variable in the buffer
1328!     If it is instantaneous output then we do not use the buffer
1329!-
1330  IF (check) WRITE(*,*) "histdef : 3.0"
1331!-
1332! 3.1 We get the size of the arrays histwrite will get and check
1333!     that they fit into the tmp_buffer
1334!-
1335  buff_sz = zsize(pfileid,iv,1)*zsize(pfileid,iv,2)*zsize(pfileid,iv,3)
1336!-
1337! 3.2 move the pointer of the buffer array for operation
1338!     which need bufferisation
1339!-
1340  IF (     (TRIM(tmp_topp) /= "inst") &
1341 &    .AND.(TRIM(tmp_topp) /= "once") &
1342 &    .AND.(TRIM(tmp_topp) /= "never") )THEN
1343    point(pfileid,iv) = buff_pos+1
1344    buff_pos = buff_pos+buff_sz
1345    IF (check) THEN
1346      WRITE(*,*) "histdef : 3.2 bufpos for iv = ",iv, &
1347 &               " pfileid = ",pfileid," is = ",point(pfileid,iv)
1348    ENDIF
1349  ENDIF
1350!-
1351! 4.0 Transfer the frequency of the operations and check
1352!     for validity. We have to pay attention to negative values
1353!     of the frequency which indicate monthly time-steps.
1354!     The strategy is to bring it back to seconds for the tests
1355!-
1356  IF (check) WRITE(*,*) "histdef : 4.0"
1357!-
1358  freq_opp(pfileid,iv) = pfreq_opp
1359  freq_wrt(pfileid,iv) = pfreq_wrt
1360!-
1361  CALL ioget_calendar(un_an, un_jour)
1362  IF ( pfreq_opp < 0) THEN
1363    CALL ioget_calendar(un_an)
1364    test_fopp = pfreq_opp*(-1.)*un_an/12.*un_jour
1365  ELSE
1366    test_fopp = pfreq_opp
1367  ENDIF
1368  IF ( pfreq_wrt < 0) THEN
1369    CALL ioget_calendar(un_an)
1370    test_fwrt = pfreq_wrt*(-1.)*un_an/12.*un_jour
1371  ELSE
1372    test_fwrt = pfreq_wrt
1373  ENDIF
1374!-
1375! 4.1 Frequency of operations and output should be larger than deltat !
1376!-
1377  IF (test_fopp < deltat(pfileid)) THEN
1378    str70 = 'Frequency of operations should be larger than deltat'
1379    WRITE(str71,'("It is not the case for variable ",a," :",F10.4)') &
1380 &   TRIM(tmp_name),pfreq_opp
1381    str72 = "PATCH : frequency set to deltat"
1382!-
1383    CALL ipslerr (2,"histdef", str70, str71, str72)
1384!-
1385    freq_opp(pfileid,iv) = deltat(pfileid)
1386  ENDIF
1387!-
1388  IF (test_fwrt < deltat(pfileid)) THEN
1389    str70 = 'Frequency of output should be larger than deltat'
1390    WRITE(str71,'("It is not the case for variable ",a," :",F10.4)') &
1391 &   TRIM(tmp_name),pfreq_wrt
1392    str72 = "PATCH : frequency set to deltat"
1393!-
1394    CALL ipslerr (2,"histdef", str70, str71, str72)
1395!-
1396    freq_wrt(pfileid,iv) = deltat(pfileid)
1397  ENDIF
1398!-
1399! 4.2 First the existence of the operation is tested and then
1400!     its compaticility with the choice of frequencies
1401!-
1402  IF (TRIM(tmp_topp) == "inst") THEN
1403    IF (test_fopp /= test_fwrt) THEN
1404      str70 = 'For instantaneous output the frequency '// &
1405 &            'of operations and output'
1406      WRITE(str71, &
1407 &     '("should be the same, this was not case for variable ",a)') &
1408 &      TRIM(tmp_name)
1409      str72 = "PATCH : The smalest frequency of both is used"
1410      CALL ipslerr (2,"histdef", str70, str71, str72)
1411      IF ( test_fopp < test_fwrt) THEN
1412        freq_opp(pfileid,iv) = pfreq_opp
1413        freq_wrt(pfileid,iv) = pfreq_opp
1414      ELSE
1415        freq_opp(pfileid,iv) = pfreq_wrt
1416        freq_wrt(pfileid,iv) = pfreq_wrt
1417      ENDIF
1418    ENDIF
1419  ELSE IF (INDEX(ex_topps,TRIM(tmp_topp)) > 0) THEN
1420    IF (test_fopp > test_fwrt) THEN
1421      str70 = 'For averages the frequency of operations '// &
1422&             'should be smaller or equal'
1423      WRITE(str71, &
1424 &     '("to that of output. It is not the case for variable ",a)') &
1425 &     TRIM(tmp_name)
1426      str72 = 'PATCH : The output frequency is used for both'
1427      CALL ipslerr (2,"histdef", str70, str71, str72)
1428      freq_opp(pfileid,iv) = pfreq_wrt
1429    ENDIF
1430  ELSE
1431    WRITE (str70,'("Operation on variable ",a," is unknown")') &
1432&    TRIM(tmp_name)
1433    WRITE (str71, '("operation requested is :",a)') tmp_topp
1434    WRITE (str72, '("File ID :",I3)') pfileid
1435    CALL ipslerr (3,"histdef", str70, str71, str72)
1436  ENDIF
1437!-
1438! 5.0 Initialize other variables of the common
1439!-
1440  IF (check) WRITE(*,*) "histdef : 5.0"
1441!-
1442  minmax(pfileid,iv,1) =  ABS(missing_val)
1443  minmax(pfileid,iv,2) = -ABS(missing_val)
1444!-
1445  last_opp(pfileid,iv) = itau0(pfileid)       ! - freq_opp(pfileid,iv)/2./deltat(pfileid)
1446  last_wrt(pfileid,iv) = itau0(pfileid)       ! - freq_wrt(pfileid,iv)/2./deltat(pfileid)
1447  last_opp_chk(pfileid,iv) = itau0(pfileid)   ! - freq_opp(pfileid,iv)/2./deltat(pfileid)
1448  last_wrt_chk(pfileid,iv) = itau0(pfileid)   ! - freq_wrt(pfileid,iv)/2./deltat(pfileid)
1449  nb_opp(pfileid,iv) = 0
1450  nb_wrt(pfileid,iv) = 0
1451!-
1452! 6.0 Get the time axis for this variable
1453!-
1454  IF (check) WRITE(*,*) "histdef : 6.0"
1455!-
1456  IF ( freq_wrt(pfileid,iv) > 0 ) THEN
1457    WRITE(str10,'(I8.8)') INT(freq_wrt(pfileid,iv))
1458    str40 = TRIM(tmp_topp)//"_"//TRIM(str10)
1459  ELSE
1460    WRITE(str10,'(I2.2,"month")') ABS(INT(freq_wrt(pfileid,iv)))
1461    str40 = TRIM(tmp_topp)//"_"//TRIM(str10)
1462  ENDIF
1463!-
1464  DO i=1,nb_tax(pfileid)
1465    tab_str40(i) = tax_name(pfileid,i)
1466    tab_str40_length(i) = tax_name_length(pfileid,i)
1467  ENDDO
1468!-
1469  CALL find_str (nb_tax(pfileid),tab_str40,tab_str40_length,str40,pos)
1470!-
1471! No time axis for once, l_max, l_min or never operation
1472!-
1473  IF (     (TRIM(tmp_topp) /= 'once')  &
1474 &    .AND.(TRIM(tmp_topp) /= 'never') &
1475 &    .AND.(TRIM(tmp_topp) /= 'l_max') &
1476 &    .AND.(TRIM(tmp_topp) /= 'l_min') ) THEN
1477    IF ( pos < 0) THEN
1478      nb_tax(pfileid) = nb_tax(pfileid)+1
1479      tax_name(pfileid,nb_tax(pfileid)) = str40
1480      tax_name_length(pfileid, nb_tax(pfileid)) = LEN_TRIM(str40)
1481      tax_last(pfileid,nb_tax(pfileid)) = 0
1482      var_axid(pfileid,iv) = nb_tax(pfileid)
1483    ELSE
1484      var_axid(pfileid,iv) = pos
1485    ENDIF
1486  ELSE
1487    IF (check)   WRITE(*,*) "histdef : 7.0 ",TRIM(tmp_topp),'----'
1488    var_axid(pfileid,iv) = -99
1489  ENDIF
1490!-
1491! 7.0 prepare frequence of writing and operation
1492!     for never or once operation
1493!-
1494  IF (    (TRIM(tmp_topp) == 'once')  &
1495 &    .OR.(TRIM(tmp_topp) == 'never') ) THEN
1496    freq_opp(pfileid,iv) = 0.
1497    freq_wrt(pfileid,iv) = 0.
1498  ENDIF
1499!---------------------
1500END SUBROUTINE histdef
1501!===
1502SUBROUTINE histend (pfileid)
1503!---------------------------------------------------------------------
1504!- This subroutine end the decalaration of variables and sets the
1505!- time axes in the netcdf file and puts it into the write mode.
1506!-
1507!- INPUT
1508!-
1509!- pfileid : ID of the file to be worked on
1510!-
1511!- VERSION
1512!-
1513!---------------------------------------------------------------------
1514  IMPLICIT NONE
1515!-
1516  INTEGER, INTENT(IN) :: pfileid
1517!-
1518  INTEGER :: ncid, ncvarid
1519  INTEGER :: iret, ndim, iv, itx, ziv
1520  INTEGER :: itax
1521  INTEGER :: dims(4), dim_cnt
1522  INTEGER :: year, month, day, hours, minutes
1523  REAL :: sec
1524  REAL :: rtime0
1525  CHARACTER(LEN=20) :: tname, tunit
1526  CHARACTER(LEN=30) :: str30
1527  CHARACTER(LEN=80) :: ttitle
1528  CHARACTER(LEN=120) :: assoc
1529  CHARACTER(LEN=70) :: str70
1530  CHARACTER(LEN=3),DIMENSION(12) :: cal =   &
1531 &  (/ 'JAN','FEB','MAR','APR','MAY','JUN', &
1532 &     'JUL','AUG','SEP','OCT','NOV','DEC' /)
1533  CHARACTER(LEN=7) :: tmp_opp
1534!-
1535  LOGICAL :: check = .FALSE.
1536!---------------------------------------------------------------------
1537  ncid = ncdf_ids(pfileid)
1538!-
1539! 1.0 Create the time axes
1540!-
1541  IF (check) WRITE(*,*) "histend : 1.0"
1542!---
1543  iret = NF90_DEF_DIM (ncid,'time_counter',NF90_UNLIMITED,tid(pfileid))
1544!-
1545! 1.1 Define all the time axes needed for this file
1546!-
1547  DO itx=1,nb_tax(pfileid)
1548    dims(1) = tid(pfileid)
1549    IF (nb_tax(pfileid) > 1) THEN
1550      str30 = "t_"//tax_name(pfileid,itx)
1551    ELSE
1552      str30 = "time_counter"
1553    ENDIF
1554    iret = NF90_DEF_VAR (ncid,str30,NF90_FLOAT, &
1555 &                       dims(1),tdimid(pfileid,itx))
1556!---
1557!   To transform the current itau into a real date and take it
1558!   as the origin of the file requires the time counter to change.
1559!   Thus it is an operation the user has to ask for.
1560!   This function should thus only be re-instated
1561!   if there is a ioconf routine to control it.
1562!---
1563!-- rtime0 = itau2date(itau0(pfileid), date0(pfileid), deltat(pfileid))
1564    rtime0 = date0(pfileid)
1565!-
1566    CALL ju2ymds(rtime0, year, month, day, sec)
1567!---
1568!   Catch any error induced by a change in calendar !
1569!---
1570    IF (year < 0) THEN
1571      year = 2000+year
1572    ENDIF
1573!-
1574    hours = INT(sec/(60.*60.))
1575    minutes = INT((sec-hours*60.*60.)/60.)
1576    sec = sec-(hours*60.*60.+minutes*60.)
1577!-
1578    WRITE(str70,7000) year, month, day, hours, minutes, INT(sec)
1579    iret = NF90_PUT_ATT (ncid,tdimid(pfileid,itx),'units',TRIM(str70))
1580!-
1581    CALL ioget_calendar (str30)
1582    iret = NF90_PUT_ATT (ncid,tdimid(pfileid,itx), &
1583 &                       'calendar',TRIM(str30))
1584!-
1585    iret = NF90_PUT_ATT (ncid,tdimid(pfileid,itx),'title','Time')
1586!-
1587    iret = NF90_PUT_ATT (ncid,tdimid(pfileid,itx), &
1588 &                       'long_name','Time axis')
1589!-
1590    WRITE(str70,7001) year, cal(month), day, hours, minutes, INT(sec)
1591    iret = NF90_PUT_ATT (ncid,tdimid(pfileid,itx), &
1592 &                       'time_origin',TRIM(str70))
1593  ENDDO
1594!-
1595! The formats we need
1596!-
15977000 FORMAT('seconds since ', I4.4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
15987001 FORMAT(' ', I4.4,'-',A3,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
1599!-
1600! 2.0 declare the variables
1601!-
1602  IF (check) WRITE(*,*) "histend : 2.0"
1603!-
1604  DO iv=1,nb_var(pfileid)
1605!---
1606    itax = var_axid(pfileid,iv)
1607!---
1608    tname = name(pfileid,iv)
1609    tunit = unit_name(pfileid,iv)
1610    ttitle = title(pfileid,iv)
1611!---
1612    IF ( regular(pfileid) ) THEN
1613      dims(1:2) = (/ xid(pfileid), yid(pfileid) /)
1614      dim_cnt = 2
1615    ELSE
1616      dims(1) = xid(pfileid)
1617      dim_cnt = 1
1618    ENDIF
1619!---
1620    tmp_opp = topp(pfileid,iv)
1621    ziv = var_zaxid(pfileid,iv)
1622!---
1623!   2.1 dimension of field
1624!---
1625    IF ( (TRIM(tmp_opp) /= 'never')) THEN
1626      IF (     (TRIM(tmp_opp) /= 'once')  &
1627     &    .AND.(TRIM(tmp_opp) /= 'l_max') &
1628     &    .AND.(TRIM(tmp_opp) /= 'l_min') ) THEN
1629        IF (ziv == -99) THEN
1630          ndim = dim_cnt+1
1631          dims(dim_cnt+1:dim_cnt+2) = (/ tid(pfileid), 0 /)
1632        ELSE
1633          ndim = dim_cnt+2
1634          dims(dim_cnt+1:dim_cnt+2) = (/ zax_ids(pfileid,ziv), tid(pfileid) /)
1635        ENDIF
1636      ELSE
1637        IF (ziv == -99) THEN
1638          ndim = dim_cnt
1639          dims(dim_cnt+1:dim_cnt+2) = (/ 0, 0 /)
1640        ELSE
1641          ndim = dim_cnt+1
1642          dims(dim_cnt+1:dim_cnt+2) = (/ zax_ids(pfileid,ziv), 0 /)
1643        ENDIF
1644      ENDIF
1645!-
1646      iret = NF90_DEF_VAR (ncid,TRIM(tname),NF90_FLOAT, &
1647 &                         dims(1:ABS(ndim)),ncvarid)
1648!-
1649      ncvar_ids(pfileid,iv) = ncvarid
1650!-
1651      iret = NF90_PUT_ATT (ncid,ncvarid,'units',TRIM(tunit))
1652!-
1653      iret = NF90_PUT_ATT (ncid,ncvarid,'missing_value', &
1654 &                         REAL(missing_val,KIND=4))
1655      iret = NF90_PUT_ATT (ncid,ncvarid,'valid_min', &
1656 &                         REAL(minmax(pfileid,iv,1),KIND=4))
1657      iret = NF90_PUT_ATT (ncid,ncvarid,'valid_max', &
1658 &                         REAL(minmax(pfileid,iv,2),KIND=4))
1659!-
1660      iret = NF90_PUT_ATT (ncid,ncvarid,'long_name',TRIM(ttitle))
1661!-
1662      iret = NF90_PUT_ATT (ncid,ncvarid,'short_name',TRIM(tname))
1663!-
1664      iret = NF90_PUT_ATT (ncid,ncvarid,'online_operation', &
1665 &                         TRIM(fullop(pfileid,iv)))
1666!-
1667      SELECT CASE(ndim)
1668      CASE(-3)
1669        str30 = 'ZYX'
1670      CASE(2)
1671        str30 = 'YX'
1672      CASE(3)
1673        str30 = 'TYX'
1674      CASE(4)
1675        str30 = 'TZYX'
1676      CASE DEFAULT
1677        CALL ipslerr (3,"histend", &
1678       &  'less than 2 or more than 4 dimensions are not', &
1679       &  'allowed at this stage',' ')
1680      END SELECT
1681!-
1682      iret = NF90_PUT_ATT (ncid,ncvarid,'axis',TRIM(str30))
1683!-
1684      assoc='nav_lat nav_lon'
1685      ziv = var_zaxid(pfileid, iv)
1686      IF (ziv > 0) THEN
1687        str30 = zax_name(pfileid,ziv)
1688        assoc = TRIM(str30)//' '//TRIM(assoc)
1689      ENDIF
1690!-
1691      IF (itax > 0) THEN
1692        IF ( nb_tax(pfileid) > 1) THEN
1693          str30 = "t_"//tax_name(pfileid,itax)
1694        ELSE
1695          str30 = "time_counter"
1696        ENDIF
1697        assoc = TRIM(str30)//' '//TRIM(assoc)
1698!-
1699        IF (check) THEN
1700          WRITE(*,*) "histend : 2.0.n, freq_opp, freq_wrt", &
1701 &                   freq_opp(pfileid,iv), freq_wrt(pfileid,iv)
1702        ENDIF
1703!-
1704        iret = NF90_PUT_ATT (ncid,ncvarid,'interval_operation', &
1705 &                           REAL(freq_opp(pfileid,iv),KIND=4))
1706        iret = NF90_PUT_ATT (ncid,ncvarid,'interval_write', &
1707 &                           REAL(freq_wrt(pfileid,iv),KIND=4))
1708      ENDIF
1709      iret = NF90_PUT_ATT (ncid,ncvarid,'associate',TRIM(assoc))
1710    ENDIF
1711  ENDDO
1712!-
1713! 3.0 Put the netcdf file into wrte mode
1714!-
1715  IF (check) WRITE(*,*) "histend : 3.0"
1716!-
1717  iret = NF90_ENDDEF (ncid)
1718!-
1719! 4.0 Give some informations to the user
1720!-
1721  IF (check) WRITE(*,*) "histend : 4.0"
1722!-
1723  WRITE(str70,'("All variables have been initialized on file :",I3)') pfileid
1724  CALL ipslerr (1,'histend',str70,'',' ')
1725!---------------------
1726END SUBROUTINE histend
1727!===
1728SUBROUTINE histwrite_r1d (pfileid,pvarname,pitau,pdata,nbindex,nindex)
1729!---------------------------------------------------------------------
1730  IMPLICIT NONE
1731!-
1732  INTEGER,INTENT(IN) :: pfileid, pitau, nbindex, nindex(nbindex)
1733  REAL,DIMENSION(:),INTENT(IN) :: pdata
1734  CHARACTER(LEN=*),INTENT(IN) :: pvarname
1735!-
1736  LOGICAL :: do_oper, do_write, largebuf
1737  INTEGER :: varid, io, nbpt_in, nbpt_out
1738  REAL, ALLOCATABLE,SAVE :: buff_tmp(:)
1739  INTEGER,SAVE :: buff_tmp_sz
1740  CHARACTER(LEN=7) :: tmp_opp
1741!-
1742  LOGICAL :: check = .FALSE.
1743!---------------------------------------------------------------------
1744!-
1745! 1.0 Try to catch errors like specifying the wrong file ID.
1746!     Thanks Marine for showing us what errors users can make !
1747!-
1748  IF ( (pfileid < 1).OR.(pfileid > nb_files) ) THEN
1749    CALL ipslerr (3,"histwrite", &
1750 &    'Illegal file ID in the histwrite of variable',pvarname,' ')
1751  ENDIF
1752!-
1753! 1.1 Find the id of the variable to be written and the real time
1754!-
1755  CALL histvar_seq (pfileid,pvarname,varid)
1756!-
1757! 2.0 do nothing for never operation
1758!-
1759  tmp_opp = topp(pfileid,varid)
1760!-
1761  IF (TRIM(tmp_opp) == "never") THEN
1762    last_opp_chk(pfileid,varid) = -99
1763    last_wrt_chk(pfileid,varid) = -99
1764  ENDIF
1765!-
1766! 3.0 We check if we need to do an operation
1767!-
1768  IF (last_opp_chk(pfileid,varid) == pitau) THEN
1769    CALL ipslerr (3,"histwrite", &
1770 &    'This variable as already been analysed at the present', &
1771 &    'time step',' ')
1772  ENDIF
1773!-
1774  CALL isittime &
1775 &  (pitau, date0(pfileid), deltat(pfileid), freq_opp(pfileid,varid), &
1776 &   last_opp(pfileid,varid), last_opp_chk(pfileid,varid), do_oper)
1777!-
1778! 4.0 We check if we need to write the data
1779!-
1780  IF (last_wrt_chk(pfileid,varid) == pitau) THEN
1781    CALL ipslerr (3,"histwrite", &
1782 &    'This variable as already been written for the present', &
1783 &    'time step',' ')
1784  ENDIF
1785!-
1786  CALL isittime &
1787 &  (pitau, date0(pfileid), deltat(pfileid), freq_wrt(pfileid,varid), &
1788 &   last_wrt(pfileid,varid), last_wrt_chk(pfileid,varid), do_write)
1789!-
1790! 5.0 histwrite called
1791!-
1792  IF (do_oper.OR.do_write) THEN
1793!-
1794!-- 5.1 Get the sizes of the data we will handle
1795!-
1796    IF (datasz_in(pfileid,varid,1) <= 0) THEN
1797!---- There is the risk here that the user has over-sized the array.
1798!---- But how can we catch this ?
1799!---- In the worst case we will do impossible operations
1800!---- on part of the data !
1801      datasz_in(pfileid,varid,1) = SIZE(pdata)
1802      datasz_in(pfileid,varid,2) = -1
1803      datasz_in(pfileid,varid,3) = -1
1804    ENDIF
1805!-
1806!-- 5.2 The maximum size of the data will give the size of the buffer
1807!-
1808    IF (datasz_max(pfileid,varid) <= 0) THEN
1809      largebuf = .FALSE.
1810      DO io=1,nbopp(pfileid,varid)
1811        IF (INDEX(fuchnbout,sopps(pfileid,varid,io)) > 0) THEN
1812          largebuf = .TRUE.
1813        ENDIF
1814      ENDDO
1815      IF (largebuf) THEN
1816        datasz_max(pfileid,varid) = &
1817 &        scsize(pfileid,varid,1) &
1818 &       *scsize(pfileid,varid,2) &
1819 &       *scsize(pfileid,varid,3)
1820      ELSE
1821        datasz_max(pfileid,varid) = &
1822 &        datasz_in(pfileid,varid,1)
1823      ENDIF
1824    ENDIF
1825!-
1826    IF (.NOT.ALLOCATED(buff_tmp)) THEN
1827      IF (check) THEN
1828        WRITE(*,*) &
1829 &       "histwrite_r1d : allocate buff_tmp for buff_sz = ", &
1830 &       datasz_max(pfileid,varid)
1831      ENDIF
1832      ALLOCATE (buff_tmp(datasz_max(pfileid,varid)))
1833      buff_tmp_sz = datasz_max(pfileid,varid)
1834    ELSE IF (datasz_max(pfileid,varid) > buff_tmp_sz) THEN
1835      IF (check) THEN
1836        WRITE(*,*) &
1837 &       "histwrite_r1d : re-allocate buff_tmp for buff_sz = ", &
1838 &       datasz_max(pfileid,varid)
1839      ENDIF
1840      DEALLOCATE (buff_tmp)
1841      ALLOCATE (buff_tmp(datasz_max(pfileid,varid)))
1842      buff_tmp_sz = datasz_max(pfileid,varid)
1843    ENDIF
1844!-
1845!-- We have to do the first operation anyway.
1846!-- Thus we do it here and change the ranke
1847!-- of the data at the same time. This should speed up things.
1848!-
1849    nbpt_in = datasz_in(pfileid,varid,1)
1850    nbpt_out = datasz_max(pfileid,varid)
1851    CALL mathop (sopps(pfileid,varid,1), nbpt_in, pdata, &
1852 &               missing_val, nbindex, nindex, &
1853 &               scal(pfileid,varid,1), nbpt_out, buff_tmp)
1854    CALL histwrite_real (pfileid, varid, pitau, nbpt_out, &
1855 &            buff_tmp, nbindex, nindex, do_oper, do_write)
1856  ENDIF
1857!-
1858! 6.0 Manage time steps
1859!-
1860  IF ((TRIM(tmp_opp) /= "once").AND.(TRIM(tmp_opp) /= "never")) THEN
1861    last_opp_chk(pfileid,varid) = pitau
1862    last_wrt_chk(pfileid,varid) = pitau
1863  ELSE
1864    last_opp_chk(pfileid,varid) = -99
1865    last_wrt_chk(pfileid,varid) = -99
1866  ENDIF
1867!---------------------------
1868END SUBROUTINE histwrite_r1d
1869!===
1870SUBROUTINE histwrite_r2d (pfileid,pvarname,pitau,pdata,nbindex,nindex)
1871!---------------------------------------------------------------------
1872  IMPLICIT NONE
1873!-
1874  INTEGER,INTENT(IN) :: pfileid, pitau, nbindex, nindex(nbindex)
1875  REAL,DIMENSION(:,:),INTENT(IN) :: pdata
1876  CHARACTER(LEN=*),INTENT(IN) :: pvarname
1877!-
1878  LOGICAL :: do_oper, do_write, largebuf
1879  INTEGER :: varid, io, nbpt_in(1:2), nbpt_out
1880  REAL, ALLOCATABLE,SAVE :: buff_tmp(:)
1881  INTEGER,SAVE :: buff_tmp_sz
1882  CHARACTER(LEN=7) :: tmp_opp
1883!-
1884  LOGICAL :: check = .FALSE.
1885!---------------------------------------------------------------------
1886!-
1887! 1.0 Try to catch errors like specifying the wrong file ID.
1888!     Thanks Marine for showing us what errors users can make !
1889!-
1890  IF ( (pfileid < 1).OR.(pfileid > nb_files) ) THEN
1891    CALL ipslerr (3,"histwrite", &
1892 &    'Illegal file ID in the histwrite of variable',pvarname,' ')
1893  ENDIF
1894!-
1895! 1.1 Find the id of the variable to be written and the real time
1896!-
1897  CALL histvar_seq (pfileid,pvarname,varid)
1898!-
1899! 2.0 do nothing for never operation
1900!-
1901  tmp_opp = topp(pfileid,varid)
1902!-
1903  IF (TRIM(tmp_opp) == "never") THEN
1904    last_opp_chk(pfileid,varid) = -99
1905    last_wrt_chk(pfileid,varid) = -99
1906  ENDIF
1907!-
1908! 3.0 We check if we need to do an operation
1909!-
1910  IF (last_opp_chk(pfileid,varid) == pitau) THEN
1911    CALL ipslerr (3,"histwrite", &
1912 &    'This variable as already been analysed at the present', &
1913 &    'time step',' ')
1914  ENDIF
1915!-
1916  CALL isittime &
1917 &  (pitau, date0(pfileid), deltat(pfileid), freq_opp(pfileid,varid), &
1918 &   last_opp(pfileid,varid), last_opp_chk(pfileid,varid), do_oper)
1919!-
1920! 4.0 We check if we need to write the data
1921!-
1922  IF (last_wrt_chk(pfileid,varid) == pitau) THEN
1923    CALL ipslerr (3,"histwrite", &
1924 &    'This variable as already been written for the present', &
1925 &    'time step',' ')
1926  ENDIF
1927!-
1928  CALL isittime &
1929 &  (pitau, date0(pfileid), deltat(pfileid), freq_wrt(pfileid,varid), &
1930 &   last_wrt(pfileid,varid), last_wrt_chk(pfileid,varid), do_write)
1931!-
1932! 5.0 histwrite called
1933!-
1934  IF (do_oper.OR.do_write) THEN
1935!-
1936!-- 5.1 Get the sizes of the data we will handle
1937!-
1938    IF (datasz_in(pfileid,varid,1) <= 0) THEN
1939!---- There is the risk here that the user has over-sized the array.
1940!---- But how can we catch this ?
1941!---- In the worst case we will do impossible operations
1942!---- on part of the data !
1943      datasz_in(pfileid,varid,1) = SIZE(pdata, DIM=1)
1944      datasz_in(pfileid,varid,2) = SIZE(pdata, DIM=2)
1945      datasz_in(pfileid,varid,3) = -1
1946    ENDIF
1947!-
1948!-- 5.2 The maximum size of the data will give the size of the buffer
1949!-
1950    IF (datasz_max(pfileid,varid) <= 0) THEN
1951      largebuf = .FALSE.
1952      DO io=1,nbopp(pfileid,varid)
1953        IF (INDEX(fuchnbout,sopps(pfileid,varid,io)) > 0) THEN
1954          largebuf = .TRUE.
1955        ENDIF
1956      ENDDO
1957      IF (largebuf) THEN
1958        datasz_max(pfileid,varid) = &
1959 &        scsize(pfileid,varid,1) &
1960 &       *scsize(pfileid,varid,2) &
1961 &       *scsize(pfileid,varid,3)
1962      ELSE
1963        datasz_max(pfileid,varid) = &
1964 &        datasz_in(pfileid,varid,1) &
1965 &       *datasz_in(pfileid,varid,2)
1966      ENDIF
1967    ENDIF
1968!-
1969    IF (.NOT.ALLOCATED(buff_tmp)) THEN
1970      IF (check) THEN
1971        WRITE(*,*) &
1972 &       "histwrite_r2d : allocate buff_tmp for buff_sz = ", &
1973 &       datasz_max(pfileid,varid)
1974      ENDIF
1975      ALLOCATE (buff_tmp(datasz_max(pfileid,varid)))
1976      buff_tmp_sz = datasz_max(pfileid,varid)
1977    ELSE IF (datasz_max(pfileid,varid) > buff_tmp_sz) THEN
1978      IF (check) THEN
1979        WRITE(*,*) &
1980 &       "histwrite_r2d : re-allocate buff_tmp for buff_sz = ", &
1981 &       datasz_max(pfileid,varid)
1982      ENDIF
1983      DEALLOCATE (buff_tmp)
1984      ALLOCATE (buff_tmp(datasz_max(pfileid,varid)))
1985      buff_tmp_sz = datasz_max(pfileid,varid)
1986    ENDIF
1987!-
1988!-- We have to do the first operation anyway.
1989!-- Thus we do it here and change the ranke
1990!-- of the data at the same time. This should speed up things.
1991!-
1992    nbpt_in(1:2) = datasz_in(pfileid,varid,1:2)
1993    nbpt_out = datasz_max(pfileid,varid)
1994    CALL mathop (sopps(pfileid,varid,1), nbpt_in, pdata, &
1995 &               missing_val, nbindex, nindex, &
1996 &               scal(pfileid,varid,1), nbpt_out, buff_tmp)
1997    CALL histwrite_real (pfileid, varid, pitau, nbpt_out, &
1998 &            buff_tmp, nbindex, nindex, do_oper, do_write)
1999  ENDIF
2000!-
2001! 6.0 Manage time steps
2002!-
2003  IF ((TRIM(tmp_opp) /= "once").AND.(TRIM(tmp_opp) /= "never")) THEN
2004    last_opp_chk(pfileid,varid) = pitau
2005    last_wrt_chk(pfileid,varid) = pitau
2006  ELSE
2007    last_opp_chk(pfileid,varid) = -99
2008    last_wrt_chk(pfileid,varid) = -99
2009  ENDIF
2010!---------------------------
2011END SUBROUTINE histwrite_r2d
2012!===
2013SUBROUTINE histwrite_r3d (pfileid,pvarname,pitau,pdata,nbindex,nindex)
2014!---------------------------------------------------------------------
2015  IMPLICIT NONE
2016!-
2017  INTEGER,INTENT(IN) :: pfileid, pitau, nbindex, nindex(nbindex)
2018  REAL,DIMENSION(:,:,:),INTENT(IN) :: pdata
2019  CHARACTER(LEN=*),INTENT(IN) :: pvarname
2020!-
2021  LOGICAL :: do_oper, do_write, largebuf
2022  INTEGER :: varid, io, nbpt_in(1:3), nbpt_out
2023  REAL, ALLOCATABLE,SAVE :: buff_tmp(:)
2024  INTEGER,SAVE :: buff_tmp_sz
2025  CHARACTER(LEN=7) :: tmp_opp
2026!-
2027  LOGICAL :: check = .FALSE.
2028!---------------------------------------------------------------------
2029!-
2030! 1.0 Try to catch errors like specifying the wrong file ID.
2031!     Thanks Marine for showing us what errors users can make !
2032!-
2033  IF ( (pfileid < 1).OR.(pfileid > nb_files) ) THEN
2034    CALL ipslerr (3,"histwrite", &
2035 &    'Illegal file ID in the histwrite of variable',pvarname,' ')
2036  ENDIF
2037!-
2038! 1.1 Find the id of the variable to be written and the real time
2039!-
2040  CALL histvar_seq (pfileid,pvarname,varid)
2041!-
2042! 2.0 do nothing for never operation
2043!-
2044  tmp_opp = topp(pfileid,varid)
2045!-
2046  IF (TRIM(tmp_opp) == "never") THEN
2047    last_opp_chk(pfileid,varid) = -99
2048    last_wrt_chk(pfileid,varid) = -99
2049  ENDIF
2050!-
2051! 3.0 We check if we need to do an operation
2052!-
2053  IF (last_opp_chk(pfileid,varid) == pitau) THEN
2054    CALL ipslerr (3,"histwrite", &
2055 &    'This variable as already been analysed at the present', &
2056 &    'time step',' ')
2057  ENDIF
2058!-
2059  CALL isittime &
2060 &  (pitau, date0(pfileid), deltat(pfileid), freq_opp(pfileid,varid), &
2061 &   last_opp(pfileid,varid), last_opp_chk(pfileid,varid), do_oper)
2062!-
2063! 4.0 We check if we need to write the data
2064!-
2065  IF (last_wrt_chk(pfileid,varid) == pitau) THEN
2066    CALL ipslerr (3,"histwrite", &
2067 &    'This variable as already been written for the present', &
2068 &    'time step',' ')
2069  ENDIF
2070!-
2071  CALL isittime &
2072 &  (pitau, date0(pfileid), deltat(pfileid), freq_wrt(pfileid,varid), &
2073 &   last_wrt(pfileid,varid), last_wrt_chk(pfileid,varid), do_write)
2074!-
2075! 5.0 histwrite called
2076!-
2077  IF (do_oper.OR.do_write) THEN
2078!-
2079!-- 5.1 Get the sizes of the data we will handle
2080!-
2081    IF (datasz_in(pfileid,varid,1) <= 0) THEN
2082!---- There is the risk here that the user has over-sized the array.
2083!---- But how can we catch this ?
2084!---- In the worst case we will do impossible operations
2085!---- on part of the data !
2086      datasz_in(pfileid,varid,1) = SIZE(pdata, DIM=1)
2087      datasz_in(pfileid,varid,2) = SIZE(pdata, DIM=2)
2088      datasz_in(pfileid,varid,3) = SIZE(pdata, DIM=3)
2089    ENDIF
2090!-
2091!-- 5.2 The maximum size of the data will give the size of the buffer
2092!-
2093    IF (datasz_max(pfileid,varid) <= 0) THEN
2094      largebuf = .FALSE.
2095      DO io =1,nbopp(pfileid,varid)
2096        IF (INDEX(fuchnbout,sopps(pfileid,varid,io)) > 0) THEN
2097          largebuf = .TRUE.
2098        ENDIF
2099      ENDDO
2100      IF (largebuf) THEN
2101        datasz_max(pfileid,varid) = &
2102 &        scsize(pfileid,varid,1) &
2103 &       *scsize(pfileid,varid,2) &
2104 &       *scsize(pfileid,varid,3)
2105      ELSE
2106        datasz_max(pfileid,varid) = &
2107 &        datasz_in(pfileid,varid,1) &
2108 &       *datasz_in(pfileid,varid,2) &
2109 &       *datasz_in(pfileid,varid,3)
2110      ENDIF
2111    ENDIF
2112!-
2113    IF (.NOT.ALLOCATED(buff_tmp)) THEN
2114      IF (check) THEN
2115        WRITE(*,*) &
2116 &       "histwrite_r1d : allocate buff_tmp for buff_sz = ", &
2117 &       datasz_max(pfileid,varid)
2118      ENDIF
2119      ALLOCATE (buff_tmp(datasz_max(pfileid,varid)))
2120      buff_tmp_sz = datasz_max(pfileid,varid)
2121    ELSE IF (datasz_max(pfileid,varid) > buff_tmp_sz) THEN
2122      IF (check) THEN
2123        WRITE(*,*) &
2124 &       "histwrite_r1d : re-allocate buff_tmp for buff_sz = ", &
2125 &       datasz_max(pfileid,varid)
2126      ENDIF
2127      DEALLOCATE (buff_tmp)
2128      ALLOCATE (buff_tmp(datasz_max(pfileid,varid)))
2129      buff_tmp_sz = datasz_max(pfileid,varid)
2130    ENDIF
2131!-
2132!-- We have to do the first operation anyway.
2133!-- Thus we do it here and change the ranke
2134!-- of the data at the same time. This should speed up things.
2135!-
2136    nbpt_in(1:3) = datasz_in(pfileid,varid,1:3)
2137    nbpt_out = datasz_max(pfileid,varid)
2138    CALL mathop (sopps(pfileid,varid,1), nbpt_in, pdata, &
2139 &               missing_val, nbindex, nindex, &
2140 &               scal(pfileid,varid,1), nbpt_out, buff_tmp)
2141    CALL histwrite_real (pfileid, varid, pitau, nbpt_out, &
2142 &            buff_tmp, nbindex, nindex, do_oper, do_write)
2143  ENDIF
2144!-
2145! 6.0 Manage time steps
2146!-
2147  IF ((TRIM(tmp_opp) /= "once").AND.(TRIM(tmp_opp) /= "never")) THEN
2148    last_opp_chk(pfileid,varid) = pitau
2149    last_wrt_chk(pfileid,varid) = pitau
2150  ELSE
2151    last_opp_chk(pfileid,varid) = -99
2152    last_wrt_chk(pfileid,varid) = -99
2153  ENDIF
2154!---------------------------
2155END SUBROUTINE histwrite_r3d
2156!===
2157SUBROUTINE histwrite_real &
2158 & (pfileid,varid,pitau,nbdpt,buff_tmp,nbindex,nindex,do_oper,do_write)
2159!---------------------------------------------------------------------
2160!- This subroutine is internal and does the calculations and writing
2161!- if needed. At a later stage it should be split into an operation
2162!- and writing subroutines.
2163!---------------------------------------------------------------------
2164  IMPLICIT NONE
2165!-
2166  INTEGER,INTENT(IN) :: pfileid,pitau,varid, &
2167 &                      nbindex,nindex(nbindex),nbdpt
2168  REAL,DIMENSION(:)  :: buff_tmp
2169  LOGICAL,INTENT(IN) :: do_oper,do_write
2170!-
2171  INTEGER :: tsz, ncid, ncvarid
2172  INTEGER :: i, iret, ipt, itax
2173  INTEGER :: io, nbin, nbout
2174  INTEGER,DIMENSION(4) :: corner, edges
2175  INTEGER :: itime
2176!-
2177  REAL :: rtime
2178  CHARACTER(LEN=7) :: tmp_opp
2179  REAL :: mindata, maxdata
2180  REAL,ALLOCATABLE,SAVE :: buff_tmp2(:)
2181  INTEGER,SAVE          :: buff_tmp2_sz
2182  REAL,ALLOCATABLE,SAVE :: buffer_used(:)
2183  INTEGER,SAVE          :: buffer_sz
2184!-xx  INTEGER :: ji
2185!-
2186  LOGICAL :: check = .FALSE.
2187!---------------------------------------------------------------------
2188  IF (check) THEN
2189    WRITE(*,*) "histwrite 0.0 :  VAR : ", name(pfileid,varid)
2190    WRITE(*,*) "histwrite 0.0 : nbindex, nindex :", &
2191    &  nbindex,nindex(1:MIN(3,nbindex)),'...',nindex(MAX(1,nbindex-3):nbindex)
2192  ENDIF
2193!-
2194! The sizes which can be encoutered
2195!-
2196  tsz = zsize(pfileid,varid,1)*zsize(pfileid,varid,2)*zsize(pfileid,varid,3)
2197!-
2198! 1.0 We allocate the memory needed to store the data between write
2199!     and the temporary space needed for operations.
2200!     We have to keep precedent buffer if needed
2201!-
2202  IF (.NOT. ALLOCATED(buffer)) THEN
2203    IF (check) WRITE(*,*) "histwrite_real 1.0 allocate buffer ",buff_pos
2204    ALLOCATE(buffer(buff_pos))
2205    buffer_sz = buff_pos
2206    buffer(:)=0.0
2207  ELSE IF (buffer_sz < buff_pos) THEN
2208    IF (check) WRITE(*,*) "histwrite_real 1.0.1 re-allocate buffer for ",buff_pos," instead of ",SIZE(buffer)
2209    IF (SUM(buffer)/=0.0) THEN
2210      IF (check) WRITE (*,*) ' histwrite : buffer has been used. We have to save it before re-allocating it '
2211      ALLOCATE (buffer_used(buffer_sz))
2212      buffer_used(:)=buffer(:)
2213      DEALLOCATE (buffer)
2214      ALLOCATE (buffer(buff_pos))
2215      buffer_sz = buff_pos
2216      buffer(:SIZE(buffer_used))=buffer_used
2217      DEALLOCATE (buffer_used)
2218    ELSE
2219      IF (check) WRITE (*,*) ' histwrite : buffer has not been used. We have just to re-allocating it '
2220      DEALLOCATE (buffer)
2221      ALLOCATE (buffer(buff_pos))
2222      buffer_sz = buff_pos
2223      buffer(:)=0.0
2224    ENDIF
2225  ENDIF
2226!-
2227! The buffers are only deallocated when more space is needed. This
2228! reduces the umber of allocates but increases memory needs.
2229!-
2230  IF (.NOT.ALLOCATED(buff_tmp2)) THEN
2231    IF (check) THEN
2232      WRITE(*,*) "histwrite_real 1.1 allocate buff_tmp2 ",SIZE(buff_tmp)
2233    ENDIF
2234    ALLOCATE (buff_tmp2(datasz_max(pfileid,varid)))
2235    buff_tmp2_sz = datasz_max(pfileid,varid)
2236  ELSE IF ( datasz_max(pfileid,varid) > buff_tmp2_sz) THEN
2237    IF (check) THEN
2238      WRITE(*,*) "histwrite_real 1.2 re-allocate buff_tmp2 : ", &
2239     & SIZE(buff_tmp)," instead of ",SIZE(buff_tmp2)
2240    ENDIF
2241    DEALLOCATE (buff_tmp2)
2242    ALLOCATE (buff_tmp2(datasz_max(pfileid,varid)))
2243    buff_tmp2_sz = datasz_max(pfileid,varid)
2244  ENDIF
2245!-
2246  rtime = pitau * deltat(pfileid)
2247  tmp_opp = topp(pfileid,varid)
2248!-
2249! 3.0 Do the operations or transfer the slab of data into buff_tmp
2250!-
2251  IF (check) WRITE(*,*) "histwrite: 3.0", pfileid
2252!-
2253! 3.1 DO the Operations only if needed
2254!-
2255  IF ( do_oper ) THEN
2256    i = pfileid
2257    nbout = nbdpt
2258!-
2259!-- 3.4 We continue the sequence of operations
2260!--     we started in the interface routine
2261!-
2262    DO io = 2, nbopp(i,varid),2
2263      nbin = nbout
2264      nbout = datasz_max(i,varid)
2265      CALL mathop(sopps(i,varid,io),nbin,buff_tmp,missing_val, &
2266 &      nbindex,nindex,scal(i,varid,io),nbout,buff_tmp2)
2267      IF (check) THEN
2268        WRITE(*,*) &
2269 &       "histwrite: 3.4a nbout : ",nbin,nbout,sopps(i,varid,io)
2270      ENDIF
2271!-
2272      nbin = nbout
2273      nbout = datasz_max(i,varid)
2274      CALL mathop(sopps(i,varid,io+1),nbin,buff_tmp2,missing_val, &
2275 &      nbindex,nindex,scal(i,varid,io+1),nbout,buff_tmp)
2276      IF (check) THEN
2277        WRITE(*,*) &
2278 &       "histwrite: 3.4b nbout : ",nbin,nbout,sopps(i,varid,io+1)
2279      ENDIF
2280    ENDDO
2281!-
2282!   3.5 Zoom into the data
2283!-
2284    IF (check) THEN
2285      WRITE(*,*) &
2286 &     "histwrite: 3.5 size(buff_tmp) : ",SIZE(buff_tmp)
2287      WRITE(*,*) &
2288 &     "histwrite: 3.5 slab in X :",zorig(i,varid,1),zsize(i,varid,1)
2289      WRITE(*,*) &
2290 &     "histwrite: 3.5 slab in Y :",zorig(i,varid,2),zsize(i,varid,2)
2291      WRITE(*,*) &
2292 &     "histwrite: 3.5 slab in Z :",zorig(i,varid,3),zsize(i,varid,3)
2293      WRITE(*,*) &
2294 &     "histwrite: 3.5 slab of input:", &
2295 &     scsize(i,varid,1),scsize(i,varid,2),scsize(i,varid,3)
2296    ENDIF
2297    CALL trans_buff &
2298 &      (zorig(i,varid,1),zsize(i,varid,1), &
2299 &       zorig(i,varid,2),zsize(i,varid,2), &
2300 &       zorig(i,varid,3),zsize(i,varid,3), &
2301 &       scsize(i,varid,1),scsize(i,varid,2),scsize(i,varid,3), &
2302 &       buff_tmp, buff_tmp2_sz,buff_tmp2)
2303!-
2304!-- 4.0 Get the min and max of the field (buff_tmp)
2305!-
2306    IF (check) WRITE(*,*) "histwrite: 4.0 buff_tmp",pfileid,varid, &
2307 &    TRIM(tmp_opp),'----',LEN_TRIM(tmp_opp),nbindex
2308!-
2309    mindata =  ABS(missing_val)
2310    maxdata = -ABS(missing_val)
2311!-xx DO ji=1,tsz
2312!-xx   IF (buff_tmp2(ji)/= missing_val) THEN
2313!-xx     mindata = MIN(mindata, buff_tmp2(ji))
2314!-xx     maxdata = MAX(maxdata, buff_tmp2(ji))
2315!-xx   ENDIF
2316!-xx ENDDO
2317!-??
2318!-??   mindata = MINVAL(buff_tmp2(1:tsz),
2319!-?? &                  MASK = buff_tmp2(1:tsz) /= missing_val)
2320!-??   maxdata = MAXVAL(buff_tmp2(1:tsz),
2321!-?? &                  MASK = buff_tmp2(1:tsz) /= missing_val)
2322!-??
2323    minmax(pfileid,varid,1) = mindata
2324    minmax(pfileid,varid,2) = maxdata
2325!-
2326!-- 5.0 Do the operations if needed. In the case of instantaneous
2327!--     output we do not transfer to the buffer.
2328!-
2329    IF (check) WRITE(*,*) "histwrite: 5.0", pfileid, "tsz :", tsz
2330!-
2331    ipt = point(pfileid,varid)
2332!-
2333!   WRITE(*,*) 'OPE ipt, buffer :', pvarname, ipt, varid
2334!-
2335    IF (     (TRIM(tmp_opp) /= "inst") &
2336   &    .AND.(TRIM(tmp_opp) /= "once") ) THEN
2337      CALL moycum(tmp_opp,tsz,buffer(ipt:), &
2338     &       buff_tmp2,nb_opp(pfileid,varid))
2339    ENDIF
2340!-
2341    last_opp(pfileid,varid) = pitau
2342    nb_opp(pfileid,varid) = nb_opp(pfileid,varid)+1
2343!-
2344   ENDIF
2345!-
2346! 6.0 Write to file if needed
2347!-
2348  IF (check) WRITE(*,*) "histwrite: 6.0", pfileid
2349!-
2350  IF ( do_write ) THEN
2351!-
2352    ncvarid = ncvar_ids(pfileid,varid)
2353    ncid = ncdf_ids(pfileid)
2354!-
2355!-- 6.1 Do the operations that are needed before writting
2356!-
2357    IF (check) WRITE(*,*) "histwrite: 6.1", pfileid
2358!-
2359    IF (     (TRIM(tmp_opp) /= "inst") &
2360   &    .AND.(TRIM(tmp_opp) /= "once") ) THEN
2361      rtime = (rtime+last_wrt(pfileid,varid)*deltat(pfileid))/2.0
2362    ENDIF
2363!-
2364!-- 6.2 Add a value to the time axis of this variable if needed
2365!-
2366    IF (     (TRIM(tmp_opp) /= "l_max") &
2367   &    .AND.(TRIM(tmp_opp) /= "l_min") &
2368   &    .AND.(TRIM(tmp_opp) /= "once") ) THEN
2369!-
2370      IF (check) WRITE(*,*) "histwrite: 6.2", pfileid
2371!-
2372      itax = var_axid(pfileid, varid)
2373      itime = nb_wrt(pfileid, varid)+1
2374!-
2375      IF (tax_last(pfileid, itax) < itime) THEN
2376        iret = NF90_PUT_VAR (ncid,tdimid(pfileid,itax),(/ rtime /), &
2377 &                            start=(/ itime /),count=(/ 1 /))
2378        tax_last(pfileid, itax) = itime
2379      ENDIF
2380    ELSE
2381      itime=1
2382    ENDIF
2383!-
2384!-- 6.3 Write the data. Only in the case of instantaneous output
2385!       we do not write the buffer.
2386!-
2387    IF (check) THEN
2388      WRITE(*,*) "histwrite: 6.3",pfileid,ncid,ncvarid,varid,itime
2389    ENDIF
2390!-
2391    IF (scsize(pfileid,varid,3) == 1) THEN
2392      IF (regular(pfileid)) THEN
2393        corner(1:4) = (/ 1, 1, itime, 0 /)
2394        edges(1:4) = (/ zsize(pfileid,varid,1), &
2395 &                      zsize(pfileid,varid,2), &
2396 &                       1, 0 /)
2397      ELSE
2398        corner(1:4) = (/ 1, itime, 0, 0 /)
2399        edges(1:4) = (/ zsize(pfileid,varid,1), 1, 0, 0 /)
2400      ENDIF
2401    ELSE
2402      IF ( regular(pfileid) ) THEN
2403        corner(1:4) = (/ 1, 1, 1, itime /)
2404        edges(1:4) = (/ zsize(pfileid,varid,1), &
2405 &                      zsize(pfileid,varid,2), &
2406 &                      zsize(pfileid,varid,3), 1 /)
2407      ELSE
2408        corner(1:4) = (/ 1, 1, itime, 0 /)
2409        edges(1:4) = (/ zsize(pfileid,varid,1), &
2410 &                      zsize(pfileid,varid,3), 1, 0 /)
2411      ENDIF
2412    ENDIF
2413!-
2414    ipt = point(pfileid,varid)
2415!-
2416    IF (     (TRIM(tmp_opp) /= "inst") &
2417 &      .AND.(TRIM(tmp_opp) /= "once") ) THEN
2418      iret = NF90_PUT_VAR (ncid,ncvarid,buffer(ipt:), &
2419 &                       start=corner(1:4),count=edges(1:4))
2420    ELSE
2421      iret = NF90_PUT_VAR (ncid,ncvarid,buff_tmp2, &
2422 &                       start=corner(1:4),count=edges(1:4))
2423    ENDIF
2424!-
2425    last_wrt(pfileid,varid) = pitau
2426    nb_wrt(pfileid,varid) = nb_wrt(pfileid,varid)+1
2427    nb_opp(pfileid,varid) = 0
2428!---
2429!   After the write the file can be synchronized so that no data is
2430!   lost in case of a crash. This feature gives up on the benefits of
2431!   buffering and should only be used in debuging mode. A flag is
2432!   needed here to switch to this mode.
2433!---
2434!   iret = NF90_SYNC (ncid)
2435!-
2436  ENDIF
2437!----------------------------
2438END SUBROUTINE histwrite_real
2439!===
2440SUBROUTINE histvar_seq (pfid,pvarname,pvid)
2441!---------------------------------------------------------------------
2442!- This subroutine optimized the search for the variable in the table.
2443!- In a first phase it will learn the succession of the variables
2444!- called and then it will use the table to guess what comes next.
2445!- It is the best solution to avoid lengthy searches through array
2446!- vectors.
2447!-
2448!- ARGUMENTS :
2449!-
2450!- pfid  : id of the file on which we work
2451!- pvarname : The name of the variable we are looking for
2452!- pvid     : The var id we found
2453!---------------------------------------------------------------------
2454  IMPLICIT NONE
2455!-
2456  INTEGER,INTENT(in)  :: pfid
2457  CHARACTER(LEN=*),INTENT(IN) :: pvarname
2458  INTEGER,INTENT(out) :: pvid
2459!-
2460  LOGICAL,SAVE :: learning(nb_files_max)=.TRUE.
2461  INTEGER,SAVE :: overlap(nb_files_max) = -1
2462  INTEGER,SAVE :: varseq(nb_files_max, nb_var_max*3)
2463  INTEGER,SAVE :: varseq_len(nb_files_max) = 0
2464  INTEGER,SAVE :: varseq_pos(nb_files_max)
2465  INTEGER,SAVE :: varseq_err(nb_files_max) = 0
2466  INTEGER      :: ib, nb, sp, nx, pos
2467  CHARACTER(LEN=20),DIMENSION(nb_var_max) :: tab_str20
2468  CHARACTER(LEN=20) :: str20
2469  CHARACTER(LEN=70) :: str70
2470  INTEGER      :: tab_str20_length(nb_var_max)
2471!-
2472  LOGICAL :: check = .FALSE.
2473!---------------------------------------------------------------------
2474  nb = nb_var(pfid)
2475!-
2476  IF (check) THEN
2477    WRITE(*,*) 'histvar_seq, start of the subroutine :',learning(pfid)
2478  ENDIF
2479!-
2480  IF (learning(pfid)) THEN
2481!-
2482!-- 1.0 We compute the length over which we are going
2483!--     to check the overlap
2484!-
2485    IF (overlap(pfid) <= 0) THEN
2486      IF (nb_var(pfid) > 6) THEN
2487        overlap(pfid) = nb_var(pfid)/3*2
2488      ELSE
2489        overlap(pfid) = nb_var(pfid)
2490      ENDIF
2491    ENDIF
2492!-
2493!-- 1.1 Find the position of this string
2494!-
2495    str20 = pvarname
2496    tab_str20(1:nb) = name(pfid,1:nb)
2497    tab_str20_length(1:nb) = name_length(pfid,1:nb)
2498!-
2499    CALL find_str (nb, tab_str20, tab_str20_length, str20, pos)
2500!-
2501    IF (pos > 0) THEN
2502      pvid = pos
2503    ELSE
2504      CALL ipslerr (3,"histvar_seq", &
2505 &      'The name of the variable you gave has not been declared', &
2506 &      'You should use subroutine histdef for declaring variable', &
2507 &      TRIM(str20))
2508    ENDIF
2509!-
2510!-- 1.2 If we have not given up we store the position
2511!--     in the sequence of calls
2512!-
2513    IF ( varseq_err(pfid) .GE. 0 ) THEN
2514      sp = varseq_len(pfid)+1
2515      IF (sp <= nb_var_max*3) THEN
2516        varseq(pfid,sp) = pvid
2517        varseq_len(pfid) = sp
2518      ELSE
2519        CALL ipslerr (2,"histvar_seq",&
2520 &       'The learning process has failed and we give up. '// &
2521 &       'Either you sequence is',&
2522 &       'too complex or I am too dumb. '// &
2523 &       'This will only affect the efficiency',&
2524 &       'of your code. Thus if you wish to save time'// &
2525 &       ' contact the IOIPSL team. ')
2526        WRITE(*,*) 'The sequence we have found up to now :'
2527        WRITE(*,*) varseq(pfid,1:sp-1)
2528        varseq_err(pfid) = -1
2529      ENDIF
2530!-
2531!---- 1.3 Check if we have found the right overlap
2532!-
2533      IF (varseq_len(pfid) .GE. overlap(pfid)*2) THEN
2534!-
2535!------ We skip a few variables if needed as they could come
2536!------ from the initialisation of the model.
2537!-
2538        DO ib = 0, sp-overlap(pfid)*2
2539          IF ( learning(pfid) .AND.&
2540            & SUM(ABS(varseq(pfid,ib+1:ib+overlap(pfid)) -&
2541            & varseq(pfid,sp-overlap(pfid)+1:sp))) == 0 ) THEN
2542            learning(pfid) = .FALSE.
2543            varseq_len(pfid) = sp-overlap(pfid)-ib
2544            varseq_pos(pfid) = overlap(pfid)+ib
2545            varseq(pfid,1:varseq_len(pfid)) = &
2546 &            varseq(pfid,ib+1:ib+varseq_len(pfid))
2547          ENDIF
2548        ENDDO
2549      ENDIF
2550    ENDIF
2551  ELSE
2552!-
2553!-- 2.0 Now we know how the calls to histwrite are sequenced
2554!--     and we can get a guess at the var ID
2555!-
2556    nx = varseq_pos(pfid)+1
2557    IF (nx > varseq_len(pfid)) nx = 1
2558!-
2559    pvid = varseq(pfid, nx)
2560!-
2561    IF (    (INDEX(name(pfid,pvid),pvarname) <= 0)         &
2562   &    .OR.(name_length(pfid,pvid) /= len_trim(pvarname)) ) THEN
2563      str20 = pvarname
2564      tab_str20(1:nb) = name(pfid,1:nb)
2565      tab_str20_length(1:nb) = name_length(pfid,1:nb)
2566      CALL find_str (nb,tab_str20,tab_str20_length,str20,pos)
2567      IF (pos > 0) THEN
2568        pvid = pos
2569      ELSE
2570        CALL ipslerr (3,"histvar_seq", &
2571 &  'The name of the variable you gave has not been declared',&
2572 &  'You should use subroutine histdef for declaring variable',str20)
2573      ENDIF
2574      varseq_err(pfid) = varseq_err(pfid)+1
2575    ELSE
2576!-
2577!---- We only keep the new position if we have found the variable
2578!---- this way. This way an out of sequence call to histwrite does
2579!---- not defeat the process.
2580!-
2581      varseq_pos(pfid) = nx
2582    ENDIF
2583!-
2584    IF (varseq_err(pfid) .GE. 10) THEN
2585      WRITE(str70,'("for file ",I3)') pfid
2586      CALL ipslerr (2,"histvar_seq", &
2587 &  'There were 10 errors in the learned sequence of variables',&
2588 &  str70,'This looks like a bug, please report it.')
2589         varseq_err(pfid) = 0
2590    ENDIF
2591  ENDIF
2592!-
2593  IF (check) THEN
2594    WRITE(*,*) &
2595 &   'histvar_seq, end of the subroutine :',TRIM(pvarname),pvid
2596  ENDIF
2597!-------------------------
2598END SUBROUTINE histvar_seq
2599!===
2600SUBROUTINE histsync (file)
2601!---------------------------------------------------------------------
2602!- This subroutine will synchronise all
2603!- (or one if defined) opened files.
2604!-
2605!- VERSION
2606!-
2607!---------------------------------------------------------------------
2608  IMPLICIT NONE
2609!-
2610! file  : optional argument for fileid
2611  INTEGER,INTENT(in),OPTIONAL :: file
2612!-
2613  INTEGER :: ifile,ncid,iret
2614!-
2615  LOGICAL :: file_exists
2616  LOGICAL :: check = .FALSE.
2617!---------------------------------------------------------------------
2618  IF (check) WRITE(*,*) 'Entering loop on files :', nb_files
2619!-
2620! 1.The loop on files to synchronise
2621!-
2622  DO ifile = 1,nb_files
2623!-
2624    IF (PRESENT(file)) THEN
2625      file_exists = (ifile == file)
2626    ELSE
2627      file_exists = .TRUE.
2628    ENDIF
2629!-
2630    IF ( file_exists ) THEN
2631      IF (check) THEN
2632        WRITE(*,*) 'Synchronising specified file number :', file
2633      ENDIF
2634      ncid = ncdf_ids(ifile)
2635      iret = NF90_SYNC (ncid)
2636    ENDIF
2637!-
2638  ENDDO
2639!----------------------
2640END SUBROUTINE histsync
2641!===
2642SUBROUTINE histclo (fid)
2643!---------------------------------------------------------------------
2644!- This subroutine will close all (or one if defined) opened files
2645!-
2646!- VERSION
2647!-
2648!---------------------------------------------------------------------
2649  IMPLICIT NONE
2650!-
2651! fid  : optional argument for fileid
2652  INTEGER,INTENT(in),OPTIONAL :: fid
2653!-
2654  INTEGER :: ifile,ncid,iret,iv,ncvarid
2655  INTEGER :: start_loop,end_loop
2656  CHARACTER(LEN=70) :: str70
2657!-
2658  LOGICAL :: check=.FALSE.
2659!---------------------------------------------------------------------
2660  IF (check) WRITE(*,*) 'Entering loop on files :', nb_files
2661!-
2662  IF (PRESENT(fid)) THEN
2663    start_loop = fid
2664    end_loop = fid
2665  ELSE
2666    start_loop = 1
2667    end_loop = nb_files
2668  ENDIF
2669!-
2670  DO ifile=start_loop,end_loop
2671    IF (check) WRITE(*,*) 'Closing specified file number :', ifile
2672    ncid = ncdf_ids(ifile)
2673    iret = NF90_REDEF (ncid)
2674!-
2675!-- 1. The loop on the number of variables to add
2676!-     some final information
2677!-
2678    IF ( check ) WRITE(*,*) 'Entering loop on vars :', nb_var(ifile)
2679    DO iv = 1,nb_var(ifile)
2680      ncvarid = ncvar_ids(ifile,iv)
2681      IF (check) THEN
2682        WRITE(*,*) 'min value for file :',ifile,' var n. :',iv, &
2683       &           ' is : ',minmax(ifile,iv,1)
2684        WRITE(*,*) 'max value for file :',ifile,' var n. :',iv, &
2685       &           ' is : ',minmax(ifile,iv,2)
2686      ENDIF
2687!-
2688!---- 1.1 Put the min and max values on the file
2689!-
2690      iret = NF90_PUT_ATT (ncid,ncvarid,'valid_min', &
2691 &                         REAL(minmax(ifile,iv,1),KIND=4))
2692      iret = NF90_PUT_ATT (ncid,ncvarid,'valid_max', &
2693 &                         REAL(minmax(ifile,iv,2),KIND=4))
2694    ENDDO
2695!-
2696!-- 2.0 We list the names of the other files
2697!--     in the associated_file attribute
2698!-
2699    IF (nb_files > 1 ) THEN
2700      iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'associate_file', &
2701 &                         TRIM(assc_file))
2702    ENDIF
2703    IF ( check ) WRITE(*,*) 'close file :', ncid
2704    iret = NF90_CLOSE (ncid)
2705    IF (iret /= NF90_NOERR) THEN
2706      WRITE(str70,'("This file has been already closed :",I3)') ifile
2707      CALL ipslerr (2,'histclo',str70,'',' ')
2708    ENDIF
2709  ENDDO
2710!---------------------
2711END SUBROUTINE histclo
2712!===
2713SUBROUTINE ioconf_modname (str)
2714!---------------------------------------------------------------------
2715!- This subroutine allows to configure the name
2716!- of the model written into the file
2717!---------------------------------------------------------------------
2718  IMPLICIT NONE
2719!-
2720  CHARACTER(LEN=*),INTENT(IN) :: str
2721!---------------------------------------------------------------------
2722  IF (.NOT.lock_modname) THEN
2723    model_name = str(1:MIN(LEN_TRIM(str),80))
2724    lock_modname = .TRUE.
2725  ELSE
2726    CALL ipslerr (2,"ioconf_modname", &
2727   &  'The model name can only be changed once and only', &
2728   &  'before it is used. It is now set to :',model_name)
2729  ENDIF
2730!----------------------------
2731END SUBROUTINE ioconf_modname
2732!-
2733!===
2734!-
2735!-----------------
2736END MODULE histcom
Note: See TracBrowser for help on using the repository browser.