source: trunk/rseries_ncdf.pro

Last change on this file was 48, checked in by pinsard, 10 years ago

fix thanks to coding rules

  • Property svn:keyword set to Id
File size: 10.9 KB
Line 
1;+
2;
3; @file_comments
4; reading timeseries writing on many files
5;
6; @categories
7; Reading
8;
9; @param var {in} {type=string}
10; the name of the variable to be read
11;
12; @param date1 {in} {type=scalar}
13; give the first date of the time series.
14; Date format is ymmdd, yymmdd, yyymmdd, yyyymmdd, yyyyymmdd, yyyyyymmdd.
15;
16; @param date2  {in} {type=scalar}
17; give the last date of the time series.
18; Date format is ymmdd, yymmdd, yyymmdd, yyyymmdd, yyyyymmdd, yyyyyymmdd.
19;
20; @param expin {in} {type=string} {default=varexp}
21; the name of the experiment.
22;
23; @param freqin {in} {type=string} {default='5d'}
24; the averaging frequency.
25;
26; @keyword CENTURY {type=integer}
27; give the true century of the calendar.
28; for example if filename is AA5_5d_920101_921231* and the calendar variable
29; in the file is 19920101 to 19921231 then CENTURY=19
30;
31; @keyword NOSTRUCT {default=1}
32; Set this keyword to return an array instead of a structure.
33;
34; @keyword GRIDTYPE
35; name of the grid to be read 'grid_T' ++'gridT'
36;
37; @keyword _EXTRA
38; Used to pass read_ncdf keywords
39;
40; @returns
41; a structure with the following Structure Tags:
42;  arr:the array output
43;  grid: the array grid
44;  units: the array units
45;  experiment: the name of the experiment
46;  name: the name of the variable
47;
48; @uses
49; <pro>common</pro>
50;
51; @restrictions
52; Update the time and jpt common variables.
53; Time is the calendar in IDL julian days.
54; 1) The file must contain an unlimited dimension, and the
55; variable to be read must contain this unlimited dimension.
56; 2) The file must contain a one dimension variable which
57; dimension is the unlimited dimension. This variable is the
58; calendar.
59; 3) This variable calendar must have an attribut called "units"
60; which must have a format similar to
61; "seconds since 0001-01-01 00:00:00"
62; "hours since 0001-01-01 00:00:00"
63; "days since 1979-01-01 00:00:00"
64; "months since 1979-01-01 00:00:00"
65; "years since 1979-01-01 00:00:00"
66; 4) The calendar must be the Gregorian calendar
67; 5) The name of the file must beginning by
68; exp_freq_datefirst_datelast_*
69; 6) The maximum gap between 2 consecutive files must be one day.
70;
71; @examples
72; IDL> res = rseries_ncdf('sozotaux',920501,930410,'AA5','5d')
73;
74; for ORCA2 outputs
75; IDL> iodir='/usr/work/sur/fvi/OPA/ORCA2/'
76; IDL> res= rseries_ncdf('votemper',010101,061231,'ESS','5d')
77; IDL> help,res,/structure
78;
79;** Structure <310ebc0>, 5 tags, length=1800, data length=1800, refs=1:
80;   ARR             FLOAT     Array[1, 1, 1, 438]
81;   GRID            STRING    'T'
82;   UNITS           STRING    'C'
83;   EXPERIMENT      STRING    'ESS_5d_060101_061231_grid_T.nc'
84;   NAME            STRING    'votemper'
85;
86; @history
87; Sebastien Masson (smasson\@lodyc.jussieu.fr) Apr 23 2001
88;
89; @todo
90; adaptation to Drakkar terminologie
91; ORCA2 terminology of output files
92; <i>experience</i>_5d_<i>yymmdd</i>_<i>yymmdd</i>_<i>grid</i>.nc
93; with experience in 'ESS'
94; with grid in 'grid_T'
95;
96; ORCA025 terminology of output files
97; /u/rech/cli/rcli002/ORCA025/ORCA025-<i>experience_drakkar<i>-S/<i>year_drakkar</i>/ORCA025-<i>experience_drakkar</i>-y<i>year_drakkar</i>n<i>mois</i>d<i>jour</i>_<i>grid</i>.nc
98; with experience_drakkar in 'G70',
99; with grid in 'gridT'
100;
101; @version
102; $Id$
103;
104;-
105FUNCTION rseries_ncdf, var, date1, date2, expin, freqin, CENTURY = century, NOSTRUCT = nostruct, GRIDTYPE = gridtype, _EXTRA = ex
106@common
107; name of the file: exp_freq_datefirst_datelast_*
108  date1 = (long(date1))[0]
109  date2 = (long(date2))[0]
110  if date2 LT date1 then return, report('date2 must be larger than date1')
111  if n_elements(expin) EQ 0 then exp = varexp ELSE BEGIN
112    IF (strpos(expin, '_'))[0] NE -1 AND n_elements(freqin) EQ 0 THEN BEGIN
113      exp = strmid(expin, 0, strpos(expin, '_'))
114      freqin = strmid(expin, strpos(expin, '_')+1)
115    ENDIF ELSE exp = expin
116    varexp = exp
117  ENDELSE
118  if n_elements(freqin) EQ 0 then freq = '5d' ELSE freq = freqin
119;------------------------------------------------
120; determination of the filename beginning with exp_freq_*
121;------------------------------------------------
122  IF keyword_set(gridtype) EQ 0 THEN gridtype = ''
123; determination OF datefirst and datelast
124; list of the files beginning by iodir+exp+sep+freq
125  sep = '_'
126  possiblenames = iodir+exp+sep+freq+'*'+gridtype+'.nc'
127  possiblenames = findfile(possiblenames)
128  if possiblenames[0] EQ '' then return, report('nofilename :'+iodir+exp+sep+freq+'*'+gridtype+'.nc'+' found')
129  npos = n_elements(possiblenames)
130; list of the datefirst and datelast of the files beginning by
131; iodir+exp+sep+freq
132  datefirst = lonarr(npos)
133  datelast = lonarr(npos)
134  sepshift = n_elements(str_sep(exp, sep))-1
135  for i = 0, npos-1 do BEGIN
136    separate = str_sep(possiblenames[i], sep)
137    datefirst[i] = separate[2+sepshift]
138    datelast[i] = separate[3+sepshift]
139  ENDFOR
140; selection of the files for which datefirst le date1 and datelast ge
141; date1
142  CASE strmid(freqin, 0, 1, /rever) OF
143    'm' : div = 100
144    'y' : div = 10000
145    ELSE : div = 1
146  ENDCASE
147  goodfile = where(datefirst le date1/div and datelast GE date1/div)
148  if goodfile[0] EQ -1 then return, report('filename :'+iodir+exp+sep+freq+'*'+gridtype+'.nc'+' not found with the dates containing '+strtrim(date1, 1))
149  datefirst = datefirst[goodfile]
150  datelast = datelast[goodfile]
151; how many different pairs of dates are present ?
152; find the unique pairs of dates
153  pairofdate = dcomplex(datefirst, datelast)
154  pairofdate = pairofdate[uniq(pairofdate, sort(pairofdate))]
155  fileok = ''
156  datefirstok = 0L
157  datelastok = 0L
158; loop on the files for which date1 is between datefirst and datelast
159  for p = 0, n_elements(pairofdate)-1 do begin
160; name of the file: exp_freq_datefirst_datelast_*
161    datefirst = long(pairofdate[p])
162    datelast = long(imaginary(pairofdate[p]))
163; determination OF the possible filenames
164; test if the year format is i1, i2, i3, i4, i5 or i6
165    namebegin = iodir+exp+sep+freq+sep+strtrim(datefirst, 1)+sep+strtrim(datelast, 1)+'*'+gridtype+'.nc'
166    namebegin = findfile(namebegin)
167    possiblenames = ''
168    if namebegin[0] NE '' then possiblenames = [possiblenames, namebegin]
169    if datefirst LT 1e9 then begin
170      for i = 1, 5-(datefirst GE 1e5)-(datefirst GE 1e6) $
171        -(datefirst GE 1e7)-(datefirst GE 1e8) do begin
172        zero = string(replicate(byte('0'), i))
173        namebegin = iodir+exp+sep+freq+sep $
174          + zero+strtrim(datefirst, 1) +sep+ zero+strtrim(datelast, 1) +'*'+gridtype+'.nc'
175        namebegin = findfile(namebegin)
176        if namebegin[0] NE '' then possiblenames = [possiblenames, namebegin]
177      endfor
178    ENDIF
179    if n_elements(possiblenames) eq 1 then return, report('filename :'+iodir+exp+sep+freq+sep+'*'+strtrim(datefirst, 1)+sep+'*'+strtrim(datelast, 1)+'*'+gridtype+'.nc'+' not found')
180    possiblenames = possiblenames[1:n_elements(possiblenames)-1]
181; determination OF the filenames
182    ncdf_control, 0, /noverbose
183    i = 0
184    repeat BEGIN
185      cdfid = ncdf_open(possiblenames[i])
186;         print,possiblenames[i],var
187      test = ncdf_varid(Cdfid, var)
188      ncdf_close, cdfid
189      i = i+1
190    endrep until test NE -1 OR i EQ n_elements(possiblenames)
191    ncdf_control, 0, /verbose
192    if test NE -1 then begin
193      fileok = [fileok, possiblenames[i-1]]
194      datefirstok = [datefirstok, datefirst]
195      datelastok = [datelastok, datelast]
196    endif
197  ENDFOR
198  numoffileok = n_elements(fileok)-1
199  if numoffileok EQ 0 then return, report('the variable '+var+' was not fond in the file: '+possiblenames)
200  fileok = fileok[1:numoffileok]
201  datefirstok = datefirstok[1: numoffileok]
202  datelastok = datelastok[1: numoffileok]
203  if numoffileok NE 1 then BEGIN
204; more than one file containts the variable var and has the date1
205; between datefirst and datelast...
206; Is there any file FOR which date2 LE datelast?
207    goodfile = where(date2 LE datelastok)
208    if goodfile[0] NE -1 then begin
209      fileok = fileok[goodfile]
210      datefirstok = datefirstok[goodfile]
211      datelastok = datelastok[goodfile]
212; we choose the file which has the smallest datelast
213      bestfile = sort(datelastok)
214      filename = fileok[bestfile[0]]
215      datefirst = datefirstok[bestfile[0]]
216      datelast = datelastok[bestfile[0]]
217    ENDIF ELSE BEGIN
218; we choose the file which has the bigest datelast
219      bestfile = sort(datelastok)
220      filename = fileok[bestfile[numoffileok-1]]
221      datefirst = datefirstok[bestfile[numoffileok-1]]
222      datelast = datelastok[bestfile[numoffileok-1]]
223    ENDELSE
224  ENDIF ELSE BEGIN
225    filename = fileok[0]
226    datefirst = datefirstok[0]
227    datelast = datelastok[0]
228  ENDELSE
229; now we have find the good file with the good dates and the godd
230; variable inside.
231; we get the number of dimension of the variable
232  cdfid = ncdf_open(filename)
233  varcontient = ncdf_varinq(cdfid, var)
234  ncdf_close, cdfid
235;
236;------------------------------------------------
237; reading of the variables
238;------------------------------------------------
239;
240  if NOT keyword_set(century) then century = 0l
241  IF chkstru(ex, 'filename') THEN ex.filename = filename
242  CASE strmid(freqin, 0, 1, /rever) OF
243    'm':datelast = 100*datelast + daysinmonth(datelast MOD 100, datelast / 100)
244    'y':div = 10000*datelast+360+(5+leapyr(datelast+century))*(key_caltype EQ 'greg')
245    ELSE : div = 1
246  ENDCASE
247  if date2 GT datelast THEN BEGIN
248; if we need to read more than one file,
249; first we read the first file
250;++    print,var,date1+century*1000000L, datelast[0]+century*1000000L
251;++READ, B, PROMPT='Enter Name: '
252    res1 = read_ncdf(var, date1+century*1000000L, datelast[0]+century*1000000L $
253                     , filename = filename, /nostruct, _extra = ex)
254    time1 = time                ; store the first part of the calendar
255    jpt1 = jpt                  ; store the number time steps already read
256
257; and after we call again rseries_ncdf
258; newdatefirst is defined as datelast+1day
259    newdatefirst = jul2date(date2jul(datelast)+1)
260    res2 = rseries_ncdf(var, newdatefirst, date2, exp, freq, /NOSTRUCT, _extra = ex)
261;
262;
263    CASE 1 OF
264      res1[0] EQ -1 AND res2[0] EQ -1: return, -1
265      res1[0] EQ -1:res = temporary(res2)
266      res2[0] EQ -1:BEGIN
267        time = time1
268        jpt = jpt1
269        res = temporary(res1)
270      END
271      ELSE : BEGIN
272 ; we glue the result of the first read and the result of the new call
273; to rseries_ncdf
274        time = [time1, time]
275        jpt = jpt1+jpt
276        case varcontient.ndims OF
277          1:res = [temporary(res1), temporary(res2)]
278          2:res = [ [temporary(res1)], [temporary(res2)] ]
279          3:res = [ [ [temporary(res1)] ], [ [temporary(res2)] ] ]
280          4:BEGIN
281            res = [(temporary(res1))[*], (temporary(res2))[*]]
282            grille, mask, glam, gphi, gdep, nx, ny, nz
283            res = reform(res, nx, ny, nz, jpt, /over)
284          END
285        ENDCASE
286      ENDELSE
287    ENDCASE
288  endif ELSE BEGIN
289    res = read_ncdf(var, date1+century*1000000L, date2+century*1000000L $
290                    , filename = filename, /nostruct, _extra = ex)
291  ENDELSE
292;------------------------------------------------
293  if keyword_set(nostruct) then return, res $
294  ELSE return, {arr:res, grid:vargrid, units:varunit, experiment:varexp, name:varname}
295
296end
Note: See TracBrowser for help on using the repository browser.