dustem_plot_mlog.pro 6.22 KB
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:
;     dustem_plot_mlog
;
; 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 JPB
;    Evolution details on the DustEMWrap gitlab.
;    See http://dustemwrap.irap.omp.eu/ for FAQ and help.  
;-

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,noerase=1,xcharsize=xcharsize[0],ycharsize=ycharsize[0],/ylog,/xlog,/nodata,color=color,ytickformat='dstmwrp_exp',_extra=_extra   	 
          endif else cgplot,x,y,pos=pos,xs=1,noerase=1,xcharsize=xcharsize[0],ycharsize=ycharsize[0],/ylog,/xlog,/nodata,color=color,ytickformat='dstmwrp_exp',_extra=_extra	 
    	 
	 endif else begin
        	 
    		 cgplot,x[indpos],y[indpos],pos=pos,xs=1,ys=1,noerase=1,xcharsize=xcharsize[0],ycharsize=ycharsize[0],/xlog,/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=alog10(_extra.yr);!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,/xlog,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,/xlog,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,ys=1,/xlog,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