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

Contents of /trunk/libf/IOIPSL/histcom_var.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 30 - (show annotations)
Thu Apr 1 09:07:28 2010 UTC (14 years, 2 months ago) by guez
File size: 3271 byte(s)
Imported Source files of the external library "IOIPSL_Lionel" into
"libf/IOIPSL".

Split "cray.f90" into "scopy.f90" and "ssum.f90".

Rewrote "leapfrog" in order to have a clearer algorithmic structure.

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

  ViewVC Help
Powered by ViewVC 1.1.21