source: trunk/SRC/ToBeReviewed/LECTURE/read_ncdf.pro @ 333

Last change on this file since 333 was 333, checked in by smasson, 16 years ago

bugfix when missing_value = 0.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 17.3 KB
Line 
1;+
2;
3; @file_comments
4; Reading function for the file net_cdf.
5; This program is less universal than ncdf_lec (it appeal to declared
6; variables in common.pro) but it is very easier to be used. It considerate
7; the declaration of the different zooms which have been defined
8; (ixminmesh...premierx...), the declaration of the variable key_shift...
9; To put it in a nutshell, the result of read_ncdf can be directly used in plt...
10; This is also this program which is used by default in our reading widgets.
11;
12; @categories
13; Reading
14;
15; @param NAME {in}{required}{type=string}
16; It define the field to be read.
17;
18; @param BEGINNING {in}{required}
19; Relative with the time axis.
20; These can be
21;  - 2 date of the  type yyyymmdd and in this case, we select dates
22;  which are included between these two dates.
23;  - 2 indexes which define between which and which time step we have
24;  to extract the temporal dimension.
25;
26; @param ENDING  {in}{required}
27; Relative with the time axis.
28; See BEGINNING.
29;
30; @param COMPATIBILITY {in}{optional}
31; Useless, defined for compatibility
32;
33; @keyword ADDSCL_BEFORE {default=0}{type=scalar: 0 or 1}
34; put 1 to apply add_offset ad scale factor on data before looking for
35; missing values
36;
37; @keyword BOXZOOM
38; Contain the boxzoom on which we have to do the reading
39;
40; @keyword CALLITSELF {default=0}{type=scalar: 0 or 1}
41; For ROMS outputs. Use by read_ncdf itself to access auxilliary data (h and zeta).
42;
43; @keyword DIREC
44; a string used to specify the direction along which we want to make
45; spatial and/or temporal mean. It could be: 'x' 'y' 'z' 't' 'xy' 'xz'
46; 'yz' 'xyz' 'xt' 'yt' 'zt' 'xyt' 'xzt' 'yzt' or 'xyzt'
47;
48; @keyword FILENAME {required}{type=string}
49; It contains the file's name.
50;
51; @keyword INIT {default=0}{type=scalar: 0 or 1}
52; To call automatically <pro>initncdf</pro> with filename as input argument
53; and thus ; redefine all the grid parameters
54;
55; @keyword GRID
56; ='[UTVWF]' to specify the type of grid. Default is (1)
57; based on the name of the file if the file ends by
58; GRID[._][TUVFW].NC (not case sensible) or (2) T if case (1)
59; is not found.
60;
61; @keyword TIMESTEP {default=0}{type=scalar: 0 or 1}
62; Specify that BEGINNING and ENDING refer to indexes of the time axis and not to dates
63;
64; @keyword TOUT {default=0}{type=scalar: 0 or 1}
65; We activate it if we want to read the file on the whole domain without
66; considerate the sub-domain defined by the boxzoom or
67; lon1,lon2,lat1,lat2,vert1,vert2.
68;
69; @keyword NOSTRUCT {default=0}{type=scalar: 0 or 1}
70; We activate it if we do not want that read_ncdf send back a structure
71; but only the array referring to the field.
72;
73; @keyword ZETAFILENAME {default=FILENAME}{type=string}
74; For ROMS outputs. The filename of the file where zeta variable should be read
75;
76; @keyword ZETAZERO {default=0}{type=scalar: 0 or 1}
77; For ROMS outputs. To define zeta to 0. instead of reading it
78;
79; @keyword _EXTRA
80; Used to pass keywords to <pro>isafile</pro>, <pro>initncdf</pro>,
81; <pro>ncdf_gettime</pro> and <pro>domdef</pro>
82;
83; @returns
84; Structure readable by <pro>litchamp</pro> or an array if NOSTRUCT is activated.
85; @uses
86; common.pro
87;
88; @restrictions
89; The field must have a temporal dimension.
90;
91; @history
92; Sebastien Masson (smasson\@lodyc.jussieu.fr)
93;                      15/10/1999
94;
95; @version
96; $Id$
97;
98;-
99FUNCTION read_ncdf, name, beginning, ending, compatibility $
100                  , BOXZOOM=boxzoom, FILENAME=filename $
101                  , PARENTIN=parentin, TIMESTEP=timestep $
102                  , ADDSCL_BEFORE=addscl_before $
103                  , TOUT=tout, NOSTRUCT=nostruct, CONT_NOFILL=CONT_NOFILL, INIT=init $
104                  , GRID=grid, CALLITSELF=callitself, DIREC=direc $
105                  , ZETAFILENAME=zetafilename, ZETAZERO=zetazero $
106                  , _EXTRA=ex
107;
108  compile_opt idl2, strictarrsubs
109;
110@cm_4mesh
111@cm_4data
112@cm_4cal
113  IF NOT keyword_set(key_forgetold) THEN BEGIN
114@updatenew
115@updatekwd
116  ENDIF
117;------------------------------------------------------------
118; we find the filename.
119;------------------------------------------------------------
120;  print,filename
121; is parent a valid widget ?
122  IF keyword_set(parentin) THEN BEGIN
123    parent = long(parentin)
124    parent = parent*widget_info(parent, /managed)
125  ENDIF
126  filename = isafile(filename = filename, IODIRECTORY = iodir, _EXTRA = ex)
127;------------------------------------------------------------
128; Opening of the name file
129;------------------------------------------------------------
130  IF size(filename, /type) NE 7 THEN $
131    return, report('read_ncdf cancelled')
132  IF !version.OS_FAMILY EQ 'unix' THEN spawn, '\file '+filename+' > /dev/null'
133  cdfid = ncdf_open(filename)
134  inq = ncdf_inquire(cdfid)
135;------------------------------------------------------------
136; we check if the variable name exists in the file.
137;------------------------------------------------------------
138  IF ncdf_varid(cdfid, name) EQ -1 THEN BEGIN
139    ncdf_close, cdfid
140    return, report('variable '+name+' !C not found in the file '+filename)
141  ENDIF
142  varinq = ncdf_varinq(cdfid, name)
143  IF varinq.ndims LT 2 THEN return, report('read_ncdf cannot read scalar or 1D data')
144; look for the dimension names
145  dimnames = strarr(varinq.ndims)
146  FOR i = 0, varinq.ndims-1 DO BEGIN
147    ncdf_diminq, cdfid, varinq.dim[i], tmp, dimsize
148    dimnames[i] = tmp
149  ENDFOR
150;------------------------------------------------------------
151; shall we redefine the grid parameters
152;------------------------------------------------------------
153  IF keyword_set(init) THEN initncdf, filename, _extra = ex
154;------------------------------------------------------------
155; check the time axis and the debut and ending dates
156;------------------------------------------------------------
157  IF n_elements(beginning) EQ 0 THEN BEGIN
158    beginning = 0L
159    timestep = 1L
160  ENDIF
161; define time and jpt
162  CASE 1 OF
163    keyword_set(timestep):BEGIN
164      firsttps = long(beginning[0])
165      IF n_elements(ending) NE 0 THEN lasttps = long(ending[0]) ELSE lasttps = firsttps
166      jpt = lasttps-firsttps+1
167      IF NOT keyword_set(callitself) then time = julday(1, 1, 1) + lindgen(jpt)
168    END
169    keyword_set(parent):BEGIN
170      widget_control, parent, get_uvalue = top_uvalue
171      filelist = extractatt(top_uvalue, 'filelist')
172      IF filelist[0] EQ 'many !' THEN filelist = filename
173      currentfile = (where(filelist EQ filename))[0]
174      time = (*(extractatt(top_uvalue, 'fileparameters'))[currentfile]).time_counter
175      date1 = date2jul(beginning[0])
176      if n_elements(ending) NE 0 then date2 = date2jul(ending[0]) ELSE date2 = date1
177      firsttps = (where(abs(time - date1) LT 0.9d/86400.d))[0]   ; beware of rounding errors...
178      lasttps = (where(abs(time - date2) LT 0.9d/86400.d))[0]
179      jpt = lasttps-firsttps+1
180    END
181    ELSE:BEGIN
182      time = ncdf_gettime(filename, cdfid, caller = 'read_ncdf', err = err, _extra = ex)
183      IF n_elements(err) NE 0 THEN BEGIN
184        dummy = report(err)
185        ncdf_close, cdfid
186        return, -1
187      ENDIF
188; date1
189      date1 = date2jul(beginning[0])
190; date2
191      if n_elements(ending) NE 0 then date2 = date2jul(ending[0]) ELSE date2 = date1
192; firsttps
193      firsttps = where(time GE (date1 - 0.9d/86400.d)) & firsttps = firsttps[0]
194      if firsttps EQ -1 THEN BEGIN
195        ncdf_close, cdfid
196        return, report('date 1: '+strtrim(jul2date(date1), 1)+' is not found in the time axis.')
197      ENDIF
198; lasttps
199      lasttps = where(time LE (date2 + 0.9d/86400.d)) & lasttps = lasttps[n_elements(lasttps)-1]
200      if lasttps EQ -1 THEN BEGIN
201        ncdf_close, cdfid
202        return, report('the time axis has no date before date 2: '+strtrim(jul2date(date2), 1))
203      endif
204      if lasttps LT firsttps then BEGIN
205        ncdf_close, cdfid
206        return, report('the time axis has no dates between date1 and  date 2: '+strtrim(jul2date(date1), 1)+' '+strtrim(jul2date(date2), 1))
207      endif
208      time = time[firsttps:lasttps]
209      jpt = lasttps-firsttps+1
210    END
211  ENDCASE
212;------------------------------------------------------------
213; Name of the grid on which the field refer to.
214;------------------------------------------------------------
215  IF keyword_set(grid) THEN vargrid = strupcase(grid) ELSE BEGIN
216    vargrid = 'T'               ; default definition
217    IF finite(glamu[0]) EQ 1 THEN BEGIN
218; are we in one of the case corresponding to ROMS conventions?
219      CASE 1 OF
220        dimnames[2 <(varinq.ndims-1)] EQ 's_w':vargrid = 'W'
221        dimnames[0] EQ 'xi_rho' AND dimnames[1] EQ 'eta_rho':vargrid = 'T'
222        dimnames[0] EQ 'xi_u'   AND dimnames[1] EQ 'eta_u'  :vargrid = 'U'
223        dimnames[0] EQ 'xi_v'   AND dimnames[1] EQ 'eta_v'  :vargrid = 'V'
224        dimnames[0] EQ 'xi_psi' AND dimnames[1] EQ 'eta_psi':vargrid = 'F'
225        dimnames[0] EQ 'xi_rho' AND dimnames[1] EQ 'eta_v'  :vargrid = 'V'
226        dimnames[0] EQ 'xi_u'   AND dimnames[1] EQ 'eta_rho':vargrid = 'U'
227        dimnames[0] EQ 'xi_u'   AND dimnames[1] EQ 'eta_v'  :vargrid = 'F'
228        ELSE:BEGIN
229; could we define the grid type from the file name??
230          pattern = ['GRID.', 'GRID_', 'GRID', 'UPID_', '30ID_']
231          gdtype = ['T', 'U', 'V', 'W', 'F']
232          fnametest = strupcase(filename)
233          FOR i = 0, n_elements(pattern)-1 DO BEGIN
234            FOR j = 0, n_elements(gdtype)-1 DO BEGIN
235              substr = pattern[i]+gdtype[j]
236              pos = strpos(fnametest, substr)
237              IF pos NE -1 THEN $
238                 vargrid = strmid(fnametest, pos+strlen(substr)-1, 1)
239            ENDFOR
240          ENDFOR
241        END
242      ENDCASE
243     ENDIF
244  ENDELSE
245;---------------------------------------------------------------
246; redefinition of the  domain
247;---------------------------------------------------------------
248  IF keyword_set(tout) THEN BEGIN
249    nx = jpi
250    ny = jpj
251    nz = jpk
252    firstx = 0
253    firsty = 0
254    firstz = 0
255    lastx = jpi-1
256    lasty = jpj-1
257    lastz = jpk-1
258    case strupcase(vargrid) of
259      'T':mask = tmask
260      'U':mask = umask()
261      'V':mask = vmask()
262      'W':mask = tmask
263      'F':mask = fmask()
264    endcase
265  ENDIF ELSE BEGIN
266    if keyword_set(boxzoom) then BEGIN
267      Case 1 Of
268        N_Elements(Boxzoom) Eq 1:bte = [lon1, lon2, lat1, lat2, 0., boxzoom[0]]
269        N_Elements(Boxzoom) Eq 2:bte = [lon1, lon2, lat1, lat2, boxzoom[0], boxzoom[1]]
270        N_Elements(Boxzoom) Eq 4:bte = [Boxzoom, vert1, vert2]
271        N_Elements(Boxzoom) Eq 5:bte = [Boxzoom[0:3], 0, Boxzoom[4]]
272        N_Elements(Boxzoom) Eq 6:bte = Boxzoom
273        Else: BEGIN
274          ncdf_close, cdfid
275          return, report('Wrong Definition of Boxzoom')
276        end
277      ENDCASE
278      savedbox = 1b
279      saveboxparam, 'boxparam4rdncdf.dat'
280      domdef, bte, GRIDTYPE = ['T', vargrid], _extra = ex
281    ENDIF
282    grille, mask, glam, gphi, gdep, nx, ny, nz, firstx, firsty, firstz, lastx, lasty, lastz
283    undefine, glam & undefine, gphi & ; We liberate some memory!
284  ENDELSE
285;---------------------------------------------------------------------
286; We initialize ixmindta, iymindta if needed
287;---------------------------------------------------------------------
288  if n_elements(jpidta) EQ 0 THEN jpidta = jpiglo
289  if n_elements(jpjdta) EQ 0 THEN jpjdta = jpjglo
290  if n_elements(jpkdta) EQ 0 THEN jpkdta = jpkglo
291  if n_elements(ixmindta) EQ 0 THEN ixmindta = 0
292  if n_elements(ixmaxdta) EQ 0 then ixmaxdta = jpidta-1
293  if ixmindta EQ -1 THEN ixmindta = 0
294  IF ixmaxdta EQ -1 then ixmaxdta = jpidta-1
295  if n_elements(iymindta) EQ 0 THEN iymindta = 0
296  IF n_elements(iymaxdta) EQ 0 then iymaxdta = jpjdta-1
297  if iymindta EQ -1 THEN iymindta = 0
298  IF iymaxdta EQ -1 then iymaxdta = jpjdta-1
299  if n_elements(izmindta) EQ 0 THEN izmindta = 0
300  IF n_elements(izmaxdta) EQ 0 then izmaxdta = jpkdta-1
301  if izmindta EQ -1 THEN izmindta = 0
302  IF izmaxdta EQ -1 then izmaxdta = jpkdta-1
303;----------------------------------------------------------------
304; We will read the file
305;---------------------------------------------------------------
306  if n_elements(key_stride) LE 2 then key_stride = [1, 1, 1]
307  key_stride = 1l > long(key_stride)
308;---------------------------------------------------------------------
309;---------------------------------------------------------------------
310@read_ncdf_varget
311;---------------------------------------------------------------------
312;---------------------------------------------------------------------
313; We define common (cm_4data) variables associated with the variable.
314;---------------------------------------------------------------------
315; varname
316  IF NOT keyword_set(callitself) THEN varname = name
317; varunit and others...
318  ncdf_getatt, cdfid, name, add_offset = add_offset, scale_factor = scale_factor, missing_value = missing_value, units = units
319  IF NOT keyword_set(callitself) THEN varunit = units
320; vardate
321; We make a legible date in function of the specified language.
322  year = long(beginning[0])/10000
323  month = (long(beginning[0])/100) MOD 100
324  day = (long(beginning[0]) MOD 100)
325  vardate = string(format = '(C(CMoA))', 31*(month-1))+' '+strtrim(day, 1)+', '+strtrim(year, 1)
326  varexp = file_basename(filename)
327
328; We apply the value valmask on land points.
329  if NOT keyword_set(cont_nofill) then begin
330    valmask = 1.e20
331    case 1 of
332      varinq.ndims eq 2:                                               earth = where(mask[*, *, 0] EQ 0) ;xy   array
333      varinq.ndims eq 3 AND (where(varinq.dim EQ inq.recdim))[0] EQ -1:earth = where(mask EQ 0)          ;xyz  array
334      varinq.ndims eq 3 AND (where(varinq.dim EQ inq.recdim))[0] NE -1:earth = where(mask[*, *, 0] EQ 0) ;xyt  array   
335      varinq.ndims eq 4:                                               earth = where(mask EQ 0)          ;xyzt array
336    ENDCASE
337  ENDIF ELSE earth = -1
338; we look for  missing_value
339; we apply add_offset, scale_factor and missing_value
340  IF keyword_set(addscl_before) THEN BEGIN
341    IF scale_factor NE 1 THEN res = temporary(res)*scale_factor
342    IF add_offset   NE 0 THEN res = temporary(res)+add_offset
343  ENDIF
344  IF size(missing_value, /type) NE 7 THEN BEGIN
345    IF finite(missing_value) EQ 1 THEN BEGIN
346        CASE 1 OF
347          missing_value GT 1.e6:missing = where(res GT missing_value/10.)
348          missing_value LT -1.e6:missing = where(res LT missing_value/10.)
349          abs(missing_value) LT 1.e-6:missing = where(abs(res) LT 1.e-6)
350          ELSE:missing = where(res EQ missing_value)
351        ENDCASE
352    ENDIF ELSE missing = where(finite(res) EQ 0)
353  ENDIF ELSE missing = -1
354  IF NOT keyword_set(addscl_before) THEN BEGIN
355    if scale_factor NE 1 then res = temporary(res)*scale_factor
356    if add_offset NE 0 then res = temporary(res)+add_offset
357  ENDIF
358  IF missing[0] NE -1 THEN res[temporary(missing)] = !values.f_nan
359  IF earth[0] NE -1 THEN BEGIN
360    IF varinq.ndims eq 3 AND (where(varinq.dim EQ inq.recdim))[0] NE -1 THEN $   ;xyt array   
361       earth = earth#replicate(1, jpt)+replicate(nx*ny, n_elements(earth))#lindgen(jpt)
362    IF varinq.ndims eq 4 THEN earth = earth#replicate(1, jpt)+replicate(nx*ny*nz, n_elements(earth))#lindgen(jpt)
363    res[temporary(earth)] = 1.e20
364  ENDIF
365;---------------------------------------------------------------------
366; if it is roms outputs, we need to get additionals infos...
367  IF NOT keyword_set(callitself) THEN BEGIN
368    IF strmid(dimnames[0], 0, 3) EQ 'xi_' AND strmid(dimnames[1], 0, 4) EQ 'eta_' THEN BEGIN
369      ncdf_attget, cdfid, 'theta_s', theta_s, /global
370      ncdf_attget, cdfid, 'theta_b', theta_b, /global
371      ncdf_attget, cdfid, 'hc', hc, /global
372; look for all variables names
373      allvarnames = strarr(inq.nvars)
374      FOR i = 0, inq.nvars-1 DO BEGIN
375        tmp = ncdf_varinq( cdfid, i)
376        allvarnames[i] = tmp.name
377      ENDFOR
378      CASE 1 OF
379        keyword_set(zetazero):zeta = fltarr(nx, ny, jpt)
380        keyword_set(zetafilename):  $
381           zeta = read_ncdf('zeta', firsttps, lasttps, FILENAME = zetafilename $
382                            , /TIMESTEP, /NOSTRUCT, CONT_NOFILL = CONT_NOFILL $
383                            , GRID = vargrid, /CALLITSELF, _EXTRA = ex)
384        (where(allvarnames EQ 'zeta'))[0] NE -1: $
385           zeta = read_ncdf('zeta', firsttps, lasttps, FILENAME = filename $
386                            , /TIMESTEP, /NOSTRUCT, CONT_NOFILL = CONT_NOFILL $
387                            , GRID = vargrid, /CALLITSELF, _EXTRA = ex)
388        ELSE:return, report('The variable zeta was not found in the file, please use the keyword ZETAFILENAME to specify the name of a file containing zeta or use  keyword ZETAZERO to define zeta to 0.')
389      ENDCASE
390      romszinfos = {h:romszinfos.h, zeta:temporary(zeta), theta_s:theta_s, theta_b:theta_b, hc:hc}
391    ENDIF ELSE romszinfos = {h:-1, zeta:-1, theta_s:-1, theta_b:-1, hc:-1}
392  ENDIF
393;---------------------------------------------------------------------
394  IF keyword_set(direc) THEN BEGIN
395    IF jpt EQ 1 THEN res = moyenne(temporary(res), direc, _extra = ex) $
396    ELSE BEGIN
397      res = grossemoyenne(temporary(res), direc, _extra = ex)
398      IF ( strpos(strlowcase(direc), 't') ge 0 ) THEN BEGIN
399        vardate = strtrim(jul2date(time[0]), 1)+' - '+strtrim(jul2date(time[jpt-1]), 1)
400        time = total(time)/float(jpt)
401        jpt = 1
402      ENDIF
403    ENDELSE
404  ENDIF
405;---------------------------------------------------------------------
406  ncdf_close, cdfid
407
408  IF keyword_set(savedbox) THEN restoreboxparam, 'boxparam4rdncdf.dat'
409
410  IF keyword_set(nostruct) THEN return, res
411  IF keyword_set(key_forgetold) THEN BEGIN
412    return, {arr:temporary(res), grid:vargrid, unit:varunit, experiment:varexp, name:varname}
413  ENDIF ELSE BEGIN
414    return, {tab:temporary(res), grille:vargrid, unite:varunit, experience:varexp, nom:varname}
415  ENDELSE
416
417END
Note: See TracBrowser for help on using the repository browser.