/[lmdze]/trunk/IOIPSL/histcom_var.f90
ViewVC logotype

Annotation of /trunk/IOIPSL/histcom_var.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (hide annotations)
Thu Jun 13 14:40:06 2019 UTC (5 years, 1 month ago) by guez
File size: 2784 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 guez 30 MODULE histcom_var
2    
3     implicit none
4    
5     ! Fixed parameter
6 guez 62 INTEGER, PARAMETER:: nb_files_max=20, nb_var_max=400, &
7     nb_hax_max=5, nb_zax_max=10, nbopp_max=10
8     REAL, PARAMETER:: missing_val = 1e20
9 guez 30
10 guez 62 INTEGER:: bufftmp_max(nb_files_max) = 1
11 guez 30
12     ! Time variables
13 guez 62 INTEGER, SAVE:: itau0(nb_files_max)=0
14 guez 30
15     ! Counter of elements
16 guez 62 INTEGER, DIMENSION(nb_files_max), SAVE:: nb_var=0, nb_tax=0
17 guez 30
18     ! NETCDF IDs for files and axes
19 guez 62 INTEGER, DIMENSION(nb_files_max), SAVE:: ncdf_ids, xid, yid, tid
20     CHARACTER(LEN=500):: assc_file = ''
21 guez 30
22     ! General definitions in the NETCDF file
23 guez 62 INTEGER, DIMENSION(nb_files_max, 2), SAVE:: full_size=0, slab_ori, slab_sz
24 guez 30
25     ! The horizontal axes
26 guez 62 INTEGER, SAVE:: nb_hax(nb_files_max)=0
27     CHARACTER(LEN=25), SAVE:: hax_name(nb_files_max, nb_hax_max, 2)
28 guez 30
29     ! The vertical axes
30 guez 62 INTEGER, SAVE:: nb_zax(nb_files_max)=0
31     INTEGER, DIMENSION(nb_files_max, nb_zax_max), SAVE:: &
32     zax_size, zax_ids, zax_name_length
33     CHARACTER(LEN=20), SAVE:: zax_name(nb_files_max, nb_zax_max)
34 guez 30
35     ! Informations on each variable
36 guez 62 INTEGER, DIMENSION(nb_files_max, nb_var_max), SAVE:: &
37     name_length, nbopp
38     CHARACTER(LEN=20), DIMENSION(nb_files_max, nb_var_max), SAVE:: &
39     name, unit_name
40     CHARACTER(LEN=80), DIMENSION(nb_files_max, nb_var_max), SAVE:: &
41     title, fullop
42     CHARACTER(LEN=7), SAVE:: topp(nb_files_max, nb_var_max)
43     CHARACTER(LEN=7), SAVE:: sopps(nb_files_max, nb_var_max, nbopp_max)
44     REAL, SAVE:: scal(nb_files_max, nb_var_max, nbopp_max)
45     ! Sizes of the associated grid and zommed area
46     INTEGER, DIMENSION(nb_files_max, nb_var_max, 3), SAVE:: &
47     scsize, zorig, zsize
48     ! Sizes for the data as it goes through the various math operations
49     INTEGER, SAVE:: datasz_in(nb_files_max, nb_var_max, 3) = -1
50 guez 30
51 guez 62 INTEGER, DIMENSION(nb_files_max, nb_var_max), SAVE:: var_haxid, var_zaxid, &
52 guez 178 var_axid
53 guez 30
54 guez 62 REAL, SAVE:: minmax(nb_files_max, nb_var_max, 2)
55 guez 30
56 guez 178 REAL, DIMENSION(nb_files_max, nb_var_max), SAVE:: freq_opp, freq_wrt
57     INTEGER, DIMENSION(nb_files_max, nb_var_max), SAVE:: last_opp, last_wrt, &
58     last_opp_chk, last_wrt_chk, nb_opp, nb_wrt
59 guez 30
60     ! Book keeping for the buffers
61 guez 178 LOGICAL:: zoom(nb_files_max) = .FALSE.
62 guez 30
63     ! Book keeping of the axes
64    
65 guez 62 INTEGER, DIMENSION(nb_files_max, nb_var_max), SAVE:: tdimid, tax_last, &
66     tax_name_length
67     CHARACTER(LEN=40), DIMENSION(nb_files_max, nb_var_max), SAVE:: tax_name
68 guez 30
69     ! A list of functions which require special action
70     ! (Needs to be updated when functions are added
71     ! but they are well located here)
72    
73 guez 62 CHARACTER(LEN=120):: indchfun = 'scatter, fill, gather, coll', &
74     fuchnbout = 'scatter, fill'
75     ! Some configurable variables with locks
76     CHARACTER(LEN=80):: model_name = 'An IPSL model'
77     LOGICAL:: lock_modname = .FALSE.
78 guez 30
79     END MODULE histcom_var

  ViewVC Help
Powered by ViewVC 1.1.21