source: trunk/procs/def_work.pro @ 205

Last change on this file since 205 was 205, checked in by pinsard, 14 years ago

homegenize THEN BEGIN ... ENDIF

  • Property svn:keywords set to Id
File size: 13.5 KB
Line 
1;+
2;
3; reads each command line
4;
5; calls <propost_it>plt_map</pro_post_it> for each plot/window/overlay
6;
7; @param DATA_BASE_LIST {in}{required}{type=string}
8;
9; @param OUT_PS {in}{required}{type=string}
10;
11; @param CMDLINE {in}{required}{type=array of strings}
12;
13; @param OUT_ALL {in}{required}{type=string}
14;
15; @param OTHER_FILE {in}{required}{type=string}
16;
17; @param SPEC_BASE_LIST {in}{required}{type=string}
18;
19; @examples
20; IDL> data_base_list='local:.'
21; IDL> out_ps='./'
22; IDL> cmdline=['temp_1 0 HH1 umath xy 1m 199201 - 1 1 v']
23; IDL> out_all='-'
24; IDL> other_file='-'
25; IDL> spec_base_list='local:.'
26; IDL> def_work, data_base_list, out_ps, cmdline, out_all, other_file, spec_base_list
27;
28; @uses
29; <pro>common</pro>
30; <propost_it>com_eg</propost_it>
31;
32; <propost_it>decode_cmd</propost_it>
33; <propost_it>plt_map</propost_it>
34;
35; @todo
36; get rid of spawn
37;
38; realistic examples
39;
40; test if it is allowed to open and write ./.hist_post_it
41;
42; what is the purpose of  ./.hist_post_it ?
43;
44; @history
45; - fplod 20091209T094630Z aedon.locean-ipsl.upmc.fr (Darwin)
46;
47;   * check parameters
48;
49; - 11-6-99 EG
50;
51; @version
52; $Id$
53;
54;-
55PRO def_work, data_base_list, out_ps, cmdline, out_all, other_file, spec_base_list
56;
57  compile_opt idl2, strictarrsubs
58;
59@common
60@com_eg
61
62; Return to caller if errors
63 ON_ERROR, 2
64;
65 IF debug_w THEN BEGIN
66  info = report('enter ...')
67 ENDIF
68;
69 usage='def_work, data_base_list, out_ps, cmdline, out_all, other_file, spec_base_list'
70;
71 nparam = N_PARAMS()
72 IF (nparam LT 6) THEN BEGIN
73    ras = report(['Incorrect number of arguments.' $
74          + '!C' $
75          + 'Usage : ' + usage])
76    stop
77 ENDIF
78 arg_type = size(data_base_list,/type)
79 IF (arg_type NE 7) THEN BEGIN
80   ras = report(['Incorrect arg type data_base_list' $
81          + '!C' $
82          + 'Usage : ' + usage])
83   stop
84 ENDIF
85 arg_type = size(out_ps,/type)
86 IF (arg_type NE 7) THEN BEGIN
87   ras = report(['Incorrect arg type out_ps' $
88          + '!C' $
89          + 'Usage : ' + usage])
90   stop
91 ENDIF
92 arg_type = size(cmdline,/type)
93 IF (arg_type NE 7) THEN BEGIN
94   ras = report(['Incorrect arg type cmdline' $
95          + '!C' $
96          + 'Usage : ' + usage])
97   stop
98 ENDIF
99 arg_type = size(out_all,/type)
100 IF (arg_type NE 7) THEN BEGIN
101   ras = report(['Incorrect arg type out_all' $
102          + '!C' $
103          + 'Usage : ' + usage])
104   stop
105 ENDIF
106 arg_type = size(other_file,/type)
107 IF (arg_type NE 7) THEN BEGIN
108   ras = report(['Incorrect arg type other_file' $
109          + '!C' $
110          + 'Usage : ' + usage])
111   stop
112 ENDIF
113 arg_type = size(spec_base_list,/type)
114 IF (arg_type NE 7) THEN BEGIN
115   ras = report(['Incorrect arg type spec_base_list' $
116          + '!C' $
117          + 'Usage : ' + usage])
118   stop
119 ENDIF
120
121; Data bases
122   data_bases = data_base_list
123   spec_bases = spec_base_list
124
125;
126; Graphic init
127; set plot graphic defaults
128   resolve_routine, 'plt_def'
129   plt_def
130
131; other inits
132   fld_flag = 1
133;
134; other input file ?
135;
136IF other_file NE '-' THEN BEGIN
137
138   resolve_routine, other_file
139   res = execute(other_file)
140
141   cmdline = cmdline2
142
143ENDIF
144
145cmdline_main = cmdline
146
147;
148; Field init
149;
150   fld_prev = '-'
151   movie_count = 0
152
153; Open history file
154;
155   get_lun, nulhis
156   openw, nulhis, '.hist_post_it'
157;
158;
159; Interpret command lines
160;
161   nlines = n_elements(cmdline)
162   IF nlines LE 1 THEN BEGIN
163    info = report('cmdline empty so nothing to be plot',/SIMPLE)
164    stop
165   ENDIF
166;
167   iline = 0
168   iplot = 0
169
170   WHILE iline LE nlines-2 DO BEGIN
171
172      cmd = decode_cmd(cmdline, iline)
173
174      IF out_all NE '-'  THEN BEGIN
175       cmd.out = out_all
176      ENDIF
177
178      IF cmd.on EQ 1 THEN BEGIN
179         IF debug_w THEN BEGIN
180          print, '    iline = ', iline
181         ENDIF
182         iplot = iplot + 1
183         print, ' '
184         print, ' -------------'
185         print, ' Plot No.', iplot, format = '(A10,I2)'
186         print, ' -------------'
187         print, ' '
188         printf, nulhis, ' '
189         printf, nulhis, ' -------------'
190         printf, nulhis, ' Plot No.', iplot, format = '(A10,I2)'
191         printf, nulhis, ' -------------'
192         printf, nulhis, ' '
193
194
195         ; format of output
196
197         posP = rstrpos(cmd.disp, 'P')
198         posL = rstrpos(cmd.disp, 'L')
199         len = strlen(cmd.disp)
200         IF posP GE 0 THEN BEGIN
201            landscape = 0
202            key_portrait = 1
203         ENDIF ELSE BEGIN
204            landscape = 1
205            key_portrait = 0
206         ENDELSE
207
208         IF strmid(cmd.out, 0, 2) EQ 'ps' THEN BEGIN
209            reinitplt, /z,/invert
210            fileps = 'idl_out_p'+strtrim(string(iplot), 2)+'.ps'
211            openps, out_ps+fileps
212            set_ps_devices
213         ENDIF ELSE BEGIN
214            set_plot,dev_type
215            set_x_devices
216         ENDELSE
217
218         ; windows management : decode cmd.disp = n[xm][or]
219
220         display = cmd.disp
221         IF posP GT 0 OR posL GT 0 THEN BEGIN
222          display = strmid(cmd.disp, 0, len-1)
223         ENDIF
224         posx = rstrpos(display, 'x')
225         IF posx GT 0 THEN BEGIN
226            nwin = long(strmid(display, 0, posx))
227            mwin = long(strmid(display, posx+1, len-posx+1))
228         ENDIF ELSE BEGIN
229            IF posP GT 0 THEN BEGIN
230               nwin = 1
231               mwin = long(display)
232            ENDIF ELSE BEGIN
233               nwin = long(display)
234               mwin = 1
235            ENDELSE
236         ENDELSE
237         nwin_tot = nwin*mwin
238
239         ; plot inits
240
241         idx_pal = 0
242         iwin = 1
243         nb_lines = 0
244
245         ; make loop on number of windows
246         WHILE iwin LE nwin*mwin DO BEGIN
247
248            index_over = 0
249
250            win = [nwin, mwin, iwin]
251
252            idx = iline + nb_lines
253
254            cmdi = decode_cmd(cmdline, idx)
255            cmdm = cmdi
256
257            ; specific formatting for legend
258            leg_format = ''
259            IF strpos(cmdi.proj, '[') NE -1 THEN BEGIN
260               leg_format = extract_str(cmdi.proj, '[', ']')
261               cmdi.proj = strmid(cmdi.proj, 0, strpos(cmdi.proj, '['))
262            ENDIF ELSE leg_format = default_txt_format
263
264            ; decode proj for number of overlays in window (min=1)
265            overl = strpos(cmdi.proj, 'o')
266            IF overl GE 0 THEN BEGIN
267               nover = 1+max([1, long(strmid(cmdi.proj, overl+1, strlen(cmdi.proj)-overl-1))])
268            ENDIF ELSE BEGIN
269               nover = 1
270            ENDELSE
271
272            nadd = nover
273
274            ; make loop on number of overlays
275            iover = 1
276            inext = 0
277            WHILE iover LE nover DO BEGIN
278
279               idx = iline + nb_lines + iover + inext - 1
280               cmdo = decode_cmd(cmdline, idx)
281               idx_main=idx
282
283               IF debug_w THEN BEGIN
284                  print, ' In def_work:'
285                  print, ' plot,window,overlay, inext = ', iplot, iwin, iover, inext
286                  print, '     max win, max over = ', nwin, nover
287                  print, ' index = ', idx
288               ENDIF
289
290               ; make overlay
291
292               plt_map, cmdo, iplot, win, iover, landscape
293
294               ; end of loop on overlays
295               iover = iover+1
296               ; special case y=f(next) on 2 lines
297
298               IF strpos(cmdi.var, '(next)') GT -1 THEN BEGIN
299                  inext = inext + 1
300                  nadd = nadd + 1
301               ENDIF ELSE BEGIN
302                  inext = 0
303               ENDELSE
304
305            ENDWHILE
306            nb_lines = nb_lines + nadd
307
308
309         ; end of loop on windows
310            iwin = iwin + 1
311         ENDWHILE
312
313
314         ; close ps
315
316         IF strmid(cmd.out, 0, 2) EQ 'ps' THEN BEGIN
317            iodir = out_ps
318            closeps
319            ; save to file
320            IF save_ps GE 1 THEN BEGIN
321                  CASE file_naming OF
322                     'prompt': BEGIN ; interactive mode
323                        IF strmid(cmd.out, 0, 3) ne 'psm' OR  movie_count EQ 0 THEN BEGIN
324                        ; open last name file
325                           get_lun, nullst
326                           openr, nullst, '.last_name_post'
327                           dir_name = ' '
328                           file_name = ' '
329                           readf, nullst, dir_name
330                           readf, nullst, file_name
331                           close, nullst
332                           free_lun, nullst
333                           print, ' Save PostScript '+strtrim(string(iplot), 2)+' file to ( - to ignore / save_ps=0 to turn off - NO EXTENSIONS PLEASE) :'
334                           print, '  directory is (d to change) : '+dir_name
335                           nfile_name = xquestion('       ', file_name, /chkwid)
336                           nfile_name = strtrim(nfile_name, 2)
337                           IF nfile_name NE '-' THEN BEGIN
338                              IF nfile_name EQ 'd' THEN BEGIN
339                                 dir_name = xquestion(' New Directory ', dir_name, /chkwid)
340                                 nfile_name = xquestion(' New file', file_name, /chkwid)
341                              ENDIF
342                              openw, nullst, '.last_name_post'
343                              printf, nullst, dir_name
344                              printf, nullst, nfile_name
345                              close, nullst
346                              free_lun, nullst
347                           ENDIF ELSE BEGIN
348                              print, '  Do not save - OK'
349                           ENDELSE
350                           IF strmid(cmd.out, 0, 3) eq 'psm' THEN BEGIN
351;              movie stuff (slide 1)
352                              print, '  movie series, will create file_<n> files'
353                              file_suffix = '_'+strtrim(string(movie_count+1), 2)
354                              movie_count = movie_count + 1
355                           ENDIF ELSE file_suffix = ''
356                        ENDIF ELSE BEGIN
357;              movie stuff (slides >1 )
358                           get_lun, nullst
359                           openr, nullst, '.last_name_post'
360                           dir_name = ' '
361                           file_name = ' '
362                           readf, nullst, dir_name
363                           readf, nullst, nfile_name
364                           close, nullst
365                           free_lun, nullst
366                           file_suffix = '_'+strtrim(string(movie_count+1), 2)
367                           movie_count = movie_count + 1
368                           print, '  saving file <base name>= '+nfile_name+file_suffix
369                        ENDELSE
370                     END
371                     ELSE: BEGIN ; auto mode
372;                        def_out_name, fileps >>> TO IMPLEMENT (analyse content of plots for proper naming)
373                        dir_name = out_ps
374                        nfile_name = cmd.exp+'_'+ cmd.var+'_'+cmd.plt+'_'+cmd.timave+'_'+cmd.date1+'_'+cmd.spec+'_'+cmd.disp
375                        file_suffix = '_p'+strtrim(string(iplot), 2)
376                     END
377                  ENDCASE
378                  ; conversion (pdf or gif)
379                  IF save_ps EQ 2 THEN BEGIN
380                                ; PDF
381                     conv = 'ps2pdf '
382                     ;;IF landscape EQ 1 THEN BEGIN
383                     ;;   conv = conv+'-rotate -90 '
384                     ;;ENDIF
385                     print, '  converting to pdf...'
386                     ext = '.pdf'
387
388                  ENDIF ELSE BEGIN
389                     conv = 'cp '
390                     ext = '.ps'
391                  ENDELSE
392                  IF strpos(cmd.out, 'gif') NE -1 THEN BEGIN
393                     conv = 'convert '
394                     IF landscape EQ 1 THEN BEGIN
395                        conv = conv+'-rotate -90 '
396                     ENDIF
397                     print, '  converting to gif... to make the movie use:'
398                     print, '     convert -delay 50 -loop 100 image_?.gif image_??.gif image_???.gif movie.gif'
399                     ext = '.gif'
400                  ENDIF
401
402                  line = conv+out_ps+'/'+fileps+' '+dir_name+'/'+nfile_name+file_suffix+ext
403                  IF debug_w THEN BEGIN
404                   print, ' Convert command= ', line
405                  ENDIF
406                  spawn, line, prtout
407                  print, '   '
408                  print, ' -> saving file ', dir_name+nfile_name+file_suffix+ext
409
410            ENDIF
411            IF strlen(cmd.out) EQ 3 AND strmid(cmd.out, 0, 3) NE 'psm' THEN BEGIN
412               CASE cmd.out OF
413                  'psb': BEGIN & mess = 'printer' & cmdf = prt_BW & END
414                  'psc': BEGIN & mess = 'color printer' & cmdf = prt_col & END
415                  'pst': BEGIN & mess = 'transp printer' & cmdf = prt_tra & END
416                  ELSE: BEGIN & mess = 'ghostview ' & cmdf = ghost & END
417               ENDCASE
418               print, ' '
419               print, '    Sending ', nfile_name+'_'+cmdf, ' to ', mess, ' (',cmdf, ' + option ',lp_opt, ')'
420               line = 'cd '+out_ps+'; \cp '+fileps+' '+fileps+'_'+cmdf+'; '+homedir+'bin/'+cmdf+' '+fileps+'_'+cmdf+' '+lp_opt+'; cd '+hom_idl
421               spawn, line, prtout
422               print, prtout
423
424            ENDIF ELSE BEGIN
425               mess = 'ps'
426            ENDELSE
427         ENDIF ELSE BEGIN
428
429           ; NO ps: next plot/data
430
431            CASE cmd.out OF
432               'cdf':
433               ELSE: BEGIN
434                  ready = ''
435                  read,'<Return> for next plot ', ready
436               END
437            ENDCASE
438         ENDELSE
439
440      ENDIF ELSE  nb_lines = 1
441
442      ; end of loop on command lines
443      iline = iline + nb_lines
444
445   ENDWHILE
446
447   ; close history file
448
449   free_lun, nulhis
450   close, nulhis
451
452   IF debug_w THEN BEGIN
453    info = report('leaving ...')
454   ENDIF
455
456END
Note: See TracBrowser for help on using the repository browser.