dustem_plot_mlog.pro
6.02 KB
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
PRO dustem_plot_mlog,x,y,help=help,ppositions=ppositions,dy=dy,positive_only=positive_only,negative_only=negative_only,rms=rms,overplot=overplot,color=color,nodata=nodata,_extra=_extra;,overplot=overplot,nodata=nodata
;+
; NAME:
; plot_negative_log
; CALLING SEQUENCE:
; plot_negative_log,x,y,_extra=_extra
; PURPOSE:
; plots an array in log scale including negative values in two half-plots
; INPUTS:
; x = x vector to plot
; y = y vector to plot
; OPTIONAL INPUT:
; ppositions = a 4-element vector for global plot position in the window
; dy = fractional distance between the two half-plots along y
; ACCEPTED KEY-WORDS:
; _extra is filtered and passed to cgplot
; EXAMPLES
;x=[0,1,2,3,4,7,12] & y=[1.e-2,2,-1,-2,-5,-10,-50.]
;dustem_plot_mlog,x,y,xtitle='x',ytitle='y',xrange=[-1,15],/xsty,yrange=[0.001,100],/ysty,ppositions=[0.3,0.2,0.8,0.9],dy=0.001
;x=lindgen(1000)/500. & y=sin(x*10)*exp(-x*2.)*1.e2
;dustem_plot_mlog,x,y,xtitle='x',ytitle='y',xrange=[-0.1,2.],/xsty,yrange=[0.001,100],/ysty
;
; OUTPUTS:
; None
; OPTIONAL OUTPUTS:
; None
; PROCEDURE AND SUBROUTINE USED
;
; COMMONS:
;
; SIDE EFFECTS:
; The two half plots are forced to have the same (reflected) y axis.
; MODIFICATION HISTORY:
; written 28-06-22 by Jean-Philippe Bernard
;-
IF keyword_set(help) THEN BEGIN
doc_library,'dustem_plot_mlog'
goto,sortie
ENDIF
defsysv,'!previous_yrange',exist=exist
IF not exist THEN defsysv,'!previous_yrange',ptr_new()
indpos=where(y GT 0,countpos)
indneg=where(y LT 0,countneg)
maskpos=y*0
maskneg=y*0
maskpos[indpos]=1
maskneg[indneg]=1
if countpos ne 0 then df_pos=find_ind(maskpos,1,count=count_pos_regions)
if countneg ne 0 then df_neg=find_ind(maskneg,1,count=count_neg_regions)
Nx=1 & Ny=2
IF not keyword_set(ppositions) THEN BEGIN
x0=0.10 & y0=0.10
x1=0.90 & y1=0.90
ENDIF ELSE BEGIN
x0=ppositions[0] & y0=ppositions[1]
x1=ppositions[2] & y1=ppositions[3]
ENDELSE
dx=0.;15 ;not used anywy for this plot
use_dy=0.005;.05
IF keyword_set(dy) THEN BEGIN
use_dy=dy
ENDIF
pp=make_ppositions(x0,y0,x1,y1,dx,use_dy,Nx,Ny,xtit_plot=xtit_plot,ytit_plot=ytit_plot, $
noerase=noerase,xcharsize=xcharsize,ycharsize=ycharsize);,/silent)
;noerase=[1,1]
;i=0L
;NB: IF CGWINDOW's use and dustemwrap_plot are to be deprecated/modified and/or replaced by another routine/widget,
;the following line (if condition) needs to be uncommented for the positive block and the negative one.
;IF countpos NE 0 THEN BEGIN
IF not keyword_set(negative_only) THEN BEGIN
pos=pp[*,0]
;if keyword_set(color) then _extrabis.color=color
if keyword_set(overplot) then begin
IF countpos NE 0 THEN BEGIN
FOR k=0L,count_pos_regions-1 DO BEGIN
if keyword_set(rms) then begin ;Should this be combined with the overplot command?
cgerrplot,x[df_pos[k,0]:df_pos[k,1]],y[df_pos[k,0]:df_pos[k,1]]-rms[df_pos[k,0]:df_pos[k,1]],y[df_pos[k,0]:df_pos[k,1]]+rms[df_pos[k,0]:df_pos[k,1]],color=color;,_extra=_extra
endif else cgoplot,x[df_pos[k,0]:df_pos[k,1]],y[df_pos[k,0]:df_pos[k,1]],noerase=1,color=color,_extra=_extra
ENDFOR
ENDIF
endif else begin
if keyword_set(nodata) then begin ; maybe add xr=xr? No, modify the plotting procedure first.
if countpos ne 0 then begin
cgplot,x[indpos],y[indpos],pos=pos,xs=1,yr=yr,noerase=1,xcharsize=xcharsize[0],ycharsize=ycharsize[0],/ylog,/nodata,color=color,ytickformat='dstmwrp_exp',_extra=_extra
endif else cgplot,x,y,pos=pos,xs=1,yr=yr,noerase=1,xcharsize=xcharsize[0],ycharsize=ycharsize[0],/ylog,/nodata,color=color,ytickformat='dstmwrp_exp',_extra=_extra
endif else begin
cgplot,x[indpos],y[indpos],pos=pos,xs=1,yr=yr,noerase=1,xcharsize=xcharsize[0],ycharsize=ycharsize[0],/ylog,color=color,ytickformat='dstmwrp_exp',_extra=_extra
endelse
endelse
ENDIF
;endif
;IF countneg NE 0 THEN BEGIN
IF not keyword_set(positive_only) THEN BEGIN
pos=pp[*,1]
;stop
yrange=!y.crange
!previous_yrange=ptr_new(yrange)
new_yrange=10^[(*!previous_yrange)[1],(*!previous_yrange)[0]]
IF keyword_set(_extra) THEN BEGIN
_extrabis=modify_extra('YR',new_yrange,/replace,_extra=_extra) ; add exchange option
ENDIF
if keyword_set(overplot) then begin
IF countneg NE 0 THEN BEGIN
FOR k=0L,count_neg_regions-1 DO BEGIN
if keyword_set(rms) then begin ;Should this be combined with the overplot command?
cgerrplot,x[df_neg[k,0]:df_neg[k,1]],-1*y[df_neg[k,0]:df_neg[k,1]]-rms[df_neg[k,0]:df_neg[k,1]],-1*y[df_neg[k,0]:df_neg[k,1]]+rms[df_neg[k,0]:df_neg[k,1]],color=color;,ytickformat='(A)'
;color by default otherwise it's _extra supercedes. Let's see how this reacts to the plotting of U
endif else cgoplot,x[df_neg[k,0]:df_neg[k,1]],-1.*y[df_neg[k,0]:df_neg[k,1]],noerase=1,color=color,_extra=_extra
ENDFOR
ENDIF
endif else begin
!dustem_mlog=1
if keyword_set(nodata) then begin
if countneg ne 0 then begin
cgplot,x[indneg],-1.*y[indneg],pos=pos,xs=1,noerase=1,xcharsize=xcharsize[1],ycharsize=ycharsize[1],/ylog,color=color,/nodata,yrange=new_yrange,ytickformat='dstmwrp_exp',_extra=_extrabis
endif else cgplot,x,-1.*y,pos=pos,xs=1,noerase=1,xcharsize=xcharsize[1],ycharsize=ycharsize[1],/ylog,color=color,/nodata,yrange=new_yrange,ytickformat='dstmwrp_exp',_extra=_extrabis
endif else begin
cgplot,x[indneg],-1.*y[indneg],pos=pos,xs=1,noerase=1,xcharsize=xcharsize[1],ycharsize=ycharsize[1],/ylog,color=color,yrange=new_yrange,ytickformat='dstmwrp_exp',_extra=_extrabis
endelse
!dustem_mlog=0
endelse
ENDIF
;ENDIF
sortie:
;stop
END