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

Diff of /trunk/IOIPSL/histcom_var.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

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

Legend:
Removed from v.30  
changed lines
  Added in v.62

  ViewVC Help
Powered by ViewVC 1.1.21