source: trunk/procs/def_work.pro

Last change on this file was 211, checked in by ericg, 14 years ago

Clearer message for convert line

  • Property svn:keywords set to Id
File size: 13.7 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;      IF debug_w THEN print, '    iline = ', iline, ' ', cmdline(iline)
172
173      cmd = decode_cmd(cmdline, iline)
174
175      IF out_all NE '-'  THEN BEGIN
176       cmd.out = out_all
177      ENDIF
178
179      IF cmd.on EQ 1 THEN BEGIN
180         IF debug_w THEN BEGIN
181          print, '    iline = ', iline
182         ENDIF
183         iplot = iplot + 1
184         print, ' '
185         print, ' -------------'
186         print, ' Plot No.', iplot, format = '(A10,I2)'
187         print, ' -------------'
188         print, ' '
189         printf, nulhis, ' '
190         printf, nulhis, ' -------------'
191         printf, nulhis, ' Plot No.', iplot, format = '(A10,I2)'
192         printf, nulhis, ' -------------'
193         printf, nulhis, ' '
194
195
196         ; format of output
197
198         posP = rstrpos(cmd.disp, 'P')
199         posL = rstrpos(cmd.disp, 'L')
200         len = strlen(cmd.disp)
201         IF posP GE 0 THEN BEGIN
202            landscape = 0
203            key_portrait = 1
204         ENDIF ELSE BEGIN
205            landscape = 1
206            key_portrait = 0
207         ENDELSE
208
209         IF strmid(cmd.out, 0, 2) EQ 'ps' THEN BEGIN
210            reinitplt, /z,/invert
211            fileps = 'idl_out_p'+strtrim(string(iplot), 2)+'.ps'
212            openps, out_ps+fileps
213            set_ps_devices
214         ENDIF ELSE BEGIN
215            set_plot,dev_type
216            set_x_devices
217         ENDELSE
218
219         ; windows management : decode cmd.disp = n[xm][or]
220
221         display = cmd.disp
222         IF posP GT 0 OR posL GT 0 THEN BEGIN
223          display = strmid(cmd.disp, 0, len-1)
224         ENDIF
225         posx = rstrpos(display, 'x')
226         IF posx GT 0 THEN BEGIN
227            nwin = long(strmid(display, 0, posx))
228            mwin = long(strmid(display, posx+1, len-posx+1))
229         ENDIF ELSE BEGIN
230            IF posP GT 0 THEN BEGIN
231               nwin = 1
232               mwin = long(display)
233            ENDIF ELSE BEGIN
234               nwin = long(display)
235               mwin = 1
236            ENDELSE
237         ENDELSE
238         nwin_tot = nwin*mwin
239
240         ; plot inits
241
242         idx_pal = 0
243         iwin = 1
244         nb_lines = 0
245
246         ; make loop on number of windows
247         WHILE iwin LE nwin*mwin DO BEGIN
248
249            index_over = 0
250
251            win = [nwin, mwin, iwin]
252
253            idx = iline + nb_lines
254
255            cmdi = decode_cmd(cmdline, idx)
256            cmdm = cmdi
257
258            ; specific formatting for legend
259            leg_format = ''
260            IF strpos(cmdi.proj, '[') NE -1 THEN BEGIN
261               leg_format = extract_str(cmdi.proj, '[', ']')
262               cmdi.proj = strmid(cmdi.proj, 0, strpos(cmdi.proj, '['))
263            ENDIF ELSE BEGIN
264               leg_format = default_txt_format
265            ENDELSE
266
267            ; decode proj for number of overlays in window (min=1)
268            overl = strpos(cmdi.proj, 'o')
269            IF overl GE 0 THEN BEGIN
270               nover = 1+max([1, long(strmid(cmdi.proj, overl+1, strlen(cmdi.proj)-overl-1))])
271            ENDIF ELSE BEGIN
272               nover = 1
273            ENDELSE
274
275            nadd = nover
276
277            ; make loop on number of overlays
278            iover = 1
279            inext = 0
280            WHILE iover LE nover DO BEGIN
281
282               idx = iline + nb_lines + iover + inext - 1
283               cmdo = decode_cmd(cmdline, idx)
284               idx_main=idx
285
286               IF debug_w THEN BEGIN
287                  print, ' In def_work:'
288                  print, ' plot,window,overlay, inext = ', iplot, iwin, iover, inext
289                  print, '     max win, max over = ', nwin, nover
290                  print, ' index = ', idx
291               ENDIF
292
293               ; make overlay
294
295               plt_map, cmdo, iplot, win, iover, landscape
296
297               ; end of loop on overlays
298               iover = iover+1
299               ; special case y=f(next) on 2 lines
300
301               IF strpos(cmdi.var, '(next)') GT -1 THEN BEGIN
302                  inext = inext + 1
303                  nadd = nadd + 1
304               ENDIF ELSE BEGIN
305                  inext = 0
306               ENDELSE
307
308            ENDWHILE
309            nb_lines = nb_lines + nadd
310
311
312         ; end of loop on windows
313            iwin = iwin + 1
314         ENDWHILE
315
316
317         ; close ps
318
319         IF strmid(cmd.out, 0, 2) EQ 'ps' THEN BEGIN
320            iodir = out_ps
321            closeps
322            ; save to file
323            IF save_ps GE 1 THEN BEGIN
324                  CASE file_naming OF
325                     'prompt': BEGIN ; interactive mode
326                        IF strmid(cmd.out, 0, 3) ne 'psm' OR  movie_count EQ 0 THEN BEGIN
327                        ; open last name file
328                           get_lun, nullst
329                           openr, nullst, '.last_name_post'
330                           dir_name = ' '
331                           file_name = ' '
332                           readf, nullst, dir_name
333                           readf, nullst, file_name
334                           close, nullst
335                           free_lun, nullst
336                           print, ' Save PostScript '+strtrim(string(iplot), 2)+' file to ( - to ignore / save_ps=0 to turn off - NO EXTENSIONS PLEASE) :'
337                           print, '  directory is (d to change) : '+dir_name
338                           nfile_name = xquestion('       ', file_name, /chkwid)
339                           nfile_name = strtrim(nfile_name, 2)
340                           IF nfile_name NE '-' THEN BEGIN
341                              IF nfile_name EQ 'd' THEN BEGIN
342                                 dir_name = xquestion(' New Directory ', dir_name, /chkwid)
343                                 nfile_name = xquestion(' New file', file_name, /chkwid)
344                              ENDIF
345                              openw, nullst, '.last_name_post'
346                              printf, nullst, dir_name
347                              printf, nullst, nfile_name
348                              close, nullst
349                              free_lun, nullst
350                           ENDIF ELSE BEGIN
351                              print, '  Do not save - OK'
352                           ENDELSE
353                           IF strmid(cmd.out, 0, 3) eq 'psm' THEN BEGIN
354;              movie stuff (slide 1)
355                              print, '  movie series, will create file_<n> files'
356                              file_suffix = '_'+strtrim(string(movie_count+1), 2)
357                              movie_count = movie_count + 1
358                           ENDIF ELSE BEGIN
359                              file_suffix = ''
360                           ENDELSE
361                        ENDIF ELSE BEGIN
362;              movie stuff (slides >1 )
363                           get_lun, nullst
364                           openr, nullst, '.last_name_post'
365                           dir_name = ' '
366                           file_name = ' '
367                           readf, nullst, dir_name
368                           readf, nullst, nfile_name
369                           close, nullst
370                           free_lun, nullst
371                           file_suffix = '_'+strtrim(string(movie_count+1), 2)
372                           movie_count = movie_count + 1
373                           print, '  saving file <base name>= '+nfile_name+file_suffix
374                        ENDELSE
375                     END
376                     ELSE: BEGIN ; auto mode
377;                        def_out_name, fileps >>> TO IMPLEMENT (analyse content of plots for proper naming)
378                        dir_name = out_ps
379                        nfile_name = cmd.exp+'_'+ cmd.var+'_'+cmd.plt+'_'+cmd.timave+'_'+cmd.date1+'_'+cmd.spec+'_'+cmd.disp
380                        file_suffix = '_p'+strtrim(string(iplot), 2)
381                     END
382                  ENDCASE
383                  ; conversion (pdf or gif)
384                  IF save_ps EQ 2 THEN BEGIN
385                                ; PDF
386                     conv = 'ps2pdf  -g6000x8300 '
387                     ;;IF landscape EQ 1 THEN BEGIN
388                     ;;   conv = conv+'-rotate -90 '
389                     ;;ENDIF
390                     print, '  converting to pdf...'
391                     ext = '.pdf'
392
393                  ENDIF ELSE BEGIN
394                     conv = 'cp '
395                     ext = '.ps'
396                  ENDELSE
397                  IF strpos(cmd.out, 'gif') NE -1 THEN BEGIN
398                     conv = 'convert '
399                     IF landscape EQ 1 THEN BEGIN
400                        conv = conv+'-rotate -90 '
401                     ENDIF
402                     print, '  converting to gif... to make the movie use:'
403                     print, '     convert -delay 50 -loop 100 image_?.gif image_??.gif image_???.gif movie.gif'
404                     ext = '.gif'
405                  ENDIF
406
407                  line = conv+out_ps+'/'+fileps+' '+dir_name+'/'+nfile_name+file_suffix+ext
408                  IF debug_w THEN BEGIN
409                   print, '  Convert command (set in def_work.pro) = ', line
410                  ENDIF
411                  spawn, line, prtout
412                  print, '   '
413                  print, ' -> saving file ', dir_name+nfile_name+file_suffix+ext
414
415            ENDIF
416            IF strlen(cmd.out) EQ 3 AND strmid(cmd.out, 0, 3) NE 'psm' THEN BEGIN
417               CASE cmd.out OF
418                  'psb': BEGIN & mess = 'printer' & cmdf = prt_BW & END
419                  'psc': BEGIN & mess = 'color printer' & cmdf = prt_col & END
420                  'pst': BEGIN & mess = 'transp printer' & cmdf = prt_tra & END
421                  ELSE: BEGIN & mess = 'ghostview ' & cmdf = ghost & END
422               ENDCASE
423               print, ' '
424               print, '    Sending ', nfile_name+'_'+cmdf, ' to ', mess, ' (',cmdf, ' + option ',lp_opt, ')'
425               line = 'cd '+out_ps+'; \cp '+fileps+' '+fileps+'_'+cmdf+'; '+homedir+'bin/'+cmdf+' '+fileps+'_'+cmdf+' '+lp_opt+'; cd '+hom_idl
426               spawn, line, prtout
427               print, prtout
428
429            ENDIF ELSE BEGIN
430               mess = 'ps'
431            ENDELSE
432         ENDIF ELSE BEGIN
433
434           ; NO ps: next plot/data
435
436            CASE cmd.out OF
437               'cdf':
438               ELSE: BEGIN
439                  ready = ''
440                  read,'<Return> for next plot ', ready
441               END
442            ENDCASE
443         ENDELSE
444
445      ENDIF ELSE BEGIN
446         nb_lines = 1
447      ENDELSE
448
449      ; end of loop on command lines
450      iline = iline + nb_lines
451
452   ENDWHILE
453
454   ; close history file
455
456   free_lun, nulhis
457   close, nulhis
458
459   IF debug_w THEN BEGIN
460    info = report('leaving ...')
461   ENDIF
462
463END
Note: See TracBrowser for help on using the repository browser.