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

Contents of /trunk/IOIPSL/histcom_var.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 62 - (show annotations)
Thu Jul 26 14:37:37 2012 UTC (11 years, 9 months ago) by guez
Original Path: trunk/libf/IOIPSL/histcom_var.f90
File size: 3048 byte(s)
Changed handling of compiler in compilation system.

Removed the prefix letters "y", "p", "t" or "z" in some names of variables.

Replaced calls to NetCDF by calls to NetCDF95.

Extracted "ioget_calendar" procedures from "calendar.f90" into a
separate file.

Extracted to a separate file, "mathop2.f90", procedures that were not
part of the generic interface "mathop" in "mathop.f90".

Removed computation of "dq" in "bilan_dyn", which was not used.

In "iniadvtrac", removed schemes 20 Slopes and 30 Prather. Was not
compatible with declarations of array sizes.

In "clcdrag", "ustarhb", "vdif_kcay", "yamada4" and "coefkz", changed
the size of some arrays from "klon" to "knon".

Removed possible call to "conema3" in "physiq".

Removed unused argument "cd" in "yamada".

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

  ViewVC Help
Powered by ViewVC 1.1.21