source: trunk/SRC/ToBeReviewed/HOPE/read_hope.pro @ 231

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

improvements/corrections of some *.pro headers

  • Property svn:keywords set to Id
File size: 24.5 KB
Line 
1;+
2;
3; @file_comments
4;
5; @categories
6;
7; @param EVENT
8;
9; @returns
10;
11; @restrictions
12;
13; @examples
14;
15; @history
16;
17; @version
18; $Id$
19;
20;-
21;
22PRO read_hope_event, event
23;
24  compile_opt idl2, strictarrsubs
25;
26   widget_control, event.id, get_uvalue=uval
27   widget_control, event.top, get_uvalue=top_uvalue
28   case uval.name OF
29;---------------------------------
30      'cancel':begin
31; close the file
32         cdfid=*top_uvalue[1, findline(top_uvalue, 'cdfid')]
33         ncdf_close, cdfid
34; clear the pointer
35         for i=0,n_elements(top_uvalue)-1 do ptr_free, top_uvalue[i]
36; kill the widget
37         widget_control,event.top,/destroy
38      end
39;---------------------------------
40      'type choice':begin
41; find the new type of selected section
42         typeindex=widget_info(event.id,/droplist_select)
43         selectedtype=(*top_uvalue[1, findline(top_uvalue, 'type choice')])[typeindex]
44; find the available variables for this type of section
45         sectype = *top_uvalue[1, findline(top_uvalue, 'sectype')]
46         goodvar = where(sectype EQ selectedtype)
47         namevar = *top_uvalue[1, findline(top_uvalue, 'namevar')]
48         goodnamevar = namevar[goodvar]
49; find the selected var name
50         varchoiceid = widget_info(event.top,find_by_uname = 'var choice')
51         varindex = widget_info(varchoiceid,/droplist_select)
52         varchoice = *top_uvalue[1, findline(top_uvalue, 'var choice')]
53         selectedvarname=varchoice[varindex]
54; do we change the variable?
55         if (where(goodnamevar EQ selectedvarname))[0] EQ -1 then begin
56            selectedvarname = goodnamevar[0]
57            varindex = (where(varchoice EQ selectedvarname))[0]
58            widget_control, varchoiceid, set_droplist_select = varindex
59         ENDIF
60; displays the different domains
61         selected = goodvar[where(goodnamevar EQ selectedvarname)]
62         rh_alldomains, event.top, selected
63      end
64;---------------------------------
65      'var choice':BEGIN
66; find the new variable
67         varindex=widget_info(event.id,/droplist_select)
68         selectedvar=(*top_uvalue[1, findline(top_uvalue, 'var choice')])[varindex]
69; find the available variables for this type of section
70         namevar = *top_uvalue[1, findline(top_uvalue, 'namevar')]
71         goodvar = where(namevar EQ selectedvar)
72         sectype = *top_uvalue[1, findline(top_uvalue, 'sectype')]
73         goodtype = sectype[goodvar]
74; find the selected type of section
75         typechoiceid = widget_info(event.top,find_by_uname = 'type choice')
76         typeindex = widget_info(typechoiceid,/droplist_select)
77         typechoice = *top_uvalue[1, findline(top_uvalue, 'type choice')]
78         selectedtype=typechoice[typeindex]
79; do we change the type of section ?
80         if (where(goodtype EQ selectedtype))[0] EQ -1 then begin
81            selectedtype = goodtype[0]
82            typeindex = (where(typechoice EQ selectedtype))[0]
83            widget_control, typechoiceid, set_droplist_select = typeindex
84         ENDIF
85; displays the different domains
86         selected = goodvar[where(goodtype EQ selectedtype)]
87         rh_alldomains, event.top, selected
88      END
89;---------------------------------
90      'plot':BEGIN
91; plot the array
92         res = createhopestruct(event)
93; type of section
94         selected = *top_uvalue[1, findline(top_uvalue, 'selected')]
95         type = (*top_uvalue[1, findline(top_uvalue, 'sectype')])[selected]
96; get the informations of cw_specifie
97         specifieid=widget_info(event.top,find_by_uname = 'specifie')
98         widget_control, specifieid, get_value = specifie
99         specifie = struct2string(specifie,/direct2string)
100         case type of
101            'x':command = 'plt1d,res,''x'','+specifie
102            'y':command = 'plt1d,res,''y'','+specifie
103            'z':command = 'plt1d,res,''z'','+specifie
104            't':command = 'pltt,res,''t'' ,'+specifie
105            'xy':command = 'plt, res,'+specifie
106            'xz':command = 'pltz, res,''xz'','+specifie
107            'yz':command = 'pltz, res,''yz'','+specifie
108            'xt':command = 'pltt,res,''xt'','+specifie
109            'yt':command = 'pltt,res,''yt'','+specifie
110            'zt':command = 'pltt,res,''zt'','+specifie
111            'xyz':
112            'xyt':
113            'yzt':
114            'xyzt':
115         ENDCASE
116         test = execute(command)
117         if test EQ 0 then stop
118      end
119;---------------------------------
120      'linechoice':BEGIN
121         if event.select EQ 1 then begin
122            sensitive = bytarr(3)
123            sensitive[where(['odd', 'even', 'odd-even'] eq event.value)] = 1
124            basedomainodd=widget_info(event.top,find_by_uname = 'basedomainodd')
125            widget_control, basedomainodd, sensitive = sensitive[0]
126            basedomaineven=widget_info(event.top,find_by_uname = 'basedomaineven')
127            widget_control, basedomaineven, sensitive = sensitive[1]
128            basedomainoddeven=widget_info(event.top,find_by_uname = 'basedomainodd-even')
129            widget_control, basedomainoddeven, sensitive = sensitive[2]
130            case (where(sensitive EQ 1))[0] of
131               0:BEGIN
132                  widget_control, basedomainodd, get_uvalue = oddsecchoice
133                  oddsecchoiceid=widget_info(event.top,find_by_uname = 'oddsecchoice')
134                  if oddsecchoiceid NE 0 then $
135                   index = widget_info(oddsecchoiceid, /droplist_select) $
136                  ELSE index = 0
137                  *top_uvalue[1, findline(top_uvalue, 'selected')] = oddsecchoice[index]
138               END
139               1:BEGIN
140                  widget_control, basedomaineven, get_uvalue = evensecchoice
141                  evensecchoiceid=widget_info(event.top,find_by_uname = 'evensecchoice')
142                  if evensecchoiceid NE 0 then $
143                   index = widget_info(evensecchoiceid, /droplist_select) $
144                  ELSE index = 0
145                  *top_uvalue[1, findline(top_uvalue, 'selected')] = evensecchoice[index]
146               END
147               2:BEGIN
148                  widget_control, basedomainodd, get_uvalue = oddevensecchoice
149                  oddevensecchoiceid=widget_info(event.top,find_by_uname = 'odd-evensecchoice')
150                  if oddevensecchoiceid NE 0 then $
151                   index = widget_info(oddevensecchoiceid, /droplist_select) $
152                  ELSE index = 0
153                  *top_uvalue[1, findline(top_uvalue, 'selected')] = oddevensecchoice[index]
154               END
155            endcase
156         endif
157      END
158;---------------------------------
159      'oddsecchoice':BEGIN
160         widget_control, event.top, update=0
161         basedomainodd=widget_info(event.top,find_by_uname = 'basedomainodd')
162         widget_control, basedomainodd, get_uvalue = oddsecchoice
163         domainpart, top_uvalue, basedomainodd, oddsecchoice[event.index]
164         *top_uvalue[1, findline(top_uvalue, 'selected')] = oddsecchoice[event.index]
165         widget_control, event.top, update=1
166      END
167;---------------------------------
168      'evensecchoice':BEGIN
169         widget_control, event.top, update=0
170         basedomaineven=widget_info(event.top,find_by_uname = 'basedomaineven')
171         widget_control, basedomaineven, get_uvalue = evensecchoice
172         domainpart, top_uvalue, basedomaineven, evensecchoice[event.index]
173         *top_uvalue[1, findline(top_uvalue, 'selected')] = evensecchoice[event.index]
174         widget_control, event.top, update=1
175      END
176;---------------------------------
177      'odd-evensecchoice':BEGIN
178         widget_control, event.top, update=0
179         basedomainoddeven=widget_info(event.top,find_by_uname = 'basedomainodd-even')
180         widget_control, basedomainoddeven, get_uvalue = oddevensecchoice
181         domainpart, top_uvalue, basedomainoddeven, oddevensecchoice[event.index]
182         *top_uvalue[1, findline(top_uvalue, 'selected')] = oddevensecchoice[event.index]
183         widget_control, event.top, update=1
184      END
185;---------------------------------
186      'date1':BEGIN
187         date2id = widget_info(event.top, find_by_uname = 'date2')
188         widget_control, date2id, get_value = date2
189         if event.value GT date2 then widget_control, date2id, set_value = event.value
190      END
191;---------------------------------
192      'date2':BEGIN
193         date1id = widget_info(event.top, find_by_uname = 'date1')
194         widget_control, date1id, get_value = date1
195         if event.value LT date1 then widget_control, date1id, set_value = event.value
196      END
197;---------------------------------
198      else:
199   endcase
200   return
201end
202;
203;+
204;
205; @file_comments
206; Read the Hope grid file converted in NetCdf by xconv
207;
208; @categories
209; Reading
210;
211; @param TYPEIN {in}{required}{type=string}
212; A string specifying from which type of section the 4D
213; array based: 'xy, 'xz', 'yz'
214;
215; @param VARNAMEIN {in}{required}{type=string}
216; A string the name of the variable to be read (in
217; lower or upper case)
218;
219; @keyword FILENAME {type=string}
220; The name of the file to be read
221;
222; @keyword XLIMITS {type=vector}
223; A two elements vector [lonmin, lonmax]]
224; the boundary of the longitudes (from 0 to 360)
225;
226; @keyword YLIMITS {type=vector}
227; A two elements vector [latmin, latmax]]
228; the boundary of the latitudes (from -90 to 90)
229;
230; @keyword ZLIMITS {type=vector}
231; A two elements vector [depthmin, depthmax]]
232; the boundary of the depth
233;
234; @keyword TLIMITS {type=vector}
235; A two elements vector [date1, date2]]
236; the boundary of the calendar with date1 and date2
237; following the syntax yyyymmdd
238;
239; @keyword ODDPT
240; Activate to read only the sections located on ODD
241; points
242;
243; @keyword EVENPT
244; Activate to read only the sections located on even
245; points
246;
247; @keyword ODDEVENPT
248; Activate to read only the sections located on
249; both even and odd points (horizontal sections)
250;
251; @keyword _EXTRA
252; Used to pass keywords
253;
254; @returns
255; -1 if typein and varnamein are undefined (this is the widget
256; version)
257;
258; A structure which but be read by <pro>litchamp</pro> and is
259; necessary to complete the grid associated to the data (see
260; the example).
261;
262; @uses
263; common.pro (useful only for the definition of iodir)
264;
265; @restrictions
266; 'x', 'y', 'z', 't', 'xt', 'yt' and 'zt' section not coded, xconv
267; must be able to works with this kind of function.
268; The grid file has no zoom possibilities on horizontal dimensions.
269;
270; @restrictions
271;
272; When typein and varnamein are defined, the method to find the
273; good variable is:
274;  1) find the variables which are available on this type of
275; sections with this name
276;  2) if ODDPT, EVENPT or ODDEVENPT are specified, consider only
277; these types of sections
278;  3) For an XY section the chosen variable is the one which has
279; the most level in the vertical domain specified by ZLIMITS.
280;     For an XZ section the chosen variable is the one which has
281; the most points in the latitude domain specified by YLIMITS.
282;     For an YZ section the chosen variable is the one which has
283; the most points in the longitude domain specified by XLIMITS.
284;
285;
286; @examples
287;
288;     IDL> a=read_hope('xy','ocpt',filename='CLIM_CNT_1993-1998.nc')
289;     IDL> help, a,/struct
290;     ** Structure <82ec344>, 6 tags, length=1860176, refs=1:
291;        ARRAY           FLOAT     Array[128, 242, 15]
292;        UNIT            STRING    'deg C'
293;        NAME            STRING    'Ocean potential temperature'
294;        DATE            FLOAT     Array[1]
295;        GRID            STRING    'T'
296;        HOPEGRID        STRUCT    -> <Anonymous> Array[1]
297;     IDL> help, a.hopegrid,/struct
298;     ** Structure <82eb9cc>, 8 tags, length=1588, refs=2:
299;        XAXIS           FLOAT     Array[128]
300;        YAXIS           FLOAT     Array[242]
301;        ZAXIS           FLOAT     Array[15]
302;        FIRSTS          LONG      Array[3]
303;        LASTS           LONG      Array[3]
304;        TYPE            STRING    'xy'
305;        LINETYPE        STRING    'odd-even'
306;        PTTYPE          STRING    'T'
307;     IDL> help, litchamp(a)
308;     <Expression>    FLOAT     = Array[128, 242, 15]
309;
310; @history
311; Sebastien Masson (smasson\@lodyc.jussieu.fr)
312;                      June 2001
313;
314; @version
315; $Id$
316;
317;-
318;
319FUNCTION read_hope, typein, varnamein, FILENAME = filename, XLIMITS = xlimits, YLIMITS = ylimits,  ZLIMITS = zlimits, TLIMITS = tlimits, ODDPT = oddpt, ODDEVENPT = oddevenpt, EVENPT = evenpt, _extra = ex
320;
321  compile_opt idl2, strictarrsubs
322;
323@common                         ; usefull only for the definition of iodir
324  if n_elements(filename) EQ 0 then filename = isafile(iodirectory = iodir, _extra = ex)
325  IF size(filename, /type) NE 7 THEN return, -1
326  filename = isafile(filename = filename, iodirectory = iodir, _extra = ex)
327;
328  cdfid = ncdf_open(filename)       ; id of the netcdf file
329  wathinside = ncdf_inquire(cdfid)  ; structure with global informations
330;-------------------------------
331;  dimensions
332;-------------------------------
333  namedim = strarr(wathinside.ndims)  ; name of the dimensions
334  typedim = strarr(wathinside.ndims)  ; type of the dimensions (x,y,z,t)
335  sizedim = lonarr(wathinside.ndims)  ; size of each dimension
336; loop on the dimensions to get the names and sizes
337  for dimiq = 0, wathinside.ndims-1 do begin
338    ncdf_diminq, cdfid, dimiq, name, value
339    namedim[dimiq] = name
340    case 1 of
341      STRCMP(name, 'lon', 3, /FOLD_CASE):typedim[dimiq] = 'x'
342      STRCMP(name, 'lat', 3, /FOLD_CASE):typedim[dimiq] = 'y'
343      STRCMP(name, 'z', 1, /FOLD_CASE):typedim[dimiq] = 'z'
344      STRCMP(name, 't', 1, /FOLD_CASE):typedim[dimiq] = 't'
345      ELSE:BEGIN
346        ncdf_close, cdfid
347        return, report('Unknown name of dimension')
348      END
349    endcase
350    sizedim[dimiq] = value
351  endfor
352; dimlist: structure which contains the name and the value of each
353; dimension
354; we suppose that there is always a variable which has the
355; same name that the dimension and which gives the values of
356; this dimension
357  ncdf_varget, cdfid, namedim[0], value
358  dimlist = create_struct(namedim[0], value)
359  for dimiq = 1, wathinside.ndims-1 do begin
360    ncdf_varget, cdfid, namedim[dimiq], value ;get the value
361    dimlist = create_struct(dimlist, namedim[dimiq], value)
362  endfor
363;-------------------------------
364;  variables
365;-------------------------------
366  namevar = strarr(wathinside.nvars)   ; names of the variables
367  ndimsvar = lonarr(wathinside.nvars)  ; number of dim for each variable
368  dimvar = replicate(-1, wathinside.ndims, wathinside.nvars) ; dims of each variables
369; loop over the variable ids to fill namevar, ndimsvar and dimvar
370  for varid = 0, wathinside.nvars-1 do begin
371    res = ncdf_varinq(cdfid, varid)
372    namevar[varid] = res.name
373    namevar[varid] = strjoin(strsplit(namevar[varid], '_[0-99]', /EXTRACT, /REGEX))
374    ndimsvar[varid] = res.ndims
375    dimvar[0:res.ndims-1, varid] = res.dim
376  ENDFOR
377; we cut dimvar to select only the interessant part
378  dimvar = dimvar[0:max(ndimsvar)-1, *]
379; selection of the data variables which are different from the
380; dimension variables
381; we suppose that that data variables are 4D array (with sometime
382; dimensions equal to 1). they must be different from dimension
383; variables which have only 1 dimension
384  datavarid = where(ndimsvar eq 4)
385  numberofvar = n_elements(datavarid)
386  namevar = namevar[datavarid]
387  ndimsvar = ndimsvar[datavarid]
388  dimvar = dimvar[*, datavarid]
389;
390  sectype = strarr(numberofvar) ; the type of section for each variable :'xy', 'xz', 'yz'...
391  linetype = strarr(numberofvar) ; the line of the points : odd, even or odd-even
392  pointtype = strarr(numberofvar) ; the type of variable : scalar ('T') or vector ('U')
393  for i = 0, numberofvar-1 do begin
394    dimofthevar = dimvar[*, i]
395    sectype[i] = typedim[dimofthevar[0]]+typedim[dimofthevar[1]]
396    xaxisid = dimofthevar[where(typedim[dimofthevar] EQ 'x')]
397    yaxisid = dimofthevar[where(typedim[dimofthevar] EQ 'y')]
398    lineandpt = findlineandpointtype(sectype[i], dimlist.(xaxisid[0]), dimlist.(yaxisid[0]), iodir)
399    linetype[i] = lineandpt.linetype
400    pointtype[i] = lineandpt.pointtype
401  endfor
402;
403;---------------------------------------------------
404;---------------------------------------------------
405;---------------------------------------------------
406;  definition of the widget
407;---------------------------------------------------
408;---------------------------------------------------
409;---------------------------------------------------
410  base = widget_base(/column)
411;---------------------------------------------------
412; first base:
413;    droplist to select the type of section
414;    droplist to select the variable
415;    button to select type of line : odd, even or odd-even
416;---------------------------------------------------
417  base1 = widget_base(base, /row, /frame)
418  typechoice = sectype[uniq(sectype, sort(sectype))]
419  if n_elements(typechoice) GT 1 then typechoice = typechoice[sortdim(typechoice)]
420  base11 = widget_droplist(base1, title = 'Type of section', value = typechoice, uvalue = {name:'type choice'}, uname = 'type choice')
421  if n_elements(typein) NE 0 then BEGIN
422    selectedtype = strmid(typein, 0, 2)
423    widget_control, base11, set_droplist_select $
424                    = 0L > (where(typechoice EQ selectedtype))[0]
425  ENDIF ELSE selectedtype = typechoice[0]
426;
427  varchoice = namevar[uniq(namevar, sort(namevar))]
428  base12 = widget_droplist(base1, title = 'Available data', value = varchoice, uvalue = {name:'var choice'}, uname = 'var choice')
429  if n_elements(varnamein) NE 0 THEN BEGIN
430    selectedname = varnamein
431    widget_control, base12, set_droplist_select $
432                    = 0L > (where(strlowcase(varchoice) EQ strlowcase(varnamein)))[0]
433  ENDIF ELSE selectedname = varchoice[0]
434;
435  base13 = widget_base(base1, /row, uname = 'linechoicebase')
436;---------------------------------------------------
437; base 2: base to select the domain of the odd points
438;---------------------------------------------------
439  base2 = widget_base(base, /column, uname = 'basedomainodd', /frame)
440;---------------------------------------------------
441; base 3: base to select the domain of the even points
442;---------------------------------------------------
443  base3 = widget_base(base, /column, uname = 'basedomaineven', /frame)
444;---------------------------------------------------
445; base 4: base to select the domain of the odd-even points
446;---------------------------------------------------
447  base4 = widget_base(base, /column, uname = 'basedomainodd-even', /frame)
448;---------------------------------------------------
449; base 5: calendar
450;---------------------------------------------------
451  base5 = widget_base(base, /row, uname = 'baset', /frame)
452  timename = strlowcase((tag_names(dimlist))[wathinside.recdim])
453; read the time axis in julina days
454  time = ncdf_timeget(cdfid, timename)
455; update the dimlist structure
456  dimlist.(wathinside.recdim) = time
457  base51 = cw_calendar(base5, time, uname = 'date1', uvalue = {name:'date1'})
458  base52 = cw_calendar(base5, time, uname = 'date2', uvalue = {name:'date2'})
459;---------------------------------------------------
460;  base 6: base to select the min, max, ... and others keywords
461;---------------------------------------------------
462  base6 = cw_specifie(base, /column, uname = 'specifie', uvalue = {name:'specifie'})
463;---------------------------------------------------
464;  base 7: last base with the action buttons
465;---------------------------------------------------
466  base7 = widget_base(base, /row, uname = 'finalaction')
467  base71 = widget_button(base7, value = 'Plot', uvalue = {name:'plot'})
468  base72 = widget_button(base7, value = 'Cancel', uvalue = {name:'cancel'})
469;---------------------------------------------------
470; determination of the selected variable ......
471;---------------------------------------------------
472  goodname = 0 > where(strlowcase(namevar) EQ strlowcase(selectedname))
473  goodtype = 0 > where(sectype EQ selectedtype)
474  selected = inter(goodname, goodtype)
475  if selected[0] EQ -1 then BEGIN
476    widget_control, base, /destroy
477    ncdf_close, cdfid
478    return, report('impossible combinaison : type of section '+selectedtype+', variable name '+selectedname)
479  ENDIF
480  if n_elements(typein) NE 0 then BEGIN
481    if NOT keyword_set(xlimits) then xlimits = [-1e9, 1e9]
482    if NOT keyword_set(ylimits) then ylimits = [-1e9, 1e9]
483    if NOT keyword_set(zlimits) then zlimits = [-1e9, 1e9]
484    if NOT keyword_set(tlimits) then tlimits = [-1e9, 1e9]
485  ENDIF
486  if n_elements(typein) NE 0 AND n_elements(selected) NE 1 then BEGIN
487    if keyword_set(oddpt) then selected = inter(selected, where(linetype EQ 'odd'))
488    if keyword_set(evenpt) then selected = inter(selected, where(linetype EQ 'even'))
489    if keyword_set(oddevenpt) then selected = inter(selected, where(linetype EQ 'odd-even'))
490    if selected[0] EQ -1 then BEGIN
491      widget_control, base, /destroy
492      ncdf_close, cdfid
493      return, report('impossible combinaison : type of section '+selectedtype+', variable name '+selectedname+' and line type ')
494    endif
495    if n_elements(selected) NE 1 then begin
496      case selectedtype of
497        'xy':BEGIN
498; choice on the vertical axis
499; choice based on the variable which has the most available levels
500; between the zlimits.
501          if NOT keyword_set(zlimits) then begin
502            print, 'case not coded...'
503            stop
504          ENDIF
505          number = lonarr(n_elements(selected))
506          for i = 0, n_elements(selected)-1 do begin
507            zdim = dimvar[2, selected[i]]
508            zaxis = dimlist.(zdim)
509            nothing = where(zaxis GE zlimits[0] AND zaxis LE zlimits[1], count)
510            number[i] = count
511          ENDFOR
512          selected = selected[where(number EQ max(number))]
513          if n_elements(selected) NE 1 then begin
514            print, 'case not coded...'
515            stop
516          endif
517        END
518        'xz':BEGIN
519; choice on the latitude axis
520          if NOT keyword_set(ylimits) then begin
521            print, 'case not coded...'
522            stop
523          ENDIF
524          number = lonarr(n_elements(selected))
525          for i = 0, n_elements(selected)-1 do begin
526            ydim = dimvar[2, selected[i]]
527            yaxis = dimlist.(ydim)
528            nothing = where(yaxis GE ylimits[0] AND yaxis LE ylimits[1], count)
529            number[i] = count
530          ENDFOR
531          selected = selected[where(number EQ max(number))]
532          if n_elements(selected) NE 1 then begin
533            print, 'case not coded...'
534            stop
535          endif
536        END
537        'yz':BEGIN
538; choice on the longitude axis
539          if NOT keyword_set(xlimits) then begin
540            print, 'case not coded...'
541            stop
542          ENDIF
543          number = lonarr(n_elements(selected))
544          for i = 0, n_elements(selected)-1 do begin
545            xdim = dimvar[2, selected[i]]
546            xaxis = dimlist.(xdim)
547            nothing = where(xaxis GE xlimits[0] AND xaxis LE xlimits[1], count)
548            number[i] = count
549          ENDFOR
550          selected = selected[where(number EQ max(number))]
551          if n_elements(selected) NE 1 then begin
552            print, 'case not coded...'
553            stop
554          endif
555        END
556      endcase
557    endif
558  ENDIF
559;---------------------------------------------------
560; definition of the uvalue of the base which allows to share the
561; variables between programs.
562;---------------------------------------------------
563  top_uvalue = ptrarr(2, 18, /allocate_heap)
564  *top_uvalue[0, 0] = 'type choice' & *top_uvalue[1, 0] = temporary(typechoice)
565  *top_uvalue[0, 1] = 'var choice' & *top_uvalue[1, 1] = temporary(varchoice)
566  *top_uvalue[0, 2] = 'namevar' & *top_uvalue[1, 2] = temporary(namevar)
567  *top_uvalue[0, 3] = 'dimvar' & *top_uvalue[1, 3] = temporary(dimvar)
568  *top_uvalue[0, 4] = 'sectype' & *top_uvalue[1, 4] = temporary(sectype)
569  *top_uvalue[0, 5] = 'linetype' & *top_uvalue[1, 5] = temporary(linetype)
570  *top_uvalue[0, 6] = 'pointtype' & *top_uvalue[1, 6] = temporary(pointtype)
571  *top_uvalue[0, 7] = 'dimlist' & *top_uvalue[1, 7] = temporary(dimlist)
572  *top_uvalue[0, 8] = 'typedim' & *top_uvalue[1, 8] = temporary(typedim)
573  *top_uvalue[0, 9] = 'sizedim' & *top_uvalue[1, 9] = temporary(sizedim)
574  *top_uvalue[0, 10] = 'cdfid' & *top_uvalue[1, 10] = cdfid
575  *top_uvalue[0, 11] = 'datavarid' & *top_uvalue[1, 11] = datavarid
576  *top_uvalue[0, 12] = 'selected' & *top_uvalue[1, 12] = selected
577  *top_uvalue[0, 13] = 'filename' & *top_uvalue[1, 13] = filename
578  *top_uvalue[0, 14] = 'xlimits' & *top_uvalue[1, 14] = testvar(var = xlimits)
579  *top_uvalue[0, 15] = 'ylimits' & *top_uvalue[1, 15] = testvar(var = ylimits)
580  *top_uvalue[0, 16] = 'zlimits' & *top_uvalue[1, 16] = testvar(var = zlimits)
581  *top_uvalue[0, 17] = 'tlimits' & *top_uvalue[1, 17] = testvar(var = tlimits)
582
583
584  widget_control, base, set_uvalue = top_uvalue
585  rh_alldomains, base, selected
586
587  if n_params() EQ 0 then BEGIN
588; we use the widget
589    widget_control, base, /REALIZE
590    xmanager, 'read_hope', base, /no_block
591    return,  -1
592  ENDIF
593; get the output
594  output = createhopestruct({top:base})
595; clear the pointer
596  for i = 0, n_elements(top_uvalue)-1 do ptr_free, top_uvalue[i]
597; close the file
598  ncdf_close, cdfid
599  return, output
600end
Note: See TracBrowser for help on using the repository browser.