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

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

reduce memory use

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