/[lmdze]/trunk/IOIPSL/Histcom/histbeg_totreg.f90
ViewVC logotype

Contents of /trunk/IOIPSL/Histcom/histbeg_totreg.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 335 - (show annotations)
Thu Sep 12 21:22:46 2019 UTC (4 years, 8 months ago) by guez
File size: 5693 byte(s)
Julian dates be in double precision

`ConfigureCompilerFlags.cmake` and `TAGS.cmake` are now copied into
LMDZE, to avoid dependency on the environment.

Julian dates must be in double precision, to get time step precision.

Add optional attribute to argument sec of procedure ju2ymds. We do
not need sec in procedure dynredem0.

In procedure ju2ymds, by construction, sec cannot be > `un_jour`.

Remove useless intermediary variables in procedure ymds2ju.

1 MODULE histbeg_totreg_m
2
3 ! From histcom.f90, version 2.1 2004/04/21 09:27:10
4
5 ! Some confusing vocabulary in this code!
6
7 ! A regular grid is a grid with i, j indices and thus it is
8 ! stored in a 2D matrix. This is opposed to an irregular grid which
9 ! is in a vector and where we do not know which neighbours we
10 ! have. As a consequence we need the bounds for each grid-cell.
11
12 ! A rectilinear grid is a special case of a regular grid in which
13 ! all longitudes for i constant are equal and all latitudes for j
14 ! constant are equal. In other words we do not need the full 2D
15 ! matrix to describe the grid, just two vectors.
16
17 USE histcom_var, only: nb_files_max
18
19 IMPLICIT NONE
20
21 INTEGER:: nb_files = 0
22 double precision, SAVE:: date0(nb_files_max)
23 REAL, SAVE:: deltat(nb_files_max)
24 LOGICAL:: regular(nb_files_max) = .TRUE.
25
26 private nb_files_max
27
28 CONTAINS
29
30 SUBROUTINE histbeg_totreg(filename, lon_1d, lat_1d, orix, szx, oriy, szy, &
31 pitau0, pdate0, pdeltat, horiid, fileid)
32
33 ! We assume the grid is rectilinear. The user provides "lon_1d"
34 ! and "lat_1d" as vectors. This subroutine initializes a NetCDF
35 ! file and returns the ID. It sets up the geographical space on
36 ! which the data will be stored and offers the possibility of
37 ! setting a zoom. It also gets the global parameters into the
38 ! input-output subsystem.
39
40 USE errioipsl, ONLY: histerr
41 USE histcom_var, ONLY: assc_file, full_size, itau0, lock_modname, &
42 model_name, nb_hax, nb_tax, nb_var, nb_zax, ncdf_ids, slab_ori, &
43 slab_sz, xid, yid, zoom
44 use histhori_regular_m, only: histhori_regular
45 USE netcdf, ONLY: nf90_clobber, nf90_global
46 use netcdf95, only: nf95_create, nf95_def_dim, nf95_put_att
47
48 CHARACTER(len=*), INTENT(IN):: filename
49 ! name of the netcdf file to be created
50
51 REAL, INTENT(IN):: lon_1d(:) ! coordinates of points in longitude
52 REAL, INTENT(IN):: lat_1d(:) ! coordinates of points in latitude
53
54 ! The next 4 arguments allow to define a horizontal zoom for this
55 ! file. It is assumed that all variables to come have the same
56 ! index space. This can not be assumed for the z axis and thus we
57 ! define the zoom in histdef.
58 INTEGER, INTENT(IN):: orix ! origin of the slab of data within the X axis
59 INTEGER, INTENT(IN):: szx ! size of the slab of data in X
60 INTEGER, INTENT(IN):: oriy ! origin of the slab of data within the Y axis
61 INTEGER, INTENT(IN):: szy ! size of the slab of data in Y
62
63 INTEGER, INTENT(IN):: pitau0 ! time step at which the history tape starts
64 double precision, INTENT(IN):: pdate0 ! the Julian date at which the itau was equal to 0
65 REAL, INTENT(IN):: pdeltat ! time step of the counter itau, in seconds
66
67 INTEGER, INTENT(OUT):: horiid ! ID of the horizontal grid
68 INTEGER, INTENT(OUT):: fileid ! ID of the netcdf file
69
70 ! Variables local to the procedure:
71 REAL, DIMENSION(size(lon_1d), size(lat_1d)):: lon, lat
72 INTEGER im ! size of arrays in longitude direction
73 integer jm ! size of arrays in latitude direction
74 INTEGER ncid
75 INTEGER lengf, lenga
76 CHARACTER(len=120) file
77
78 !---------------------------------------------------------------------
79
80 im = size(lon_1d)
81 jm = size(lat_1d)
82
83 lon = spread(lon_1d, 2, jm)
84 lat = spread(lat_1d, 1, im)
85
86 nb_files = nb_files + 1
87 fileid = nb_files
88
89 ! 1. Transfer into module variables for future use
90
91 itau0(fileid) = pitau0
92 date0(fileid) = pdate0
93 deltat(fileid) = pdeltat
94
95 ! 2. Initialize all variables for this file
96
97 IF (nb_files > nb_files_max) CALL histerr(3, 'histbeg', &
98 'Table of files too small. You should increase nb_files_max', &
99 'in M_HISTCOM.f90 in order to accomodate all these files', ' ')
100
101 nb_var(fileid) = 0
102 nb_tax(fileid) = 0
103 nb_hax(fileid) = 0
104 nb_zax(fileid) = 0
105
106 slab_ori(fileid, :) = (/orix, oriy/)
107 slab_sz(fileid, :) = (/szx, szy/)
108
109 ! 3. Open NetCDF file and define dimensions
110
111 lengf = len_trim(filename)
112 IF (filename(lengf-2:lengf)/='.nc') THEN
113 file = filename(:lengf) // '.nc'
114 ELSE
115 file = filename(:lengf)
116 END IF
117
118 ! Keep track of the name of the files opened
119
120 lengf = len_trim(file)
121 lenga = len_trim(assc_file)
122 IF (nb_files==1) THEN
123 assc_file = file(:lengf)
124 ELSE IF ((lenga+lengf)<500) THEN
125 assc_file = assc_file(:lenga) // ' ' // file(:lengf)
126 ELSE IF (lenga + 7 < 500 .AND. index(assc_file(:lenga), 'et.al.') < 1) THEN
127 assc_file = assc_file(:lenga) // ' et.al.'
128 ELSE
129 CALL histerr(2, 'histbeg', &
130 'The file names do not fit into the associate_file attribute.', &
131 'Use shorter names if you wish to keep the information.', ' ')
132 END IF
133
134 call nf95_create(file, nf90_clobber, ncid)
135 call nf95_def_dim(ncid, 'lon', szx, xid(nb_files))
136 call nf95_def_dim(ncid, 'lat', szy, yid(nb_files))
137
138 ! 4. Declare the geographical coordinates and other attributes
139
140 ! 4.3 Global attributes
141
142 call nf95_put_att(ncid, nf90_global, 'Conventions', 'GDT 1.3')
143 call nf95_put_att(ncid, nf90_global, 'file_name', trim(file))
144 call nf95_put_att(ncid, nf90_global, 'production', trim(model_name))
145 lock_modname = .TRUE.
146
147 ! 5. Save some important information on this file in the module variables
148 ncdf_ids(fileid) = ncid
149 full_size(fileid, :) = (/im, jm/)
150
151 ! 6. Store the geographical coordinates
152
153 IF ((im /= szx) .OR. (jm /= szy)) zoom(fileid) = .TRUE.
154 regular(fileid) = .TRUE.
155
156 CALL histhori_regular(fileid, im, lon, jm, lat, ' ', 'Default grid', horiid)
157
158 END SUBROUTINE histbeg_totreg
159
160 end MODULE histbeg_totreg_m

  ViewVC Help
Powered by ViewVC 1.1.21