source: trunk/procs/yfx.pro @ 41

Last change on this file since 41 was 41, checked in by ericg, 16 years ago

Misc modifs, incl. read_from_grid in yfx, debug_w prints, removal of mesh_lmdz and small bug corrections

File size: 19.1 KB
Line 
1         ;
2         ; ----------------------
3         ; Scatter plot y=f(x)
4         ; called by plt_map.pro
5         ; ----------------------
6         ;
7               t = tmask
8               boxx = ''
9               boxy = ''
10               add_txt = ''
11            ; arrange/average data if needed
12              ; space and time plots fld
13               IF strpos(cmd.plt, 'xy_') NE -1 THEN BEGIN
14                  mask_z, fld, cmd, boite_plt, dimplot, boxx
15                  boxx = ' ['+boxx+']'
16                  print, '   Averaging (space) '+cmd.var+' in'+boxx
17                  fld = checkfield(fld, 'plt', type = 'xy', boite = boite_plt)
18               ENDIF
19               IF datyp.hotyp NE '-' THEN BEGIN
20                  mask_z, fld, cmd, boite_plt1d, dimplot, boxx
21                  boxx = ' ['+boxx+']'
22                  vargrid = vargrid1
23                  IF debug_w THEN print, '   yfx: domdef and vargrid : ',  boite_plt1d[0:3], vargrid
24                  domdef, boite_plt1d[0:3]
25                  print, '   Averaging (time serie plot) cmd.var '+cmd.var+' in'+boxx
26                  IF debug_w THEN print, '    fld size', size(fld) 
27                  fld = checkfield(fld, 'plt1d', type = datyp.hotyp, boite = boite_plt1d)
28                  IF cmd.trend GT 0 THEN BEGIN
29                     fld_flag = 1
30                     fld = trends(fld, cmd.trend, datyp.hotyp)
31                     add_txt = trd_txt
32                  ENDIF
33               ENDIF
34              ; space and time plots fld2
35               IF debug_w THEN print, '   cmd1_back = ', cmd1_back
36               IF debug_w THEN print, '   cmd2_back = ', cmd2_back
37               IF debug_w THEN print, '   grid1_full = ', grid1_full
38               IF debug_w THEN print, '   grid2_full = ', grid2_full
39               IF sw_diffg EQ 1 THEN BEGIN
40                  jptb = jpt
41                  IF debug_w THEN print,  '  calling def_grid, cmd2_back in plt_map/yfx '
42                  cmd2_back.grid = grid2_full
43                  def_grid, cmd2_back
44                  IF read_grid_from_file EQ 1 THEN BEGIN
45                     mesh_from_file, cmd2_back.grid, file_name2, ncdf_db2, cmd2_back.var
46                     key_shift_map = key_shift
47                  ENDIF
48                  jpt = jptb
49               ENDIF
50               IF strpos(cmd2.plt, 'xy_') NE -1 THEN BEGIN
51                  mask_z, fld2, cmd2_back, boite_plt2, dimplot, boxy
52                  boxy = ' ['+boxy+']'
53                  print, '   Averaging (space) '+cmd2_back.var+' in'+boxy
54                  fld2 = checkfield(fld2, 'plt', type = 'xy', boite = boite_plt2)
55               ENDIF 
56               IF datyp2.hotyp NE '-' THEN BEGIN
57                  run_stddev = 0
58                  IF strpos(cmd2.plt, '@r') GE 1 THEN BEGIN
59                     run_stddev =  strmid(cmd2.plt, strpos(cmd2.plt, '@r')+2, strlen(cmd2.plt))
60                     cmd2.plt = strmid(cmd2.plt, 0, strpos(cmd2.plt, '@r'))
61                  ENDIF 
62                  mask_z, fld2, cmd2_back, boite_plt1d2, dimplot, boxy
63                  boxy = ' ['+boxy+']'
64                  vargrid = vargrid2
65                  IF debug_w THEN print, '    domdef and vargrid : ',  boite_plt1d2[0:3], vargrid
66                  domdef, boite_plt1d2[0:3]
67                  print, '   Averaging  (time serie plot) cmd2.var '+cmd2.var+' in'+boxy
68                  IF debug_w THEN print, '    fld2 size', size(fld2) 
69                  fld2 = checkfield(fld2, 'plt1d', type = datyp2.hotyp, direc = 'xy', boite = boite_plt1d2, /timearray)
70                  IF cmd2.trend GT 0 THEN BEGIN
71                     fld_flag = 2
72                     fld2 = trends(fld2, cmd2.trend, datyp2.hotyp)
73                     add_txt = trd_txt
74                  ENDIF
75               ENDIF
76               IF sw_diffg EQ 1 THEN BEGIN
77                  sw_diffg = 0
78                  jptb = jpt
79                  IF debug_w THEN print,  ' calling def_grid, cmd1_back in plt_map/yfx '
80                  cmd1_back.grid = grid1_full
81                  def_grid, cmd1_back
82                  IF read_grid_from_file EQ 1 THEN BEGIN
83                     mesh_from_file, cmd1_back.grid, file_name1, ncdf_db1, cmd1_back.var
84                     key_shift_map = key_shift
85                  ENDIF
86                  jpt = jptb
87               ENDIF
88
89               ; Compute linear fit coeeficients
90               fmt_linfit = '(F9.4)'
91               ;  whole serie
92               coeff = linfit(fld2, fld, CHISQ = linerr, PROB = proberr, SIGMA = sigmaerr)
93               print, '    Linfit coef (a+bx) = ', coeff(0), coeff(1), ' errbar = ',sigmaerr
94               ; text for plot info in legend_overlay
95               coeff_txt = strtrim(string(coeff(1), format = fmt_linfit), 2)
96               IF proberr NE 1.0 THEN print, '    WARNING: proba = ',proberr
97               ; divide serie in two domains (on x axis) seperated by linfit_sep (plt_def)
98               ; do only if 1m@t412 (if full serie, then separate by season)
99
100               IF linfit_sep NE -99999 AND cmd.trend EQ 412 THEN begin
101
102                  idx_low = where (fld2 LE linfit_sep)
103                  idx_up = where (fld2 GE linfit_sep)
104                  coefflu_txt = ' ['
105                 
106                  IF idx_low(0) NE -1 THEN BEGIN
107                     coeffl = linfit(fld2(idx_low), fld(idx_low), CHISQ = linerrl, PROB = proberrl, SIGMA = sigmaerrl)
108                     print, '    Linfit coef below ',strtrim(string(linfit_sep), 2),' = ', coeffl(0), coeffl(1), ' errbar = ',sigmaerrl
109                     IF proberrl NE 1.0 THEN print, '    *** WARNING: proba lower = ',proberrl
110                     coefflu_txt = coefflu_txt+strtrim(string(coeffl(1), format = fmt_linfit), 2)+'<'+strtrim(string(linfit_sep,  format = '(F4.2)'), 2)
111                  ENDIF
112                 
113                  IF idx_up(0) NE -1 THEN BEGIN
114                     coeffu = linfit(fld2(idx_up), fld(idx_up), CHISQ = linerru, PROB = proberru, SIGMA = sigmaerru)
115                     print, '    Linfit coef above ',strtrim(string(linfit_sep), 2),' = ', coeffu(0), coeffu(1), ' errbar = ',sigmaerru
116                     IF proberru NE 1.0 THEN print, '    *** WARNING: proba upper = ',proberru
117                  coefflu_txt = coefflu_txt+'>'+strtrim(string(coeffu(1), format = fmt_linfit), 2)
118                  ENDIF
119                  coefflu_txt = coefflu_txt+']'
120               ENDIF ELSE coefflu_txt = ''
121
122               ; test lag_linfit
123               cp1 = linfit(shift(fld2, 1), fld, CHISQ = linerrp1, PROB = proberrp1, SIGMA = sigmaerrp1)
124               cp2 = linfit(shift(fld2, 2), fld, CHISQ = linerrp2, PROB = proberrp2, SIGMA = sigmaerrp2)
125               cp3 = linfit(shift(fld2, 3), fld, CHISQ = linerrp3, PROB = proberrp3, SIGMA = sigmaerrp3)
126               cm1 = linfit(shift(fld2, -1), fld, CHISQ = linerrm1, PROB = proberrm1, SIGMA = sigmaerrm1)
127               cm2 = linfit(shift(fld2, -2), fld, CHISQ = linerrm2, PROB = proberrm2, SIGMA = sigmaerrm2)
128               cm3 = linfit(shift(fld2, -3), fld, CHISQ = linerrm3, PROB = proberrm3, SIGMA = sigmaerrm3)
129               print, '   '
130               print, '    -3 Linfit coef (a+bx) = ', cm3(0), cm3(1), ' errbar = ',sigmaerrm3
131               print, '    -2 Linfit coef (a+bx) = ', cm2(0), cm2(1), ' errbar = ',sigmaerrm2
132               print, '    -1 Linfit coef (a+bx) = ', cm1(0), cm1(1), ' errbar = ',sigmaerrm1
133               print, '    +1 Linfit coef (a+bx) = ', cp1(0), cp1(1), ' errbar = ',sigmaerrp1
134               print, '    +2 Linfit coef (a+bx) = ', cp2(0), cp2(1), ' errbar = ',sigmaerrp2
135               print, '    +3 Linfit coef (a+bx) = ', cp3(0), cp3(1), ' errbar = ',sigmaerrp3
136               
137            ; plot domain
138               boxyfx = def_box(cmd.plt, dimplot, legz, time_stride)
139            ; define line color and type
140               overc = overlay_type(iover, dimplot)
141               vardate = date_txt
142               varname = varlegend
143               varunit = '    '+cmd.var+boxx+' =f('+cmd.var2+boxy+')   '+add_txt
144               pltcmdstd = 'pltsc,fld,fld2,minc,maxc,minc2,maxc2,varlegend2, boite=boxyfx'+overc+com_strplt
145
146               IF hotyp EQ 't' THEN BEGIN ; time scatter plot
147                  IF mean_sc_only EQ 0 OR mean_sc_only EQ 4 THEN BEGIN
148                    ; number of time colors
149                     IF strpos(symbol_families, 'x') NE -1 THEN BEGIN
150                        coding = str_sep(symbol_families, 'x')
151                        ncolors = long(coding(0))
152                        ntimes = long(coding(1))
153                     ENDIF ELSE BEGIN
154                        ncolors = long(symbol_families)
155                        ntimes = 1
156                     ENDELSE
157                     IF ncolors GE 2 THEN BEGIN ; time color coding
158                        ic = 0
159                        jpto = jpt
160                        jpt = jpt/ncolors
161                        lincoef = fltarr(ncolors)
162                        linerro = fltarr(ncolors)
163                        linprob = fltarr(ncolors)
164                        linerr0 = fltarr(ncolors)
165                        coeffm_txt = ' ['
166                        WHILE ic LE ncolors-1 DO BEGIN
167                           idx0 = (floor(findgen(jpto/(ncolors*ntimes)))*ncolors*ntimes)+ic*(ntimes)
168                           idx = idx0
169                           jl = 1
170                           WHILE jl LE ntimes-1 DO BEGIN
171                              idx = [idx, idx0+jl]
172                              jl = jl+1
173                           ENDWHILE
174                           fldp = fld(idx)
175                           fldp2 = fld2(idx)
176;                           coeff = linfit(fldp2(where (fldp2(*) GT 0.)), fldp(where (fldp2(*) GT 0.)), CHISQ = errlin, PROB = prblin)
177                           coeff = linfit(fldp2, fldp, CHISQ = errlin, PROB = prblin, SIGMA = sigmaerr)
178                           linerro(ic) = sigmaerr(1)
179                           linprob(ic) = prblin
180                           lincoef(ic) = coeff(1)
181                           linerr0(ic) = sigmaerr(0)
182                           print, '    Period '+strtrim(string(ic+1), 2)+' Linfit coef =', coeff(0),coeff(1), ' errbar = ',sigmaerr
183                           coeffm_txt =  coeffm_txt+strtrim(string(coeff(1), format = fmt_linfit), 2)+'/'
184                           IF mean_sc_only EQ 0 THEN BEGIN
185                              pltcmd = 'pltsc,fldp,fldp2,minc,maxc,minc2,maxc2,varlegend2, boite=boxyfx'+com_strplt+',ov1d='+string(ic)+',COLOR='+string(symbol_color(ic))+', STY1D='+string(symbol_style(ic)-1)+', SYMSIZE='+string(symbol_size)
186                              printf, nulhis, strcompress(pltcmd)
187                              IF debug_w THEN print, '   ',pltcmd
188                              res = execute(pltcmd)
189                           ENDIF
190                           IF mean_sc_only EQ 4 AND ic EQ ncolors-1 THEN BEGIN
191                              print, '    Linfit slope + error (July-Dec)=', mean(lincoef(5:10)), mean(linerro(5:10))
192                              print, '    Linfit slope + error (Jan-June)=', mean([lincoef(0:4), lincoef(11)]), mean([linerro(0:4), linerro(11)])
193                              vardate = 'toto'
194                              jpt = ncolors
195                              time = lindgen(12)*30*1+ julday(1,1,01, ndayspm = calendar_type)
196                              hotyp = 't'
197                        ;*****  edit here for field specific *****
198                             ; minmax = ',-5,20'
199                             ; mult_coeff = 1000.
200                             ; varname = 'Coupling strength ['+cmd.date1+'-'+cmd.spec+']'
201                              minmax = ',-50,10'
202                              mult_coeff = 1.
203                              varname = 'Alpha: Qtot=f(SST) ['+cmd.date1+'-'+cmd.spec+']'
204                        ;****************************************
205                              print, '    Mult, min, max set in plt_map ',mult_coeff, minmax
206                              pltcmd = 'pltt,lincoef*'+string(mult_coeff)+', '''+hotyp+''''+minmax+com_strplt+',ov1d=0,COLOR=1, thick=4, STY1D=0'
207
208                              printf, nulhis, strcompress(pltcmd)
209                              IF debug_w THEN print, '   ', pltcmd
210                              res = execute(pltcmd)     
211                              pltcmd = 'pltt,(lincoef-linerro)*'+string(mult_coeff)+', '''+hotyp+''''+minmax+com_strplt+',ov1d=1,COLOR=1, thick=1, STY1D=0'
212                              printf, nulhis, strcompress(pltcmd)
213                              IF debug_w THEN print, '   ',pltcmd
214                              res = execute(pltcmd)
215                              pltcmd = 'pltt,(lincoef+linerro)*'+string(mult_coeff)+', '''+hotyp+''''+minmax+com_strplt+',ov1d=1,COLOR=1, thick=1, STY1D=0'
216                              printf, nulhis, strcompress(pltcmd)
217                              IF debug_w THEN print, '   ',pltcmd
218                              res = execute(pltcmd)
219                              pltcmd = 'pltt,linerr0, '''+hotyp+''''+minmax+com_strplt+',ov1d=1,COLOR=2, thick=1, STY1D=0'
220                              printf, nulhis, strcompress(pltcmd)
221                              IF debug_w THEN print, '   ',pltcmd
222                              res = execute(pltcmd)
223                           ENDIF
224                           ic = ic + 1
225                        ENDWHILE
226                        coeffm_txt = coeffm_txt+']'
227                     ENDIF ELSE BEGIN ; one color
228                        IF debug_w THEN print, '   ',pltcmdstd
229                        res = execute(pltcmdstd(0))
230                     ENDELSE
231                  ENDIF     
232               ENDIF ELSE BEGIN ; standard scatter plot
233                  IF debug_w THEN print, '   ',pltcmdstd
234                  res = execute(pltcmdstd(0))
235               ENDELSE
236               IF cmd.trend EQ 412 THEN coeffm_txt = ''
237               ; Add slope value
238               @legend_overlay
239
240               ; add mean SC in 4x3 plots
241               
242               IF symbol_families EQ '4x3' THEN BEGIN
243
244                  IF cmd.trend EQ '412' THEN BEGIN
245                     fldrem_t1 = fldrem_t1-mean(fldrem_t1)
246                     fldrem_t2 = fldrem_t2-mean(fldrem_t2)
247                  ENDIF ELSE BEGIN
248                     running = 12L
249                     lenght = (size(fld))[1]
250                     fldrem_t1 =  fltarr(running)
251                     fldrem_t2 =  fltarr(running)
252                     FOR t1 = 0, running-1 DO BEGIN
253                        fldrem_t1(t1) = mean(fld(long(findgen(lenght/running)*running+t1)))
254                        fldrem_t2(t1) = mean(fld2(long(findgen(lenght/running)*running+t1)))
255                     ENDFOR
256                  ENDELSE
257
258                  print, '    Seasonal cycle var/stddev fld1 ', (moment(fldrem_t1))[1], sqrt((moment(fldrem_t1))[1])
259                  print, '    Seasonal cycle var/stddev fld2 ', (moment(fldrem_t2))[1], sqrt((moment(fldrem_t2))[1])
260
261                  fldrem_t1 = [fldrem_t1, fldrem_t1(0)]
262                  fldrem_t2 = [fldrem_t2, fldrem_t2(0)]
263                  sw_ov1d = mean_sc_only
264                  IF mean_sc_only EQ 2 AND cmd.trend EQ '412' THEN BEGIN
265                     ; SC of std dev
266                     stat = spectra(fld, jpt/12, 20, 15, 0)
267                     stat2 = spectra(fld2, jpt/12, 20, 15, 0)
268                     print, '     Stddev of monthly stddevs fld', sqrt((moment(stat.sc_std-(moment(stat.sc_std))[0]))[1])
269                     print, '     Stddev of monthly stddevs fld2', sqrt((moment(stat2.sc_std-(moment(stat2.sc_std))[0]))[1])
270                     stdsc = [stat.sc_std, stat.sc_std(0)]
271                     stdsc2 = [stat2.sc_std, stat2.sc_std(0)]
272                     pltcmd = 'pltsc,stdsc,stdsc2,0. ,maxc,0.,maxc2,varlegend2, boite=boxyfx'+com_strplt+',ov1d=1-min(1,sw_ov1d), STY1D=-1, THICKN=3, SYMSIZE='+string(symbol_size)+', FRACTION=fraction'
273                     printf, nulhis, strcompress(pltcmd)
274                     IF debug_w THEN print, pltcmd
275                     res = execute(pltcmd(0))
276                     pltcmd = 'xyouts,stdsc2-(maxc2)/(.3*win(0)*win(1)),stdsc,string(long(findgen(12))+1),charsize=1.3,alignment=0.5'
277                     printf, nulhis, strcompress(pltcmd)
278                     IF debug_w THEN print, pltcmd
279                     res = execute(pltcmd(0))
280                  ENDIF ELSE BEGIN
281                     ov1d_val = 0
282                     IF mean_sc_only EQ 0 THEN ov1d_val = 1
283                     pltcmd = 'pltsc,fldrem_t1,fldrem_t2,minc,maxc,minc2,maxc2,varlegend2, boite=boxyfx'+com_strplt+',ov1d=ov1d_val, STY1D=-1, THICKN=5, SYMSIZE='+string(symbol_size)+', FRACTION=fraction'
284                     printf, nulhis, strcompress(pltcmd)
285                     IF debug_w THEN print, pltcmd
286                     res = execute(pltcmd(0))
287                     IF mean_sc_only EQ 1 THEN BEGIN
288                                ; add month info win(0)*win(1)
289                        pltcmd = 'xyouts,fldrem_t2-(maxc2-minc2)/(0.5*win(0)*win(1)),fldrem_t1,string(long(findgen(12))+1),charsize=1.3,alignment=0.5'
290                        printf, nulhis, strcompress(pltcmd)
291                        IF debug_w THEN print, pltcmd
292                        res = execute(pltcmd(0))
293                     ENDIF
294                  ENDELSE
295               ENDIF   
296
297               ; overplot sigma contours in T-S plane
298               IF (cmd.var EQ 'sosstsst' and cmd.var2 EQ 'sosaline') OR (cmd.var EQ 'votemper' and cmd.var2 EQ 'vosaline') THEN BEGIN
299                  IF noerase EQ 0 THEN BEGIN
300                     min_t = minc-2.0
301                     max_t = maxc+2.0
302                     min_s = minc2-2.0
303                     max_s = maxc2+2.0
304                     delta_t = 0.5
305                     delta_s = 0.05
306                     t_vec = findgen((max_t-min_t)/delta_t+1)*delta_t+min_t
307                     s_vec = findgen((max_s-min_s)/delta_s+1)*delta_s+min_s
308                     t_ = t     ; since t is already defined
309                     t = t_vec
310                     FOR i = 1, (max_s-min_s)/delta_s DO t = [[t], [t_vec]]
311                     s = s_vec
312                     FOR i = 1, (max_t-min_t)/delta_t DO s = [[s], [s_vec]]
313                     s = transpose(s)
314                     sr=sqrt(abs(s))
315                     r1=((((6.536332E-9*t-1.120083E-6)*t+1.001685E-4)*t $
316                          -9.095290E-3)*t+6.793952E-2)*t+999.842594
317                     r2=(((5.3875E-9*t-8.2467E-7)*t+7.6438E-5)*t-4.0899E-3)*t+8.24493E-1
318                     r3=(-1.6546E-6*t+1.0227E-4)*t-5.72466E-3
319                     rhopn = ( ( 4.8314E-4*s + r3*sr +r2)*s +r1) -1000.0
320                     min_sig = round(min(rhopn)+0.5)-1.
321                     max_sig = round(max(rhopn)-0.5)+1.
322                     delta_sig = 1. ; define contour interval here!
323                     levels = findgen((max_sig-min_sig)/delta_sig+1)*delta_sig+min_sig
324                     labels = levels
325                     labels(*) = 1
326                     contour, rhopn, s, t, /overplot, levels = levels, c_labels = labels, c_linestyle = 0
327                     t = t_
328                  ENDIF
329               ENDIF 
330
331               printf, nulhis, 'boite_yfx=',boxyfx
332               printf, nulhis, strcompress(pltcmd)
333
334               tmask = t
335               ; force read grid for next window
336               cmd_prev.grid = 'toto'
337               
Note: See TracBrowser for help on using the repository browser.