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

Last change on this file since 209 was 209, checked in by smasson, 17 years ago

bugfix + introduce C grid based on F, U and V points

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 24.6 KB
Line 
1;+
2; @file_comments
3; Reading function for the file net_cdf.
4; This program is less universal than ncdf_lec (it appeal to declared
5; variables in common.pro) but it is very easier to be used. It considerate
6; the declaration of the different zooms which have been defined
7; (ixminmesh...premierx...), the declaration of the variable key_shift...
8; To put it in a nutshell, the result of read_ncdf can be directly used in plt...
9; This is also this program which is used by default in our reading widgets. 
10;
11; @categories
12; Reading
13;
14; @param NAME {in}{required}{type=string}
15; It define the field to be read.
16;
17; @param BEGINNING {in}{required}
18; Relative with the time axis.
19; These can be
20;  - 2 date of the  type yyyymmdd and in this case, we select dates
21;  which are included between these two dates.
22;  - 2 indexes which define between which and which time step we have
23;  to extract the temporal dimension.
24;
25; @param ENDING  {in}{required}
26; Relative with the time axis.
27; See BEGINNING.
28;
29; @param COMPATIBILITY {in}{optional}
30; Useless, defined for compatibility
31
32; @keyword BOXZOOM
33; Contain the boxzoom on which we have to do the reading
34;
35; @keyword CALLITSELF {default=0}{type=scalar: 0 or 1}
36; For ROMS outputs. Use by read_ncdf itself to access auxilliary data (h and zeta).
37;
38; @keyword FILENAME {required}{type=string}
39; It contains he file's name.
40;
41; @keyword INIT {default=0}{type=scalar: 0 or 1}
42; To call automatically initncdf, filename and thus
43; redefine all the grid parameters
44;
45; @keyword GRID
46; ='[UTVWF]' to specify the type of grid. Default is (1)
47; based on the name of the file if the file ends by
48; GRID[._][TUVFW].NC (not case sensible) or (2) T if case (1)
49; is not found.
50;
51; @keyword TIMESTEP {default=0}{type=scalar: 0 or 1}
52; Specify that BEGINNING and ENDING refer to indexes of the time axis and not to dates
53;
54; @keyword TOUT {default=0}{type=scalar: 0 or 1}
55; We activate it if we want to read the file on the whole domain without
56; considerate the sub-domain defined by the boxzoom or
57; lon1,lon2,lat1,lat2,vert1,vert2.
58;
59; @keyword NOSTRUCT {default=0}{type=scalar: 0 or 1}
60; We activate it if we do not want that read_ncdf send back a structure
61; but only the array referring to the field.
62;
63; @keyword TIMEVAR {type=string}
64; It define the name of the variable that
65; contains the time axis. This keyword can be useful if there
66; is no unlimited dimension or if the time axis selected by default
67; (the first 1D array with unlimited dimension) is not the good one.
68;
69; @keyword ZETAFILENAME {default=FILENAME}{type=string}
70; For ROMS outputs. The filename of the file where zeta vriable should be read
71;
72; @keyword ZETAZERO {default=0}{type=scalar: 0 or 1}
73; For ROMS outputs. To define zeta to 0. instead of reading it
74;
75; @keyword _EXTRA
76; Used to pass your keywords
77;
78; @returns
79; Structure readable by litchamp.pro or an array if NOSTRUCT is activated.
80;
81; @uses
82; common.pro
83;
84; @restrictions
85; The field must have a temporal dimension.
86;
87; @history
88; Sebastien Masson (smasson\@lodyc.jussieu.fr)
89;                      15/10/1999
90;
91; @version
92; $Id$
93;-
94;---------------------------------------------------------
95;---------------------------------------------------------
96;---------------------------------------------------------
97
98FUNCTION read_ncdf, name, beginning, ending, compatibility, BOXZOOM = boxzoom, FILENAME = filename $
99                    , PARENTIN = parentin, TIMESTEP = timestep, TIMEVAR = timevar $
100                    , TOUT = tout, NOSTRUCT = nostruct, CONT_NOFILL = CONT_NOFILL, INIT = init $
101                    , GRID = grid, CALLITSELF = callitself $
102                    , ZETAFILENAME = zetafilename, ZETAZERO = zetazero $
103                    , _EXTRA = ex
104;---------------------------------------------------------
105;
106  compile_opt idl2, strictarrsubs
107;
108@cm_4mesh
109@cm_4data
110@cm_4cal
111  IF NOT keyword_set(key_forgetold) THEN BEGIN
112@updatenew
113@updatekwd
114  ENDIF
115;------------------------------------------------------------
116; we find the filename.
117;------------------------------------------------------------
118;  print,filename
119; is parent a valid widget ?
120  if keyword_set(parentin) then BEGIN
121    parent = long(parentin)
122    parent = parent*widget_info(parent, /managed)
123  ENDIF
124  filename = isafile(filename = filename, IODIRECTORY = iodir, _EXTRA = ex)
125;------------------------------------------------------------
126; Opening of the name file
127;------------------------------------------------------------
128  if size(filename, /type) NE 7 then $
129    return, report('read_ncdf cancelled')
130  IF !version.OS_FAMILY EQ 'unix' THEN spawn, '\file '+filename+' > /dev/null'
131  cdfid = ncdf_open(filename)
132  contient = ncdf_inquire(cdfid)
133;------------------------------------------------------------
134; we check if the variable name exists in the file.
135;------------------------------------------------------------
136  if ncdf_varid(cdfid, name) EQ -1 then BEGIN
137    ncdf_close, cdfid
138    return, report('variable '+name+' !C not found in the file '+filename)
139  ENDIF
140  varcontient = ncdf_varinq(cdfid, name)
141  IF varcontient.ndims LT 2 THEN return, report('read_ncdf cannot read scalar or 1D data')
142; look for the dimension names
143  dimnames = strarr(varcontient.ndims)
144  FOR i = 0, varcontient.ndims-1 DO BEGIN
145    ncdf_diminq, cdfid, varcontient.dim[i], tmp, dimsize
146    dimnames[i] = tmp
147  ENDFOR
148;------------------------------------------------------------
149; shall we redefine the grid parameters
150;------------------------------------------------------------
151  if keyword_set(init) THEN initncdf, filename, _extra = ex
152;------------------------------------------------------------
153; check the time axis and the debut and ending dates
154;------------------------------------------------------------
155  if n_elements(beginning) EQ 0 then begin
156    beginning = 0
157    timestep = 1
158  endif
159  if keyword_set(timestep) then begin
160    firsttps = beginning[0]
161    if n_elements(ending) NE 0 then lasttps = ending[0] ELSE lasttps = firsttps
162    jpt = lasttps-firsttps+1
163    IF NOT keyword_set(callitself) then time = julday(1, 1, 1) + lindgen(jpt)
164  ENDIF ELSE BEGIN
165    if keyword_set(parent) then BEGIN
166      widget_control, parent, get_uvalue = top_uvalue
167      filelist = extractatt(top_uvalue, 'filelist')
168      IF filelist[0] EQ 'many !' THEN filelist = filename
169      currentfile = (where(filelist EQ filename))[0]
170      time = (*(extractatt(top_uvalue, 'fileparameters'))[currentfile]).time_counter
171      date1 = date2jul(beginning[0])
172      if n_elements(ending) NE 0 then date2 = date2jul(ending[0]) ELSE date2 = date1
173      firsttps = where(time EQ date1) & firsttps = firsttps[0]
174      lasttps = where(time EQ date2) & lasttps = lasttps[0]
175    ENDIF ELSE BEGIN
176      IF keyword_set(timevar) THEN BEGIN
177        timeid = ncdf_varid(cdfid, timevar)
178        IF timeid EQ -1 THEN BEGIN
179          ncdf_close, cdfid
180          return, report('the file '+filename+' as no variable ' + timevar $
181                         + '. !C Use the TIMESTEP keyword')
182        endif
183        timecontient = ncdf_varinq(cdfid, timeid)
184        contient.recdim = timecontient.dim[0]
185      ENDIF ELSE BEGIN
186; we find the infinite dimension
187        timedim = contient.recdim
188        if timedim EQ -1 then BEGIN
189          ncdf_close, cdfid
190          return, report('the file '+filename+' as no infinite dimension. !C Use TIMESTEP or TIMEVAR keyword')
191        endif
192; we find the FIRST time axis     
193        timeid = 0
194        repeat BEGIN       ; As long as we have not find a variable having only one dimension: the infinite one
195          timecontient = ncdf_varinq(cdfid, timeid) ; that the variable contain.
196          timeid = timeid+1
197        endrep until (n_elements(timecontient.dim) EQ 1 $
198                      AND timecontient.dim[0] EQ contient.recdim) $
199          OR timeid EQ contient.nvars+1
200;
201        if timeid EQ contient.nvars+1 then BEGIN
202          ncdf_close, cdfid
203          return, report('the file '+filename+' as no time axis variable. !C Use the TIMESTEP keyword')
204        endif
205        timeid = timeid-1
206      ENDELSE
207; we must found the time origin of the julian calendar used in the
208; time axis.
209; does the attribut units an dcalendar exist for the variable time axis?
210      if timecontient.natts EQ 0 then BEGIN
211        ncdf_close, cdfid
212        return, report('the variable '+timecontient.name+' has no attribut.!C Use the TIMESTEP keyword or add the attribut ''units'' to the variable')
213      endif
214      attnames = strarr(timecontient.natts)
215      for attiq = 0, timecontient.natts-1 do attnames[attiq] = ncdf_attname(cdfid, timeid, attiq)
216      if (where(attnames EQ 'units'))[0] EQ -1 then BEGIN
217        ncdf_close, cdfid
218        return, report('Attribut ''units'' not found for the variable '+timecontient.name+' !C Use the TIMESTEP keyword')
219      ENDIF
220;
221; now we try to find the attribut called calendar...
222; the attribute "calendar" exists?
223; If no, we suppose that the calendar is gregorian calendar
224;
225      if (where(attnames EQ 'calendar'))[0] NE -1 then BEGIN
226        ncdf_attget, cdfid, timeid, 'calendar', value
227        value = string(value)
228        CASE value OF
229          'noleap':key_caltype = 'noleap'
230          '360d':key_caltype = '360d'
231          'greg':IF n_elements(key_caltype) EQ 0 THEN key_caltype = 'greg'
232          ELSE:BEGIN
233;            notused = report('Unknown calendar: '+value+', we use greg calendar.')
234            key_caltype = 'greg'
235          END
236        ENDCASE
237      ENDIF ELSE BEGIN
238;        notused = report('Unknown calendar, we use '+key_caltype+' calendar.')
239        IF n_elements(key_caltype) EQ 0 THEN key_caltype = 'greg'
240      ENDELSE
241;
242; now we take acre of units attribut
243      ncdf_attget, cdfid, timeid, 'units', value
244;
245; time_counter:units = "seconds since 0001-01-01 00:00:00" ;
246; time_counter:units = "hours since 0001-01-01 00:00:00" ;
247; time_counter:units = "days since 1979-01-01 00:00:00" ;
248; time_counter:units = "months since 1979-01-01 00:00:00" ;
249; time_counter:units = "years since 1979-01-01 00:00:00" ;
250;
251; we decript the "units" attribut to find the time origin
252      value = strtrim(strcompress(string(value)), 2)
253      mots = str_sep(value, ' ')
254      unite = mots[0]
255      unite = strlowcase(unite)
256      IF strpos(unite, 's', strlen(unite)-1) NE -1 THEN unite = strmid(unite, 0, strlen(unite)-1)
257      IF strpos(unite, 'julian_') NE -1 THEN unite = strmid(unite, 7)
258      IF unite NE 'second' AND unite NE 'hour' AND unite NE 'day' $
259         AND unite NE 'month' AND unite NE 'year' THEN BEGIN
260        ncdf_close, cdfid
261        return, report('time units does not start with seconds/hours/days/months/years')
262      ENDIF
263      IF stregex(value, '[^ ]* since ([0-9]){1,4}-([0-9]){1,2}-([0-9]){1,2}.*', /boolean) EQ 0 THEN BEGIN
264        ncdf_close, cdfid
265        return, report('attribut units of time has not the good format: [^ ]* since ([0-9]){1,4}-([0-9]){1,2}-([0-9]){1,2}.*')
266      ENDIF
267      depart = str_sep(mots[2], '-')
268      ncdf_varget, cdfid, timeid, time
269      time = double(time)
270      case unite of
271        'second':time = julday(depart[1], depart[2], depart[0])+time/86400.d
272        'hour':time = julday(depart[1], depart[2], depart[0])+time/24.d
273        'day':time = julday(depart[1], depart[2], depart[0])+time
274        'month':BEGIN
275          if total(fix(time) NE time) NE 0 then $ ; we switch to days with 30d/m
276            time = julday(depart[1], depart[2], depart[0])+round(time*30) $
277            ELSE for t = 0, n_elements(time)-1 DO $
278            time[t] = julday(depart[1]+time[t], depart[2], depart[0])
279        END
280        'year':BEGIN
281          if total(fix(time) NE time) NE 0 then $ ; we switch to days with 365d/y
282            time = julday(depart[1], depart[2], depart[0])+round(time*365) $
283            ELSE for t = 0, n_elements(time)-1 do $
284            time[t] = julday(depart[1], depart[2], depart[0]+time[t])
285        END
286        ELSE:BEGIN
287          ncdf_close, cdfid
288          return, report('The "units" attribute of the time axis must be something like: !C "seconds since 0001-01-01 ..." !C "days since 1979-01-01 ..." !C "months since 1979-01-01 ..." !C "years since 1979-01-01 ..."')
289        end
290      ENDCASE
291      date1 = date2jul(beginning[0])
292      if n_elements(ending) NE 0 then date2 = date2jul(ending[0]) ELSE date2 = date1
293      time = double(time)
294      firsttps = where(time GE date1) & firsttps = firsttps[0]
295      if firsttps EQ -1 THEN BEGIN
296        ncdf_close, cdfid
297        return, report('date 1: '+strtrim(jul2date(date1), 1)+' is not found in the time axis.')
298      ENDIF
299      lasttps = where(time LE date2)
300      if lasttps[0] EQ -1 THEN BEGIN
301        ncdf_close, cdfid
302        return, report('the time axis has no date before date 2: '+strtrim(jul2date(date2), 1))
303      endif
304      lasttps = lasttps[n_elements(lasttps)-1]
305      if lasttps LT firsttps then BEGIN
306        ncdf_close, cdfid
307        return, report('the time axis has no dates between date1 and  date 2: '+strtrim(jul2date(date1), 1)+' '+strtrim(jul2date(date2), 1))
308      endif
309    ENDELSE
310    time = time[firsttps:lasttps]
311    jpt = lasttps-firsttps+1
312  ENDELSE
313;------------------------------------------------------------
314; Name of the grid on which the field refer to.
315;------------------------------------------------------------
316  IF keyword_set(grid) THEN vargrid = strupcase(grid) ELSE BEGIN
317    vargrid = 'T'               ; default definition
318    IF finite(glamu[0]) EQ 1 THEN BEGIN
319; are we in one of the case corresponding to ROMS conventions?
320      CASE 1 OF
321        dimnames[2 <(varcontient.ndims-1)] EQ 's_w':vargrid = 'W'
322        dimnames[0] EQ 'xi_rho' AND dimnames[1] EQ 'eta_rho':vargrid = 'T'
323        dimnames[0] EQ 'xi_u'   AND dimnames[1] EQ 'eta_u'  :vargrid = 'U'
324        dimnames[0] EQ 'xi_v'   AND dimnames[1] EQ 'eta_v'  :vargrid = 'V'
325        dimnames[0] EQ 'xi_psi' AND dimnames[1] EQ 'eta_psi':vargrid = 'F'
326        dimnames[0] EQ 'xi_rho' AND dimnames[1] EQ 'eta_v'  :vargrid = 'V'
327        dimnames[0] EQ 'xi_u'   AND dimnames[1] EQ 'eta_rho':vargrid = 'U'
328        dimnames[0] EQ 'xi_u'   AND dimnames[1] EQ 'eta_v'  :vargrid = 'F'
329        ELSE:BEGIN
330; could we define the grid type from the file name??
331          pattern = ['GRID.', 'GRID_', 'GRID', 'UPID_', '30ID_']
332          gdtype = ['T', 'U', 'V', 'W', 'F']
333          fnametest = strupcase(filename)
334          FOR i = 0, n_elements(pattern)-1 DO BEGIN
335            FOR j = 0, n_elements(gdtype)-1 DO BEGIN
336              substr = pattern[i]+gdtype[j]
337              pos = strpos(fnametest, substr)
338              IF pos NE -1 THEN $
339                 vargrid = strmid(fnametest, pos+strlen(substr)-1, 1)
340            ENDFOR
341          ENDFOR
342        END
343      ENDCASE
344     ENDIF
345  ENDELSE
346;---------------------------------------------------------------
347; call the init function ?
348;---------------------------------------------------------------
349
350;---------------------------------------------------------------
351; redefinition of the  domain
352;---------------------------------------------------------------
353  if keyword_set(tout) then begin
354    nx = jpi
355    ny = jpj
356    nz = jpk
357    firstx = 0
358    firsty = 0
359    firstz = 0
360    lastx = jpi-1
361    lasty = jpj-1
362    lastz = jpk-1
363    case strupcase(vargrid) of
364      'T':mask = tmask
365      'U':mask = umask()
366      'V':mask = vmask()
367      'W':mask = tmask
368      'F':mask = fmask()
369    endcase
370  ENDIF ELSE BEGIN
371    if keyword_set(boxzoom) then BEGIN
372      Case 1 Of
373        N_Elements(Boxzoom) Eq 1:bte = [lon1, lon2, lat1, lat2, 0., boxzoom[0]]
374        N_Elements(Boxzoom) Eq 2:bte = [lon1, lon2, lat1, lat2, boxzoom[0], boxzoom[1]]
375        N_Elements(Boxzoom) Eq 4:bte = [Boxzoom, vert1, vert2]
376        N_Elements(Boxzoom) Eq 5:bte = [Boxzoom[0:3], 0, Boxzoom[4]]
377        N_Elements(Boxzoom) Eq 6:bte = Boxzoom
378        Else: BEGIN
379          ncdf_close, cdfid
380          return, report('Wrong Definition of Boxzoom')
381        end
382      ENDCASE
383      savedbox = 1b
384      saveboxparam, 'boxparam4rdncdf.dat'
385      domdef, bte, GRIDTYPE = ['T', vargrid], _extra = ex
386    ENDIF
387    grille, mask, glam, gphi, gdep, nx, ny, nz, firstx, firsty, firstz, lastx, lasty, lastz
388    undefine, glam & undefine, gphi & ; We liberate some memoty!
389  ENDELSE
390;---------------------------------------------------------------------
391; We initializate ixmindta, iymindta if needed
392;---------------------------------------------------------------------
393  if n_elements(jpidta) EQ 0 THEN jpidta = jpiglo
394  if n_elements(jpjdta) EQ 0 THEN jpjdta = jpjglo
395  if n_elements(jpkdta) EQ 0 THEN jpkdta = jpkglo
396  if n_elements(ixmindta) EQ 0 THEN ixmindta = 0
397  if n_elements(ixmaxdta) EQ 0 then ixmaxdta = jpidta-1
398  if ixmindta EQ -1 THEN ixmindta = 0
399  IF ixmaxdta EQ -1 then ixmaxdta = jpidta-1
400  if n_elements(iymindta) EQ 0 THEN iymindta = 0
401  IF n_elements(iymaxdta) EQ 0 then iymaxdta = jpjdta-1
402  if iymindta EQ -1 THEN iymindta = 0
403  IF iymaxdta EQ -1 then iymaxdta = jpjdta-1
404  if n_elements(izmindta) EQ 0 THEN izmindta = 0
405  IF n_elements(izmaxdta) EQ 0 then izmaxdta = jpkdta-1
406  if izmindta EQ -1 THEN izmindta = 0
407  IF izmaxdta EQ -1 then izmaxdta = jpkdta-1
408;----------------------------------------------------------------
409; We will read the file
410;---------------------------------------------------------------
411  if n_elements(key_stride) LE 2 then key_stride = [1, 1, 1]
412  key_stride = 1l > long(key_stride)
413  key_shift = long(testvar(var = key_shift))
414;
415  IF n_elements(key_yreverse) EQ 0 THEN key_yreverse = 0
416  IF keyword_set(key_yreverse) THEN BEGIN
417    tmp = jpj-1-firsty
418    firsty = jpj-1-lasty
419    lasty = tmp
420  ENDIF
421;
422  IF n_elements(key_zreverse) EQ 0 THEN key_zreverse = 0
423  IF keyword_set(key_zreverse) THEN BEGIN
424    tmp = jpk-1-firstz
425    firstz = jpk-1-lastz
426    lastz = tmp
427  ENDIF
428;
429  IF (key_gridtype EQ 'c_u' OR key_gridtype EQ 'c_f') $
430     AND (vargrid EQ 'U' OR vargrid EQ 'F') THEN BEGIN
431    IF keyword_set(key_periodic)  THEN BEGIN
432      key_shift =  key_shift-1
433    ENDIF ELSE BEGIN
434      firstx = firstx+1
435      lastx = lastx+1   
436    ENDELSE
437  ENDIF
438  IF (key_gridtype EQ 'c_v' OR key_gridtype EQ 'c_f') $
439      AND (vargrid EQ 'V' OR vargrid EQ 'F') THEN BEGIN
440    firsty = firsty+1
441    lasty = lasty+1
442  ENDIF
443;
444;---------------------------------------------------------------------
445;---------------------------------------------------------------------
446@read_ncdf_varget
447;---------------------------------------------------------------------
448;---------------------------------------------------------------------
449;
450  IF (key_gridtype EQ 'c_u' OR key_gridtype EQ 'c_f') AND keyword_set(key_periodic) $
451    AND (strupcase(vargrid) EQ 'U' OR strupcase(vargrid) EQ 'F') THEN key_shift = key_shift+1
452;---------------------------------------------------------------------
453; We define global variable joined with the variable.
454;---------------------------------------------------------------------
455; varname
456  IF NOT keyword_set(callitself) THEN varname = name
457; varunit
458  if varcontient.natts NE 0 then begin
459    attnames = strarr(varcontient.natts)
460    for attiq = 0, varcontient.natts-1 do attnames[attiq] = ncdf_attname(cdfid, name, attiq)
461    lowattnames = strlowcase(attnames)
462;
463    found = (where(lowattnames EQ 'units'))[0]
464    IF found NE -1 then ncdf_attget, cdfid, name, attnames[found], value ELSE value = ''
465    IF NOT keyword_set(callitself) THEN varunit = strtrim(string(value), 2)
466;
467    found = (where(lowattnames EQ 'add_offset'))[0]
468    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], add_offset ELSE add_offset = 0.
469;
470    found = (where(lowattnames EQ 'scale_factor'))[0]
471    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], scale_factor ELSE scale_factor = 1.
472;
473    missing_value = 'no'
474    found = (where(lowattnames EQ '_fillvalue'))[0]
475    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], missing_value
476    found = (where(lowattnames EQ 'missing_value'))[0]
477    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], missing_value
478;
479  ENDIF ELSE BEGIN
480    IF NOT keyword_set(callitself) THEN varunit = ''
481    add_offset = 0.
482    scale_factor = 1.
483    missing_value = 'no'
484  ENDELSE
485; vardate
486; We make a legible date in function of the specified language.
487  year = long(beginning[0])/10000
488  month = (long(beginning[0])/100) MOD 100
489  day = (long(beginning[0]) MOD 100)
490  vardate = string(format = '(C(CMoA))', 31*(month-1))+' '+strtrim(day, 1)+', '+strtrim(year, 1)
491  varexp = file_basename(filename)
492
493; we apply reverse
494  IF keyword_set(key_yreverse) AND ny NE 1 THEN BEGIN
495    IF varcontient.ndims - ((where(varcontient.dim EQ contient.recdim))[0] NE -1) EQ 2 THEN $
496       res = reverse(reform(res, nx, ny, jpt, /overwrite),  2) $
497    ELSE res = reverse(reform(res, nx, ny, nz, jpt, /overwrite),  2)
498  ENDIF
499  if keyword_set(key_zreverse) AND nz NE 1 $
500     AND varcontient.ndims - ((where(varcontient.dim EQ contient.recdim))[0] NE -1) EQ 3 THEN $
501        res = reverse(reform(res, nx, ny, nz, jpt, /overwrite),  3)
502; We apply the value valmask on land points.
503  if NOT keyword_set(cont_nofill) then begin
504    valmask = 1e20
505    case 1 of
506      varcontient.ndims eq 2:BEGIN ;xy array
507        mask = mask[*, *, 0]
508        earth = where(mask EQ 0)
509      END
510      varcontient.ndims eq 3 AND (where(varcontient.dim EQ contient.recdim))[0] EQ -1:BEGIN ;xyz array
511        earth = where(mask EQ 0)
512      END
513      varcontient.ndims eq 3 AND (where(varcontient.dim EQ contient.recdim))[0] NE -1:BEGIN ;xyt array
514        mask = mask[*, *, 0]
515        earth = where(mask EQ 0)
516        if earth[0] NE -1 then BEGIN
517          earth = earth#replicate(1, jpt)+replicate(nx*ny, n_elements(earth))#lindgen(jpt)
518        END
519      END
520      varcontient.ndims eq 4:BEGIN ;xyzt array
521        earth = where(mask EQ 0)
522        if earth[0] NE -1 then BEGIN
523          earth = earth#replicate(1, jpt)+replicate(nx*ny*nz, n_elements(earth))#lindgen(jpt)
524        END
525      END
526    endcase
527  ENDIF ELSE earth = -1
528; we look for  missing_value
529  IF size(missing_value, /type) NE 7 then BEGIN
530    IF size(missing_value, /type) EQ 1 THEN BEGIN
531      missing_value = strlowcase(string(missing_value))
532      IF strmid(missing_value, 0, 1, /reverse_offset) EQ 'f' THEN $
533        missing_value = strmid(missing_value, 0, strlen(missing_value)-1)
534      IF isnumber(string(missing_value), tmp) EQ 1 THEN missing_value = tmp ELSE BEGIN
535        print, 'Warning: missing value is not a number: ', missing_value
536        missing_value = - 1
537      ENDELSE
538    ENDIF
539;    if missing_value NE valmask then begin
540    if abs(missing_value) LT 1e6 then missing = where(res EQ missing_value) $
541    ELSE missing = where(abs(res) gt abs(missing_value)/10.)
542;    ENDIF ELSE missing = -1
543  ENDIF ELSE missing = -1
544; we apply add_offset, scale_factor and missing_value
545  if scale_factor NE 1 then res = temporary(res)*scale_factor
546  if add_offset NE 0 then res = temporary(res)+add_offset
547  if missing[0] NE -1 then res[temporary(missing)] = !values.f_nan
548  if earth[0] NE -1 then res[temporary(earth)] = 1.e20
549;---------------------------------------------------------------------
550; if it is roms outputs, we need to get additionals infos...
551  IF NOT keyword_set(callitself) THEN BEGIN
552    IF strmid(dimnames[0], 0, 3) EQ 'xi_' AND strmid(dimnames[1], 0, 4) EQ 'eta_' THEN BEGIN
553      ncdf_attget, cdfid, 'theta_s', theta_s, /global
554      ncdf_attget, cdfid, 'theta_b', theta_b, /global
555      ncdf_attget, cdfid, 'hc', hc, /global
556; look for all variables names
557      allvarnames = strarr(contient.nvars)
558      FOR i = 0, contient.nvars-1 DO BEGIN
559        tmp = ncdf_varinq( cdfid, i)
560        allvarnames[i] = tmp.name
561      ENDFOR
562      CASE 1 OF
563        keyword_set(zetazero):zeta = fltarr(nx, ny, jpt)
564        keyword_set(zetafilename):  $
565           zeta = read_ncdf('zeta', firsttps, lasttps, FILENAME = zetafilename $
566                            , /TIMESTEP, /NOSTRUCT, CONT_NOFILL = CONT_NOFILL $
567                            , GRID = vargrid, /CALLITSELF, _EXTRA = ex)
568        (where(allvarnames EQ 'zeta'))[0] NE -1: $
569           zeta = read_ncdf('zeta', firsttps, lasttps, FILENAME = filename $
570                            , /TIMESTEP, /NOSTRUCT, CONT_NOFILL = CONT_NOFILL $
571                            , GRID = vargrid, /CALLITSELF, _EXTRA = ex)
572        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.')
573      ENDCASE
574      romszinfos = {h:romszinfos.h, zeta:temporary(zeta), theta_s:theta_s, theta_b:theta_b, hc:hc}
575    ENDIF ELSE romszinfos = {h:-1, zeta:-1, theta_s:-1, theta_b:-1, hc:-1}
576  ENDIF
577;---------------------------------------------------------------------
578  ncdf_close, cdfid
579
580  IF keyword_set(savedbox) THEN restoreboxparam, 'boxparam4rdncdf.dat'
581
582  IF keyword_set(nostruct) THEN return, res
583  IF keyword_set(key_forgetold) THEN BEGIN
584    return, {arr:temporary(res), grid:vargrid, unit:varunit, experiment:varexp, name:varname}
585  ENDIF ELSE BEGIN
586    return, {tab:temporary(res), grille:vargrid, unite:varunit, experience:varexp, nom:varname}
587  ENDELSE
588
589END
590
591
592
593
594
595
Note: See TracBrowser for help on using the repository browser.