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

Last change on this file since 134 was 134, checked in by navarro, 18 years ago

change *.pro file properties (del eof-style, del executable, set keywords Id

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 20.7 KB
Line 
1;------------------------------------------------------------
2;------------------------------------------------------------
3;------------------------------------------------------------
4;+
5; NAME: read_ncdf
6;
7; PURPOSE:fonction de lecture pour fichier net_cdf.
8; Ce programme, est moins universel que ncdf_lec (il fait appelle au
9; variables declarees dans common.pro) mais il est du cop bcp plus
10; facile d''utilisation. Il prend en compte la declaration des
11; differents zoom qui ont ete definis (ixminmesh...premierx...) la
12; declaration de la variable key_shift... bref le resultat de
13; read_ncdf peut dorectement etre utilise dans plt...
14; C''est aussi ce programme qui est utilise par defaut dans mes
15; widgets pour la partie lecture.
16;
17; CATEGORY:lecture de fichiers NetCdf
18;
19; CALLING SEQUENCE:res = read_ncdf(name,debut[,fin])
20;
21; INPUTS: name: un string definissant le champ a lire.
22;         debut et fin: sont relatifs a l''axe des temps. Ce peut etre
23;         - 2 dates du type yyyymmdd et ds ce cas on selectionne les
24;         dates qui sont comprisent entre ces 2 dates.
25;         - 2 indices qui definissent entre quel et quel pas de temps
26;           on doit extraire la dimension temporelle.
27;         exp: ne sert a rien!
28;
29; KEYWORD PARAMETERS: utilisables hors du contexte des widgets
30;
31;        BOXZOOM: contient la boxzoom sur laquelle on doit faire la
32;        lecture
33;        FILENAME: string contennant le nom du fichier
34;        /INIT; to call automatically initncdf, filename and thus
35;        redefine all the grid parameters
36;        GRID='[UTVWF]' to specify the type of grid. Defaut is (1)
37;        based on the name of the file if the file ends by
38;        GRID[._][TUVFW].NC (not case sensible) or (2) T if case (1)
39;        is not found.
40;        IODIRECTORY;a string giving the name of iodirectory (see
41;        isafile.pro for all possibilities). default value is common
42;        variable iodir
43;        TIMESTEP:activer pour specifier que debut et fin font
44;        reference a des indices de l''axe du temps et non pas a des
45;        dates.
46;        TOUT: activer si on veut lire le ficher sur l''ensemble du
47;        domaine sans tenir compte du sous domaine definit par boxzoom
48;        ou lon1,lon2,lat1,lat2,vert1,vert2.
49;        NOSTRUCT: activer si on ne veut pas que read_ncdf reourne
50;        une structure mais uniquement le tableau se rapportant au
51;        champ.
52;        TIMEVAR: a string to define the name of the variable that
53;        contains the time axis. This keyword can be usefull if there
54;        is no unlimited dimension or if the time axis selected by defaut
55;        (the first 1D array with unlimited dimension) is not the good one
56;
57;
58; OUTPUTS:une stucture lisible par litchamp.pro ou un simple tableau
59; si /NOSTRUCT est active
60;
61; COMMON BLOCKS:common.pro
62;
63; SIDE EFFECTS:
64;
65; RESTRICTIONS:le champ doit avoir une dimension temporelle
66;
67; EXAMPLE:
68;
69; MODIFICATION HISTORY:Sebastien Masson (smasson@lodyc.jussieu.fr)
70;                      15/10/1999
71;-
72;------------------------------------------------------------
73;------------------------------------------------------------
74;------------------------------------------------------------
75FUNCTION read_ncdf, name, debut, fin, pour_etre_compatible, BOXZOOM = boxzoom, FILENAME = filename $
76                    , PARENTIN = parentin, TIMESTEP = timestep, TIMEVAR = timevar $
77                    , TOUT = tout, NOSTRUCT = nostruct, CONT_NOFILL = CONT_NOFILL, INIT = init $
78                    , GRID = grid, FBASE2TBASE = fbase2tbase, _EXTRA = ex
79;---------------------------------------------------------
80;
81  compile_opt idl2, strictarrsubs
82;
83@cm_4mesh
84@cm_4data
85@cm_4cal
86  IF NOT keyword_set(key_forgetold) THEN BEGIN
87@updatenew
88@updatekwd
89  ENDIF
90;------------------------------------------------------------
91; we find the filename.
92;------------------------------------------------------------
93;  print,filename
94; is parent a valid widget ?
95  if keyword_set(parentin) then BEGIN
96    parent = long(parentin)
97    parent = parent*widget_info(parent, /managed)
98  ENDIF
99  filename = isafile(filename = filename, IODIRECTORY = iodir, _EXTRA = ex)
100;------------------------------------------------------------
101; ouverture du fichier nom
102;------------------------------------------------------------
103  if size(filename, /type) NE 7 then $
104    return, report('read_ncdf cancelled')
105  IF !version.OS_FAMILY EQ 'unix' THEN spawn, '\file '+filename+' > /dev/null'
106  cdfid = ncdf_open(filename)
107  contient = ncdf_inquire(cdfid)
108;------------------------------------------------------------
109; we check if the variable name exists in the file.
110;------------------------------------------------------------
111  if ncdf_varid(cdfid, name) EQ -1 then BEGIN
112    ncdf_close, cdfid
113    return, report('variable '+name+' !C not found in the file '+filename)
114  ENDIF
115  varcontient = ncdf_varinq(cdfid, name)
116;------------------------------------------------------------
117; shall we redefine the grid parameters
118;------------------------------------------------------------
119  if keyword_set(init) THEN initncdf, filename, _extra = ex
120;------------------------------------------------------------
121; check the time axis and the debut and fin dates
122;------------------------------------------------------------
123  if n_elements(debut) EQ 0 then begin
124    debut = 0
125    timestep = 1
126  endif
127  if keyword_set(timestep) then begin
128    firsttps = debut[0]
129    if n_elements(fin) NE 0 then lasttps = fin[0] ELSE lasttps = firsttps
130    jpt = lasttps-firsttps+1
131    time = julday(1, 1, 1) + lindgen(jpt)
132  ENDIF ELSE BEGIN
133    if keyword_set(parent) then BEGIN
134      widget_control, parent, get_uvalue = top_uvalue
135      filelist = extractatt(top_uvalue, 'filelist')
136      IF filelist[0] EQ 'many !' THEN filelist = filename
137      currentfile = (where(filelist EQ filename))[0]
138      time = (*(extractatt(top_uvalue, 'fileparameters'))[currentfile]).time_counter
139      date1 = date2jul(debut[0])
140      if n_elements(fin) NE 0 then date2 = date2jul(fin[0]) ELSE date2 = date1
141      firsttps = where(time EQ date1) & firsttps = firsttps[0]
142      lasttps = where(time EQ date2) & lasttps = lasttps[0]
143    ENDIF ELSE BEGIN
144      IF keyword_set(timevar) THEN BEGIN
145        timeid = ncdf_varid(cdfid, timevar)
146        IF timeid EQ -1 THEN BEGIN
147          ncdf_close, cdfid
148          return, report('the file '+filename+' as no variable ' + timevar $
149                         + '. !C Use the TIMESTEP keyword')
150        endif
151        timecontient = ncdf_varinq(cdfid, timeid)
152        contient.recdim = timecontient.dim[0]
153      ENDIF ELSE BEGIN
154; we find the infinite dimension
155        timedim = contient.recdim
156        if timedim EQ -1 then BEGIN
157          ncdf_close, cdfid
158          return, report('the file '+filename+' as no infinite dimension. !C Use TIMESTEP or TIMEVAR keyword')
159        endif
160; we find the FIRST time axis     
161        timeid = 0
162        repeat BEGIN       ; tant que l''on a pas trouve une variable qui n''a qu''
163                                ; une dimension: la dimension infinie
164          timecontient = ncdf_varinq(cdfid, timeid) ; que contient la variable
165          timeid = timeid+1
166        endrep until (n_elements(timecontient.dim) EQ 1 $
167                      AND timecontient.dim[0] EQ contient.recdim) $
168          OR timeid EQ contient.nvars+1
169;
170        if timeid EQ contient.nvars+1 then BEGIN
171          ncdf_close, cdfid
172          return, report('the file '+filename+' as no time axis variable. !C Use the TIMESTEP keyword')
173        endif
174        timeid = timeid-1
175      ENDELSE
176; we must found the time origin of the julian calendar used in the
177; time axis.
178; does the attribut units an dcalendar exist for the variable time axis?
179      if timecontient.natts EQ 0 then BEGIN
180        ncdf_close, cdfid
181        return, report('the variable '+timecontient.name+' has no attribut.!C Use the TIMESTEP keyword or add the attribut ''units'' to the variable')
182      endif
183      attnames = strarr(timecontient.natts)
184      for attiq = 0, timecontient.natts-1 do attnames[attiq] = ncdf_attname(cdfid, timeid, attiq)
185      if (where(attnames EQ 'units'))[0] EQ -1 then BEGIN
186        ncdf_close, cdfid
187        return, report('Attribut ''units'' not found for the variable '+timecontient.name+' !C Use the TIMESTEP keyword')
188      ENDIF
189;
190; now we try to find the attribut called calendar...
191; the the attribute "calendar" exists?
192; If no, we suppose that the calendar is gregorian calendar
193;
194      if (where(attnames EQ 'calendar'))[0] NE -1 then BEGIN
195        ncdf_attget, cdfid, timeid, 'calendar', value
196        value = string(value)
197        CASE value OF
198          'noleap':key_caltype = 'noleap'
199          '360d':key_caltype = '360d'
200          'greg':IF n_elements(key_caltype) EQ 0 THEN key_caltype = 'greg'
201          ELSE:BEGIN
202;            notused = report('Unknown calendar: '+value+', we use greg calendar.')
203            key_caltype = 'greg'
204          END
205        ENDCASE
206      ENDIF ELSE BEGIN
207;        notused = report('Unknown calendar, we use '+key_caltype+' calendar.')
208        IF n_elements(key_caltype) EQ 0 THEN key_caltype = 'greg'
209      ENDELSE
210;
211; now we take acre of units attribut
212      ncdf_attget, cdfid, timeid, 'units', value
213;
214; time_counter:units = "seconds since 0001-01-01 00:00:00" ;
215; time_counter:units = "hours since 0001-01-01 00:00:00" ;
216; time_counter:units = "days since 1979-01-01 00:00:00" ;
217; time_counter:units = "months since 1979-01-01 00:00:00" ;
218; time_counter:units = "years since 1979-01-01 00:00:00" ;
219;
220; we decript the "units" attribut to find the time origin
221      value = strtrim(strcompress(string(value)), 2)
222      mots = str_sep(value, ' ')
223      unite = mots[0]
224      depart = str_sep(mots[2], '-')
225      ncdf_varget, cdfid, timeid, time
226      time = double(time)
227      unite = strlowcase(unite)
228      IF strpos(unite, 's', strlen(unite)-1) NE -1 THEN unite = strmid(unite, 0, strlen(unite)-1)
229      IF strpos(unite, 'julian_') NE -1 THEN unite = strmid(unite, 7)
230      case unite of
231        'second':time = julday(depart[1], depart[2], depart[0])+time/86400.d
232        'hour':time = julday(depart[1], depart[2], depart[0])+time/24.d
233        'day':time = julday(depart[1], depart[2], depart[0])+time
234        'month':BEGIN
235          if total(fix(time) NE time) NE 0 then $ ; we switch to days with 30d/m
236            time = julday(depart[1], depart[2], depart[0])+round(time*30) $
237            ELSE for t = 0, n_elements(time)-1 DO $
238            time[t] = julday(depart[1]+time[t], depart[2], depart[0])
239        END
240        'year':BEGIN
241          if total(fix(time) NE time) NE 0 then $ ; we switch to days with 365d/y
242            time = julday(depart[1], depart[2], depart[0])+round(time*365) $
243            ELSE for t = 0, n_elements(time)-1 do $
244            time[t] = julday(depart[1], depart[2], depart[0]+time[t])
245        END
246        ELSE:BEGIN
247          ncdf_close, cdfid
248          return, report('The "units" attribu 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 ..."')
249        end
250      ENDCASE
251      date1 = date2jul(debut[0])
252      if n_elements(fin) NE 0 then date2 = date2jul(fin[0]) ELSE date2 = date1
253      time = double(time)
254      firsttps = where(time GE date1) & firsttps = firsttps[0]
255      if firsttps EQ -1 THEN BEGIN
256        ncdf_close, cdfid
257        return, report('date 1: '+strtrim(jul2date(date1), 1)+' is not found in the time axis.')
258      ENDIF
259      lasttps = where(time LE date2)
260      if lasttps[0] EQ -1 THEN BEGIN
261        ncdf_close, cdfid
262        return, report('the time axis as no date before date 2: '+strtrim(jul2date(date2), 1))
263      endif
264      lasttps = lasttps[n_elements(lasttps)-1]
265      if lasttps LT firsttps then BEGIN
266        ncdf_close, cdfid
267        return, report('the time axis as no dates between date1 and  date 2: '+strtrim(jul2date(date1), 1)+' '+strtrim(jul2date(date2), 1))
268      endif
269    ENDELSE
270    time = time[firsttps:lasttps]
271    jpt = lasttps-firsttps+1
272  ENDELSE
273;------------------------------------------------------------
274; nom de la grille a laquelle se rapporte le champ
275;------------------------------------------------------------
276  IF keyword_set(grid) THEN vargrid = strupcase(grid) ELSE BEGIN
277    vargrid = 'T'               ; default definition
278    IF finite(glamu[0]) EQ 1 THEN BEGIN
279      pattern = ['GRID.', 'GRID_', 'GRID', 'UPID_', '30ID_']
280      gdtype = ['T', 'U', 'V', 'W', 'F']
281      fnametest = strupcase(filename)
282      FOR i = 0, n_elements(pattern)-1 DO BEGIN
283        FOR j = 0, n_elements(gdtype)-1 DO BEGIN
284          substr = pattern[i]+gdtype[j]
285          pos = strpos(fnametest, substr)
286          IF pos NE -1 THEN $
287             vargrid = strmid(fnametest, pos+strlen(substr)-1, 1)
288        ENDFOR
289      ENDFOR
290    ENDIF
291  ENDELSE
292;---------------------------------------------------------------
293; call the init function ?
294;---------------------------------------------------------------
295
296;---------------------------------------------------------------
297; redefinition du domaine
298;---------------------------------------------------------------
299  if keyword_set(tout) then begin
300    nx = jpi
301    ny = jpj
302    nz = jpk
303    firstx = 0
304    firsty = 0
305    firstz = 0
306    lastx = jpi-1
307    lasty = jpj-1
308    lastz = jpk-1
309    case strupcase(vargrid) of
310      'T':mask = tmask
311      'U':mask = umask()
312      'V':mask = vmask()
313      'W':mask = tmask
314      'F':mask = fmask()
315    endcase
316  ENDIF ELSE BEGIN
317    if keyword_set(boxzoom) then BEGIN
318      Case 1 Of
319        N_Elements(Boxzoom) Eq 1:bte = [lon1, lon2, lat1, lat2, 0., boxzoom[0]]
320        N_Elements(Boxzoom) Eq 2:bte = [lon1, lon2, lat1, lat2, boxzoom[0], boxzoom[1]]
321        N_Elements(Boxzoom) Eq 4:bte = [Boxzoom, vert1, vert2]
322        N_Elements(Boxzoom) Eq 5:bte = [Boxzoom[0:3], 0, Boxzoom[4]]
323        N_Elements(Boxzoom) Eq 6:bte = Boxzoom
324        Else: BEGIN
325          ncdf_close, cdfid
326          return, report('Wrong Definition of Boxzoom')
327        end
328      ENDCASE
329      savedbox = 1b
330      saveboxparam, 'boxparam4rdncdf.dat'
331      domdef, bte, GRIDTYPE = ['T', vargrid], _extra = ex
332    ENDIF
333    grille, mask, glam, gphi, gdep, nx, ny, nz, firstx, firsty, firstz, lastx, lasty, lastz
334    undefine, glam & undefine, gphi & ; on libere un peu de memoire!
335  ENDELSE
336;---------------------------------------------------------------------
337; on initialise les ixmindta, iymindta au besoin
338;---------------------------------------------------------------------
339  if n_elements(jpidta) EQ 0 THEN jpidta = jpiglo
340  if n_elements(jpjdta) EQ 0 THEN jpjdta = jpjglo
341  if n_elements(jpkdta) EQ 0 THEN jpkdta = jpkglo
342  if n_elements(ixmindta) EQ 0 THEN ixmindta = 0
343  if n_elements(ixmaxdta) EQ 0 then ixmaxdta = jpidta-1
344  if ixmindta EQ -1 THEN ixmindta = 0
345  IF ixmaxdta EQ -1 then ixmaxdta = jpidta-1
346  if n_elements(iymindta) EQ 0 THEN iymindta = 0
347  IF n_elements(iymaxdta) EQ 0 then iymaxdta = jpjdta-1
348  if iymindta EQ -1 THEN iymindta = 0
349  IF iymaxdta EQ -1 then iymaxdta = jpjdta-1
350  if n_elements(izmindta) EQ 0 THEN izmindta = 0
351  IF n_elements(izmaxdta) EQ 0 then izmaxdta = jpkdta-1
352  if izmindta EQ -1 THEN izmindta = 0
353  IF izmaxdta EQ -1 then izmaxdta = jpkdta-1
354;----------------------------------------------------------------
355; on va lire le fichier
356;---------------------------------------------------------------
357  if n_elements(key_stride) LE 2 then key_stride = [1, 1, 1]
358  key_stride = 1l > long(key_stride)
359  key_shift = long(testvar(var = key_shift))
360;
361  IF n_elements(key_yreverse) EQ 0 THEN key_yreverse = 0
362  IF keyword_set(key_yreverse) THEN BEGIN
363    tmp = jpj-1-firsty
364    firsty = jpj-1-lasty
365    lasty = tmp
366  ENDIF
367;
368  IF keyword_set(fbase2tbase) THEN BEGIN
369    case strupcase(vargrid) of
370      'U':BEGIN
371        IF NOT keyword_set(key_periodic) THEN BEGIN
372          firstx = firstx+1
373          lastx = lastx+1
374        ENDIF
375      END
376      'V':BEGIN
377        firsty = firsty+1
378        lasty = lasty+1
379      END
380      'F':BEGIN
381        firsty = firsty+1
382        lasty = lasty+1
383        IF NOT keyword_set(key_periodic) THEN BEGIN
384          firstx = firstx+1
385          lastx = lastx+1
386        ENDIF
387      END
388      ELSE:
389    endcase
390  ENDIF
391;
392  IF keyword_set(fbase2tbase) AND keyword_set(key_periodic) $
393    AND (strupcase(vargrid) EQ 'U' OR strupcase(vargrid) EQ 'F') THEN key_shift =  key_shift-1
394;
395;---------------------------------------------------------------------
396;---------------------------------------------------------------------
397@read_ncdf_varget
398;---------------------------------------------------------------------
399;---------------------------------------------------------------------
400;
401  IF keyword_set(fbase2tbase) AND keyword_set(key_periodic) $
402    AND (strupcase(vargrid) EQ 'U' OR strupcase(vargrid) EQ 'F') THEN key_shift =  key_shift+1
403;---------------------------------------------------------------------
404; on definit les variables globales rattachees a la variable
405;---------------------------------------------------------------------
406; varname
407  varname = name
408; varunit
409  if varcontient.natts NE 0 then begin
410    attnames = strarr(varcontient.natts)
411    for attiq = 0, varcontient.natts-1 do attnames[attiq] = ncdf_attname(cdfid, name, attiq)
412    lowattnames = strlowcase(attnames)
413;
414    found = (where(lowattnames EQ 'units'))[0]
415    IF found NE -1 then ncdf_attget, cdfid, name, attnames[found], value ELSE value = ''
416    varunit = strtrim(string(value), 2)
417;
418    found = (where(lowattnames EQ 'add_offset'))[0]
419    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], add_offset ELSE add_offset = 0.
420;
421    found = (where(lowattnames EQ 'scale_factor'))[0]
422    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], scale_factor ELSE scale_factor = 1.
423;
424    missing_value = 'no'
425    found = (where(lowattnames EQ '_fillvalue'))[0]
426    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], missing_value
427    found = (where(lowattnames EQ 'missing_value'))[0]
428    if found NE -1 then ncdf_attget, cdfid, name, attnames[found], missing_value
429;
430  ENDIF ELSE BEGIN
431    varunit = ''
432    add_offset = 0.
433    scale_factor = 1.
434    missing_value = 'no'
435  ENDELSE
436; vardate
437; on construit une belle date lisible en fonction du langage specifie !!!
438  year = long(debut[0])/10000
439  month = (long(debut[0])/100) MOD 100
440  day = (long(debut[0]) MOD 100)
441  vardate = string(format = '(C(CMoA))', 31*(month-1))+' '+strtrim(day, 1)+', '+strtrim(year, 1)
442  varexp = file_basename(filename)
443
444; we apply reverse
445  if keyword_set(key_yreverse) then res = reverse(temporary(res),  2)
446  if keyword_set(key_zreverse) AND (size(res))[0] EQ 3 AND jpt EQ 1 then res = reverse(temporary(res), 3)
447  if keyword_set(key_zreverse) AND (size(res))[0] EQ 4 THEN res = reverse(temporary(res), 3)
448
449; on applique la valeur valmask sur les points terre
450  if NOT keyword_set(cont_nofill) then begin
451    valmask = 1e20
452    case 1 of
453      varcontient.ndims eq 2:BEGIN ;xy array
454        mask = mask[*, *, 0]
455        earth = where(mask EQ 0)
456      END
457      varcontient.ndims eq 3 AND (where(varcontient.dim EQ contient.recdim))[0] EQ -1:BEGIN ;xyz array
458        earth = where(mask EQ 0)
459      END
460      varcontient.ndims eq 3 AND (where(varcontient.dim EQ contient.recdim))[0] NE -1:BEGIN ;xyt array
461        mask = mask[*, *, 0]
462        earth = where(mask EQ 0)
463        if earth[0] NE -1 then BEGIN
464          earth = earth#replicate(1, jpt)+replicate(nx*ny, n_elements(earth))#lindgen(jpt)
465        END
466      END
467      varcontient.ndims eq 4:BEGIN ;xyzt array
468        earth = where(mask EQ 0)
469        if earth[0] NE -1 then BEGIN
470          earth = earth#replicate(1, jpt)+replicate(nx*ny*nz, n_elements(earth))#lindgen(jpt)
471        END
472      END
473    endcase
474  ENDIF ELSE earth = -1
475; we look for  missing_value
476  IF size(missing_value, /type) NE 7 then BEGIN
477    IF size(missing_value, /type) EQ 1 THEN BEGIN
478      IF isnumber(string(missing_value), tmp) EQ 1 THEN missing_value = tmp
479    ENDIF
480;    if missing_value NE valmask then begin
481    if abs(missing_value) LT 1e6 then missing = where(res EQ missing_value) $
482    ELSE missing = where(abs(res) gt abs(missing_value)/10.)
483;    ENDIF ELSE missing = -1
484  ENDIF ELSE missing = -1
485; on applique les add_offset, scale_factor et missing_value
486  if scale_factor NE 1 then res = temporary(res)*scale_factor
487  if add_offset NE 0 then res = temporary(res)+add_offset
488  if missing[0] NE -1 then res[temporary(missing)] = !values.f_nan
489  if earth[0] NE -1 then res[temporary(earth)] = 1e20
490;---------------------------------------------------------------------
491  ncdf_close, cdfid
492;---------------------------------------------------------------------
493  if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4rdncdf.dat'
494  if keyword_set(nostruct) then return, res $
495  ELSE BEGIN
496    IF keyword_set(key_forgetold) THEN BEGIN
497      return, {arr:res, grid:vargrid, unit:varunit, experiment:varexp, name:varname}
498    ENDIF ELSE BEGIN
499      return, {tab:res, grille:vargrid, unite:varunit, experience:varexp, nom:varname}
500    ENDELSE
501  ENDELSE
502END
503
504
505
506
507
508
Note: See TracBrowser for help on using the repository browser.