Commit f0bd5658a4ec55c97204c35c4dd9b098d28170ee

Authored by Jean-Philippe Bernard
1 parent 0b17c65d
Exists in master

first commit

Showing 1 changed file with 150 additions and 0 deletions   Show diff stats
src/idl_misc/JPBLib_for_Dustemwrap/plot_negative_log.pro 0 → 100644
... ... @@ -0,0 +1,150 @@
  1 +PRO plot_negative_log,x,y,help=help,ppositions=ppositions,dy=dy,positive_only=positive_only,negative_only=negative_only,_extra=_extra
  2 +
  3 +;+
  4 +; NAME:
  5 +; plot_negative_log
  6 +; CALLING SEQUENCE:
  7 +; plot_negative_log,x,y,_extra=_extra
  8 +; PURPOSE:
  9 +; plots an array in log scale including negative values in two half-plots
  10 +; INPUTS:
  11 +; x = x vector to plot
  12 +; y = y vector to plot
  13 +; OPTIONAL INPUT:
  14 +; ppositions = a 4-element vector for global plot position in the window
  15 +; dy = fractional distance between the two half-plots along y
  16 +; ACCEPTED KEY-WORDS:
  17 +; _extra is filtered and passed to cgplot
  18 +; EXAMPLES
  19 +;x=[0,1,2,3,4,7,12] & y=[1.e-2,2,-1,-2,-5,-10,-50.]
  20 +;plot_negative_log,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
  21 +;x=lindgen(1000)/500. & y=sin(x*10)*exp(-x*2.)*1.e2
  22 +;plot_negative_log,x,y,xtitle='x',ytitle='y',xrange=[-0.1,2.],/xsty,yrange=[0.001,100],/ysty
  23 +;
  24 +; OUTPUTS:
  25 +; None
  26 +; OPTIONAL OUTPUTS:
  27 +; None
  28 +; PROCEDURE AND SUBROUTINE USED
  29 +;
  30 +; COMMONS:
  31 +;
  32 +; SIDE EFFECTS:
  33 +; The two half plots are forced to have the same (reflected) y axis.
  34 +; MODIFICATION HISTORY:
  35 +; written 28-06-22 by Jean-Philippe Bernard
  36 +;-
  37 +
  38 +IF keyword_set(help) THEN BEGIN
  39 + doc_library,'plot_negative_log'
  40 + goto,sortie
  41 +ENDIF
  42 +
  43 +defsysv,'!previous_yrange',exist=exist
  44 +IF not exist THEN defsysv,'!previous_yrange',ptr_new()
  45 +
  46 +indpos=where(y GT 0,countpos)
  47 +indneg=where(y LT 0,countneg)
  48 +maskpos=y*0
  49 +maskneg=y*0
  50 +maskpos[indpos]=1
  51 +maskneg[indneg]=1
  52 +
  53 +df_pos=find_ind(maskpos,1,count=count_pos_regions)
  54 +df_neg=find_ind(maskneg,1,count=count_neg_regions)
  55 +
  56 +;print,df_pos
  57 +;print,'-----'
  58 +;print,df_neg
  59 +
  60 +Nx=1 & Ny=2
  61 +IF not keyword_set(ppositions) THEN BEGIN
  62 + x0=0.10 & y0=0.10
  63 + x1=0.90 & y1=0.90
  64 +ENDIF ELSE BEGIN
  65 + x0=ppositions[0] & y0=ppositions[1]
  66 + x1=ppositions[2] & y1=ppositions[3]
  67 +ENDELSE
  68 +dx=0.15 ;not used anywy for this plot
  69 +use_dy=0.05
  70 +IF keyword_set(dy) THEN BEGIN
  71 + use_dy=dy
  72 +ENDIF
  73 +
  74 +pp=make_ppositions(x0,y0,x1,y1,dx,use_dy,Nx,Ny,xtit_plot=xtit_plot,ytit_plot=ytit_plot, $
  75 + noerase=noerase,xcharsize=xcharsize,ycharsize=ycharsize,/silent)
  76 +
  77 +i=0L
  78 +IF countpos NE 0 THEN BEGIN
  79 + IF not keyword_set(negative_only) THEN BEGIN
  80 + ;cgplot,x[indpos],y[indpos],_extra=_extra,/ylog
  81 + !p.position=pp[*,i]
  82 + cgplot,x[indpos],y[indpos],noerase=noerase[i],xcharsize=xcharsize[i],ycharsize=ycharsize[i],xtit=xtit,ytit=ytit,_extra=_extra,/ylog,/nodata
  83 + FOR k=0L,count_pos_regions-1 DO BEGIN
  84 + cgoplot,x[df_pos[k,0]:df_pos[k,1]],y[df_pos[k,0]:df_pos[k,1]],_extra=_extra
  85 + ENDFOR
  86 + ENDIF
  87 + i=i+1
  88 +ENDIF
  89 +
  90 +; IF keyword_set(_extra) THEN BEGIN
  91 +; yyrange=get_extra(_extra=_extra,'YRANGE',count=count)
  92 +; IF count NE 0 THEN BEGIN
  93 +; yrange=yyrange
  94 +; ENDIF ELSE BEGIN
  95 +; yrange=!y.crange
  96 +; ENDELSE
  97 +; ENDIF ELSE BEGIN
  98 +; yrange=!y.crange
  99 +; ENDELSE
  100 +
  101 +yrange=!y.crange
  102 +
  103 +!previous_yrange=ptr_new(yrange)
  104 +
  105 +new_yrange=10^[(*!previous_yrange)[1],(*!previous_yrange)[0]]
  106 +
  107 +IF keyword_set(_extra) THEN BEGIN
  108 + _extrabis=modify_extra(_extra=_extra,'YRANGE',new_yrange,/replace)
  109 +ENDIF
  110 +
  111 +; IF keyword_set(_extra) THEN BEGIN
  112 +; yrange=get_extra(_extra=_extra,'YRANGE',count=count)
  113 +; ; stop
  114 +; IF count NE 0 THEN BEGIN
  115 +; new_yrange=yrange
  116 +; new_yrange[1]=yrange[0]
  117 +; new_yrange[0]=yrange[1]
  118 +; ;stop
  119 +; _extrabis=modify_extra(_extra=_extra,'YRANGE',new_yrange,/replace)
  120 +; ENDIF ELSE BEGIN
  121 +; yrange=!y.crange
  122 +; new_yrange=[(!x.crange)[1],(!x.crange)[0]]
  123 +; _extrabis=modify_extra(_extra=_extra,'YRANGE',new_yrange,/replace)
  124 +; ENDELSE
  125 +; ENDIF ELSE BEGIN
  126 +; yrange=!y.crange
  127 +; new_yrange=[(!x.crange)[1],(!x.crange)[0]]
  128 +; _extrabis=modify_extra(_extra=_extra,'YRANGE',new_yrange,/replace)
  129 +; ENDELSE
  130 +
  131 +;stop
  132 +
  133 +IF countneg NE 0 THEN BEGIN
  134 + IF not keyword_set(positive_only) THEN BEGIN
  135 + !p.position=pp[*,i]
  136 + ; cgplot,x[indneg],-1.*y[indneg],noerase=noerase[i],xcharsize=xcharsize[i],ycharsize=ycharsize[i],xtit=xtit,ytit=ytit,_extra=_extrabis,/ylog
  137 + cgplot,x[indneg],-1.*y[indneg],noerase=noerase[i],xcharsize=xcharsize[i],ycharsize=ycharsize[i],xtit=xtit,ytit=ytit,_extra=_extrabis,/ylog,/nodata,yrange=new_yrange
  138 + FOR k=0L,count_neg_regions-1 DO BEGIN
  139 + cgoplot,x[df_neg[k,0]:df_neg[k,1]],-1.*y[df_neg[k,0]:df_neg[k,1]],_extra=_extra
  140 + ENDFOR
  141 + ENDIF
  142 +ENDIF
  143 +
  144 +sortie:
  145 +
  146 +;stop
  147 +
  148 +END
  149 +
  150 +
... ...