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

Last change on this file since 238 was 238, checked in by pinsard, 17 years ago

improvements/corrections of some *.pro headers

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