FUNCTION HUNT,array,value,position ;Numerical Recipes in C n = N_ELEMENTS(array) ascnd = (array(n - 1) GE array(0)) if ((position LE -1) OR (position GT (n-1))) then begin position = -1 ; input guess not usefull i_hi = n ; go to bisektor endif else begin inc = 1 if ((value GE array(position)) EQ ascnd) then begin ;hunt up if (position EQ n-1) then return,position i_hi = position + 1 while ((value GE array(i_hi)) EQ ascnd) do begin position = i_hi inc = inc + 1 i_hi = position + inc if (i_hi GT (n-1)) then begin i_hi = n goto, BISECTOR ; goto bisector endif endwhile endif else begin ;hunt down if (position EQ 0) then begin position = -1 return,position endif i_hi = position - 1 while ((value LT array(position)) EQ ascnd) do begin i_hi = position inc = 2*inc if (inc GE i_hi) then begin position = -1 goto, BISECTOR endif else position = i_hi - inc endwhile endelse endelse BISECTOR: while ((i_hi - position) NE 1) do begin i_m = (i_hi + position) / 2 if ((value GE array(i_m)) EQ ascnd) then position = i_m else i_hi = i_m endwhile if (value EQ array(0)) then position = 0 if (value EQ array(n-1)) then $ position = n-2 return,position END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! FUNCTION GET_TAB,fileTAB,B0,l,b ;F_EXISTS,fileTAB,'GET_TAB' if ((b GT 90) OR (b LT -90) OR (l GT 90) OR (l LT -90)) then begin MESSAGE,'Bad values of l or b !',/noprefix,/informational,/continue MESSAGE,'(l,b)= -90 .. 90',/noprefix endif pi = 3.1415926d l = pi / 180 * l & b = pi / 180 * b & B0 = pi / 180 * B0 sin_theta = SQRT(1 - ((COS(b) * COS(B0) * COS(l)) + (SIN(b)*SIN(B0)))^2) sint = [0,0.6,0.8,0.9,0.95,0.98,0.99] OPENR,unit,fileTAB,/get_lun info = DBLARR(3) READF,unit,info coef = DBLARR(7) READF,unit,coef int = FLTARR(8,info(2)) READF,unit,int FREE_LUN,unit b = TOTAL(ALOG(coef)*ALOG(1-sint))/TOTAL((ALOG(1-sint))^2) fce = coef/(1-sint)^b ; zavislost sint na coef = (1-sint)^b * fce(sint) ; interpoluje se jen fce(sint) ld_coef = INTERPOL(fce,sint,sin_theta)*(1-sin_theta)^b index = WHERE(sin_theta LT sint,count) if ( count NE 0) then begin column = index(0) tab = [int(0,*),int(column:column+1,*)] data = {line : info(0),ld_coef : ld_coef, coef_tab : [coef(column - 1),coef(column)], tab : tab} endif else begin column = N_ELEMENTS(sint) PRINT,'get_data: Position of event is too close to the limb! Atlas intensity will not be precise!' tab = [int(0,*),int(column,*)] data = {line : info(0),ld_coef : ld_coef,tab : tab} endelse return, data END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! FUNCTION T_INT,koef,range COMMON universal,tab,coef,cont N = N_ELEMENTS(range) if (N NE 0) then N = N - 1 l = ABS(koef(0) + koef(1) * range - tab.line) TInt = DBLARR(N+1) dim = SIZE(tab.tab) pos_lambda = 0 for i = 0, (N) do begin dist = l(i) pos_lambda = HUNT(tab.tab(0,*),dist,pos_lambda) if ((pos_lambda EQ -1) OR (pos_lambda EQ (dim(2) - 1))) then begin MESSAGE,'Value of lambda is not tabulated!',/noprefix endif ; interpolation using bilinear method (Numerical Recipes in C) t = (dist - tab.tab(0,pos_lambda)) / (tab.tab(0,pos_lambda + 1) - tab.tab(0,pos_lambda)) if (dim(1) EQ 3) then begin u = (tab.ld_coef - tab.coef_tab(0)) / (tab.coef_tab(1) - $ tab.coef_tab(0)) TInt(i) = tab.ld_coef * ((1 - t) * (1 - u) * tab.tab(1,pos_lambda) + t * (1 - u) * $ tab.tab(1,pos_lambda + 1) + t * u * tab.tab(2,pos_lambda + 1) + $ u * (1 - t) * tab.tab(2,pos_lambda)) endif else $ TInt(i) = tab.ld_coef * ((1 - t) * tab.tab(1,pos_lambda) + t * tab.tab(1,pos_lambda + 1)) endfor return,Tint END ;------------------------------------------------------ PRO CALCUL,myprof1,pocet_klinu,a,chi2 COMMON universal,tab,coef,cont ;COMMON SHARE,X,Y,pr,Isl,In COMMON share,X,Y,pr,Int_t,Int_s,Int_q contin=cont nenuly=where(contin ne 0) contin=contin(nenuly) Int_t=dblarr(n_elements(contin)) ;teoreticke intenzity v zadanych bodech Int_s=dblarr(n_elements(contin),pocet_klinu) ;signal v zadanych bodech pro kliny Int_q=dblarr(n_elements(contin)) ;signal v zadanych bodech pro klidne slunce for i=0,n_elements(contin)-1 do begin ;teoreticke hodnoty intenzity v zadanych bodech Int_t(i)=T_INT(coef,contin(i)) ;teoreticke hodnoty v zadanych bodech (1 az 3 hodnoty) ;down=MIN(myprof1(cont(i)-2:cont(i)+2,0),max=up) ;index = where ((myprof1(*,0) GE down) AND (myprof1(*,0) LE up)) ;Int=T_INT(coef,index) ;Int_t(i)=TOTAL(Int)/n_elements(index) ;signal Int_s(i,0:pocet_klinu-1)=myprof1(contin(i),0:pocet_klinu-1) Int_q(i)=myprof1(contin(i),pocet_klinu) ;Int_s(i,0:pocet_klinu-1)=TOTAL(myprof1(index,0:pocet_klinu-1),1)/double(n_elements(index)) ;Int_q(i)=TOTAL(myprof1(index,pocet_klinu))/double(n_elements(index)) endfor X=dblarr(n_elements(contin)*pocet_klinu) & Y=dblarr(n_elements(contin)*pocet_klinu) X=reform(transpose(Int_s),n_elements(contin)*pocet_klinu) for i=0,n_elements(contin)-1 do Y(i*pocet_klinu:(i+1)*pocet_klinu-1)=Int_t(i)*pr a=svdfit(X,Y,2,chisq=chi2,/double) ;fitujem primku ;Y=a(0)+a(1)*X END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! PRO GFUNCT,x,a,f f=a(0)+x*a(1) END ;pro konst_event,event ;COMMON konst,nastavchyba,KONST,novakonst,fklid ;COMMON HELP,pom,f,chyba ;COMMON universal,tab,coef,cont ;widget_control,event.id,get_uvalue=uvalue ;case uvalue of ;'SLIDER':begin ; widget_control,event.id,get_value=val ; novakonst=KONST+val/100.0 ; wset,nastavchyba ; PLOT,coef(0)+coef(1)*pom,T_INT(coef,pom),title='quite sun' ; OPLOT,coef(0)+coef(1)*pom,fklid*novakonst,color=100 ; end ;endcase ;end ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ;PRO CLB_CURV,myprof,a,S2,reg_bounds,A_K,Id_klin = Id_klin,Start_point = Start_point,$ ; Draw = Draw PRO CLB_CURV,myprof,a,Id_klin=Id_klin COMMON konst,nastavchyba,KONST,novakonst,fklid COMMON scal,cekat,base3 COMMON clb,A_K1,myprofd,index1,pocet_klinu1,b1,a1,S21,nula3,fmin,iter,jedna3 COMMON universal,tab,coef,cont COMMON cesta,nazevsouboru COMMON udaje11,t11,t12,hranice1,hranice2,button1 COMMON obecny,cara,button114 ;no_par = N_PARAMS() ;COMMON SHARE,X,Y,pr,Isl,In COMMON HELP,pom,f,chyba COMMON share,X,Y,pr,Int_t,Int_s,Int_q COMMON obrazek,image COMMON hlavicka,header case cara of ;!!!!!!!!!!!!!!!dodelat dalsi 1:begin pr=[0.8511d,0.5754d,0.4074d,0.2818d,0.1950d,0.1318d,0.09120d,0.06166d] end 2:begin pr=[0.8318d,0.5420d,0.4017d,0.2924d,0.2070d,0.1432d,0.0986d,0.0661d] end 3:begin pr=[0.8736d,0.6143d,0.4140d,0.2695d,0.1810d,0.1185d,0.0826d,0.0565d] ;ziskane interpolaci end 4:begin pr=[0.8213d,0.5238d,0.3986d,0.2982d,0.2135d,0.1494d,0.1026d,0.0685d] end 5:begin pr=[0.8217d,0.5245d,0.3987d,0.2980d,0.2133d,0.1492d,0.1025d,0.0684d] end endcase pocet_klinu = TOTAL(Id_klin) pr = pr(where(pr * Id_klin)) CALCUL,myprof,pocet_klinu,a,chi2 ;zde se spocitaji kalibracni koeficienty a ;-----------------zobrazeni kalibracni krivky------------------ nula3=widget_base(base3,/row) & jedna3=widget_base(nula3,/column) mez31=widget_base(jedna3,ysize=50) jedna32=widget_label(jedna3,value='Calibration curve') jedna33=widget_draw(jedna3,xsize=400,ysize=400) mez32=widget_base(jedna3,ysize=10) widget_control,jedna33,get_value=nastav33 & wset,nastav33 PLOT,X,Y,psym=2,xtitle = 'Instrumental intensity',ytitle='I/Icont [%]' ;zobrazeni kalibracni krivky OPLOT,X,a(0)+X*a(1) ;----------------zobrazeni teoretickeho a naseho zkalibrovaneho profilu-------------------- chyba3=widget_base(/column) chybadraw=widget_draw(chyba3,xsize=400,ysize=300) ;if (fmin/N_ELEMENTS(pom) GT 4) then chyba31=widget_label(chyba3,value='High value of CHI2!') ;chyba32=widget_base(chyba3,/row) widget_control,chyba3,/realize widget_control,chybadraw,get_value=nastavchyba wset,nastavchyba pom = DINDGEN(N_ELEMENTS(myprof(*,0))) ;GFUNCT,myprof(*,0),a,f ;prvni klin ;PLOT,coef(0)+coef(1)*pom,pr(0)*T_INT(coef,pom),title='1st wedge' ;OPLOT,coef(0)+coef(1)*pom,f,color=100 ;psym=3 GFUNCT,myprof(*,pocet_klinu),a,fklid ;klidne slunce KONST=Int_t/(a(0)+a(1)*Int_q) KONST=total(KONST)/n_elements(KONST) ;KONST=max(KONST) PLOT,coef(0)+coef(1)*pom,T_INT(coef,pom),title='quiet sun' OPLOT,coef(0)+coef(1)*pom,fklid*KONST,color=150 ;novakonst=KONST ;chybasl=widget_slider(chyba3,title='konst',value=0,minimum=-20,maximum=20,uvalue='SLIDER',/suppress_value) ;xmanager,'konst',chyba3 coefup=fltarr(2) ;vypis vysledku hran1=float(hranice1(0)) coefup(0)=coef(0)-coef(1)*hran1 coefup(1)=coef(1) mezera=widget_base(nula3,xsize=150) dva3=widget_base(nula3,/column) mez35=widget_base(dva3,ysize=80) reslab=widget_label(dva3,value='RESULTS',/align_left) mez33=widget_base(dva3,ysize=40) dvapom1=widget_base(dva3,/column,/frame) chlab=widget_label(dvapom1,value='CHI2: '+strcompress(string(chi2),/remove_all),/align_left) ; iterlab=widget_label(dvapom1,value='Number of iterations: '+string(iter),/align_left) mez34=widget_base(dva3,ysize=40) dvapom2=widget_base(dva3,/column,/frame) alab=widget_label(dvapom2,value='a0 '+strcompress(string(a(0)),/remove_all),/align_left) blab=widget_label(dvapom2,value='a1 '+strcompress(string(a(1)),/remove_all),/align_left) clab=widget_label(dvapom2,value='konst '+strcompress(string(KONST),/remove_all),/align_left) mez36=widget_base(dva3,ysize=40) dvapom3=widget_base(dva3,/column,/frame) co1lab=widget_label(dvapom3,value='c1 '+strcompress(string(coefup(0)),/remove_all),/align_left) co2lab=widget_label(dvapom3,value='c2 '+strcompress(string(coefup(1)),/remove_all),/align_left) pomzpet=widget_base(jedna3,/column) zpet3=widget_button(pomzpet,value='PREVIOUS',uvalue='DRUHA',xsize=150) velikost=size(image) GFUNCT,image,a,novyobrazek novyobrazek=novyobrazek*KONST lastocc=rstrpos(nazevsouboru,'\') ;vytvoreni cesty pro ulozeni if lastocc eq -1 then lastocc=rstrpos(nazevsouboru,'/') kolik=strlen(nazevsouboru)-lastocc-5 cesta=strmid(nazevsouboru,lastocc+1,kolik)+'_c.fts' ;cesta=strmid(nazevsouboru,0,strlen(nazevsouboru)-4)+'_c.fts' str1=strcompress(velikost(1),/remove_all) ;vytvoreni hlavicky str2=strcompress(velikost(2),/remove_all) header=make_array(9,/string) header(0)='SIMPLE = T / Written by IDL: ' +!STIME header(1)='BITPIX = -64 / ' header(2)='NAXIS = 2 / ' header(3)='NAXIS1 = '+str1+' / ' header(4)='NAXIS2 = '+str2+' / ' header(5)='LAMBDA=C0+C1*X ' header(6)='C0='+string(coefup(0)) header(7)='C1='+string(coefup(1)) ;header(8)='K='+string(K) header(8)='END ' writefits,cesta,novyobrazek,header ;ulozeni zkalibrovaneho obrazku mez37=widget_base(dva3,ysize=20) ulozlab=widget_label(dva3,value='Calibrated image has been saved as '+cesta) END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! PRO info11_event,event ;oblast profilu COMMON inner,myprofiles,profil,prof11,prof12,prof13,prof14,prof15,$ base1,prof16,base2,poloha2,ymyprof,zavedeno,jas,klin,jasnost COMMON udaje11,t11,t12,hranice1,hranice2,button1 COMMON obrazek,image COMMON pronovy,imageklin widget_control,event.id,get_uvalue=uvalue case uvalue of 'ZAVRI':BEGIN widget_control,t11,get_value=hranice11 widget_control,t12,get_value=hranice22 s=size(image) ;kontrola spravnosti (zda je oblast v obrazku) test=1 if (fix(hranice11(0)) lt 0) or (fix(hranice11(0)) gt s(1)) then test=0 if (fix(hranice22(0)) lt 0) or (fix(hranice22(0)) gt s(1)) then test=0 if fix(hranice11(0)) ge fix(hranice22(0)) then test=0 if test eq 1 then begin ;pokud spravne zadany rozsah widget_control,button1,sensitive=1 widget_control,event.top,/destroy if ((hranice11(0) ne hranice1(0)) or (hranice22(0) ne hranice2(0))) and (zavedeno eq 1) then begin if total(myprofiles) ne 0 then begin ;prekreslovani vytvorenych profilu myprofilespom=make_array(fix(hranice22(0))-fix(hranice11(0))+1,6,value=0.0) for i=0,5 do begin if total(myprofiles(*,i)) ne 0 then begin if (i eq 5) then aktobr=image else aktobr=imageklin oblast1=aktobr(fix(hranice11(0)):fix(hranice22(0)),ymyprof(i)-2:ymyprof(i)+2) ;image; ips=make_array(fix(hranice22(0))-fix(hranice11(0))+1,value=0) for j=0,4 do ips=ips+float(oblast1(*,j)) & ips=ips/5 myprofilespom(*,i)=round(ips) endif endfor myprofiles=myprofilespom for i=0,5 do begin case i of 0:widget_control,prof11,get_value=nastav1 1:widget_control,prof12,get_value=nastav1 2:widget_control,prof13,get_value=nastav1 3:widget_control,prof14,get_value=nastav1 4:widget_control,prof15,get_value=nastav1 5:widget_control,prof16,get_value=nastav1 endcase wset,nastav1 plot,myprofiles(*,i),pos=[0,0,1,1],xstyle=4,ystyle=4 endfor endif endif hranice1=hranice11(0) & hranice2=hranice22(0) endif END endcase END PRO info12_event,event ;coordinates COMMON udaje12,t13,t14,longt,lat,t15,center widget_control,event.id,get_uvalue=uvalue case uvalue of 'ZAVRI':BEGIN widget_control,t13,get_value=longt widget_control,t14,get_value=lat widget_control,t15,get_value=center widget_control,event.top,/destroy END endcase END ;-------------------calib_event--------------------------- PRO fotocalib_event, event COMMON universal,tab,coef,cont COMMON udaje12,t13,t14,longt,lat,t15,center COMMON udaje23,iksm11,iksm12,iksm21,iksm22,reg11,reg12,reg21,reg22 ;COMMON udaje22,kont1,kont2,kontinuum1,kontinuum2 COMMON udaje21,voda2,alfa2,posvoda,posalfa COMMON udaje11,t11,t12,hranice1,hranice2,button1 COMMON udaje13,t16,grey COMMON vse,base,poloha,zac,im,zac2,w2,g1,zac3,jedna,dva,tri,basepoc,f1 COMMON inner,myprofiles,profil,prof11,prof12,prof13,prof14,prof15,$ base1,prof16,base2,poloha2,ymyprof,zavedeno,jas,klin,jasnost COMMON obrazek,image COMMON scal,cekat,base3 COMMON cesta,nazevsouboru COMMON foto,base111,oznobr COMMON knoflik,button11,button12,button13,button14,button15,button17,button18,button19 COMMON obecny,cara,button114 COMMON novy1,krbut ;COMMON novy2,krivka COMMON hlavicka,header COMMON udajenovy21,cara1,cara2,delka1,delka2 COMMON pronovy,imageklin ;COMMON disperze,data,dr12,osax,dispcoef0,dispcoef1,osaxnova COMMON disperze,data,dr12,dispcoef0,dispcoef1,dispcoef0_n,dispcoef1_n,intens,intens_n COMMON disperze2,coef0_lab,coef1_lab COMMON calibration,kont1,kont2,kont3 WIDGET_CONTROL, event.id, GET_UVALUE=uvalue CASE uvalue OF 'QUIT':BEGIN widget_control,base,/destroy END 'START1':BEGIN widget_control,event.id,get_value=pom if dva eq 1 then begin widget_control,kont1,get_value=Val & cont(0)=fix(Val(0)) widget_control,kont2,get_value=Val & cont(1)=fix(Val(0)) widget_control,kont3,get_value=Val & cont(2)=fix(Val(0)) widget_control,base2,/destroy ;z druhe obrazovky endif if tri eq 1 then widget_control,base3,/destroy ;z treti obrazovky if jedna eq 1 then widget_control,base1,/destroy ;z prvni obrazovky if pom(0) eq 'ENTER' then widget_control,basepoc,/destroy ;zacatek if (pom(0) eq 'LOAD') or (pom(0) eq 'ENTER') then begin ;zacatek widget_control,f1,sensitive=1 zac=0 & hranice1='' & hranice2='' & zac2=0 & zac3=0 posvoda='' & posalfa='' & kontinuum1='' & kontinuum2='' reg11='' & reg12='' & reg21='' & reg22='' & longt='' & lat='' zac=0 & jedna=0 & dva=0 & tri=0 & zavedeno=0 & postreti='' jasnost=0 & center='' ;& grey='' delka1='' & delka2='' klin=make_array(8,value=0) cara=1 ;& krivka=1 dispcoef0=0.0 & dispcoef1=0.0 cont=[0,0,0] profil=1 nazevsouboru=pickfile(title='Select file with wedges') pripona=strmid(nazevsouboru,strlen(nazevsouboru)-3,3) if pripona eq 'fts' then image=readfits(nazevsouboru,header) if pripona eq 'tif' then image=read_tiff(nazevsouboru,/unsigned) endif rozmer=size(image) base1=widget_base(base,/column) base11=widget_base(base1,/row) base111=widget_base(base11,/column) oznobr=widget_label(base111,value='Wedges') im=widget_draw(base111,xsize=rozmer(1),ysize=rozmer(2),x_scroll_size=500,y_scroll_size=500,$ /motion_events,/button_events,uvalue='OBR') base112=widget_base(base11,/column) mez1=widget_base(base112,ysize=20) lab1=widget_label(base112,value='range',/align_left) button112=widget_button(base112,value='range for profiles',uvalue='INFO11',xsize=110) mez2=widget_base(base112,ysize=20) lab2=widget_label(base112,value='number of profile',/align_left) ;base12 button1=widget_button(base112,value='1',/menu,xsize=110,/align_left) button11=widget_button(button1,value='1',uvalue='1jedna') button12=widget_button(button1,value='2',uvalue='2jedna') button13=widget_button(button1,value='3',uvalue='3jedna') button14=widget_button(button1,value='4',uvalue='4jedna') button15=widget_button(button1,value='5',uvalue='5jedna') button16=widget_button(button1,value='quiet sun',uvalue='6jedna') mez3=widget_base(base112,ysize=20) lab3=widget_label(base112,value='coordinates',/align_left) button113=widget_button(base112,value='coordinates of region',uvalue='INFO12',xsize=110) ; mez8=widget_base(base112,ysize=20) ; lab8=widget_label(base112,value='grey filter',/align_left) ; button118=widget_button(base112,value='grey filter',uvalue='INFO13',xsize=110) mez4=widget_base(base112,ysize=20) lab4=widget_label(base112,value='spectral line',/align_left) button114=widget_button(base112,value='Halpha',/menu,/align_left,xsize=110) button1141=widget_button(button114,value='Halpha',uvalue='HALFA') button1142=widget_button(button114,value='Hbeta',uvalue='HBETA') button1143=widget_button(button114,value='CaII',uvalue='CAII') button1144=widget_button(button114,value='CaK',uvalue='CAK') button1145=widget_button(button114,value='CaH',uvalue='CAH') ;******************* widget_control,button1143,sensitive=0 widget_control,button1144,sensitive=0 widget_control,button1145,sensitive=0 mez5=widget_base(base112,ysize=100) pollab=widget_label(base112,value='position',/align_left) poloha=widget_label(base112,value='position',/frame,xsize=110,/align_left) mez6=widget_base(base112,ysize=20) jaslab=widget_label(base112,value='brightness',/align_left) jas=widget_slider(base112,uvalue='BRI',value=jasnost,min=0,max=50) case cara of 1:widget_control,button114,set_value='Halpha' 2:widget_control,button114,set_value='Hbeta' 3:widget_control,button114,set_value='CaII' 4:widget_control,button114,set_value='CaK' 5:widget_control,button114,set_value='CaH' ;************************* endcase mez7=widget_base(base11,xsize=50) base113=widget_base(base11,/column) mez7=widget_base(base113,ysize=20) ozn11=widget_label(base113,value='Profile from 1st wedge step') & prof11=widget_draw(base113,xsize=200,ysize=62) ozn12=widget_label(base113,value='Profile from 2nd wedge step') & prof12=widget_draw(base113,xsize=200,ysize=62) ozn13=widget_label(base113,value='Profile from 3rd wedge step') & prof13=widget_draw(base113,xsize=200,ysize=62) ozn14=widget_label(base113,value='Profile from 4th wedge step') & prof14=widget_draw(base113,xsize=200,ysize=62) ozn15=widget_label(base113,value='Profile from 5th wedge step') & prof15=widget_draw(base113,xsize=200,ysize=62) ozn16=widget_label(base113,value='Profile of quiet sun') & prof16=widget_draw(base113,xsize=200,ysize=62) base12=widget_base(base1,/row) dalsi1=widget_button(base12,xsize=100,value='NEXT',uvalue='DRUHA') if zac eq 0 then widget_control,button1,sensitive=0 ;number of profile widget_control,im,get_value=okno & wset,okno tv,bytscl(image)+jasnost if zac2 eq 1 then begin ;pokud navrat tak vykreslit profily for i=0,5 do begin case i of 0:widget_control,prof11,get_value=nastav1 1:widget_control,prof12,get_value=nastav1 2:widget_control,prof13,get_value=nastav1 3:widget_control,prof14,get_value=nastav1 4:widget_control,prof15,get_value=nastav1 5:widget_control,prof16,get_value=nastav1 endcase wset,nastav1 plot,myprofiles(*,i),pos=[0,0,1,1],xstyle=4,ystyle=4 endfor widget_control,button1,set_value='quiet sun' ; widget_control,button11,sensitive=0 ; widget_control,button12,sensitive=0 ; widget_control,button13,sensitive=0 ; widget_control,button14,sensitive=0 ; widget_control,button15,sensitive=0 endif jedna=1 & dva=0 & tri=0 & zac=1 END ;--------------------range,coordinates,dispersion,kontinuum,fitting--------- 'INFO11':BEGIN ;range infobase11=widget_base(/column) b11=widget_base(infobase11,/row) & b12=widget_base(infobase11,/row) t11=cw_field(b11,title='1st x position') t12=cw_field(b12,title='2nd x position') okbut11=widget_button(infobase11,value='OK',uvalue='ZAVRI') widget_control,t11,set_value=hranice1 & widget_control,t12,set_value=hranice2 widget_control,infobase11,/realize xmanager,'info11',infobase11 END 'INFO12':BEGIN ;coordinates infobase12=widget_base(/column) ;xsize=600 b13=widget_base(infobase12,/row) & b14=widget_base(infobase12,/row) & b15=widget_base(infobase12,/row) t13=cw_field(b13,title='heliographic longtitude') t14=cw_field(b14,title='heliographic latitude') t15=cw_field(b15,title='latitude of the center of the disk') okbut12=widget_button(infobase12,value='OK',uvalue='ZAVRI') widget_control,t13,set_value=longt & widget_control,t14,set_value=lat widget_control,t15,set_value=center widget_control,infobase12,/realize xmanager,'info12',infobase12 END 'SL1':begin widget_control,event.id,get_value=val widget_control,dr12,get_value=nastav2 & wset,nastav2 ; indexy=where(klin) plot,smooth(myprofiles(*,5),2) dispcoef0_n=dispcoef0-val/10.0 ;dispcoef0_n= oplot,(data(0,*)-dispcoef0_n)*dispcoef1_n,data(1,*)*intens+intens_n,color=150 widget_control,coef0_lab,set_value=strcompress(string(dispcoef0_n),/remove_all) widget_control,coef1_lab,set_value=strcompress(string(1.0/dispcoef1_n),/remove_all) end 'SL2':begin widget_control,event.id,get_value=val widget_control,dr12,get_value=nastav2 & wset,nastav2 plot,smooth(myprofiles(*,5),2) index=where(data(1,*) eq min(data(1,*))) osax=(data(0,*)-dispcoef0_n)*dispcoef1_n x0=osax(index(0)) dispcoef1_n=dispcoef1+val/10.0 osax=(data(0,*)-dispcoef0_n)*dispcoef1_n x1=osax(index(0)) dispcoef0_n=dispcoef0_n+(x1-x0)/dispcoef1_n dispcoef0=dispcoef0+(x1-x0)/dispcoef1_n oplot,(data(0,*)-dispcoef0_n)*dispcoef1_n,data(1,*)*intens+intens_n,color=150 widget_control,coef0_lab,set_value=strcompress(string(dispcoef0_n),/remove_all) widget_control,coef1_lab,set_value=strcompress(string(1.0/dispcoef1_n),/remove_all) end 'SL3':begin widget_control,event.id,get_value=val widget_control,dr12,get_value=nastav2 & wset,nastav2 ; indexy=where(klin) plot,smooth(myprofiles(*,5),2) intens_n=val oplot,(data(0,*)-dispcoef0_n)*dispcoef1_n,data(1,*)*intens+intens_n,color=150 ;*max(myprofiles(*,indexy(0)))/100.0,color=100 end ;---------------------------------image------------------------------------ 'OBR': BEGIN ;position of cursor widget_control,poloha,set_value=strcompress('('+string(event.x)+','+ $ string(event.y)+')',/remove_all) ;plotting a profile if (event.press eq 1) and (zac eq 1) and (profil le 6) then begin hr1=fix(hranice1(0)) & hr2=fix(hranice2(0)) ;range if (hr1 ne 0) and (hr2 ne 0) then begin ;pokud zadany range if total(klin) eq 0 then begin myprofiles=make_array(hr2-hr1+1,6,value=0.0) zavedeno=1 ;zavedeno myprofiles ymyprof=make_array(6,value=0) ;y hodnoty profilu endif oblast=image(hr1:hr2,event.y-2:event.y+2) ;oblast pro profil ips=make_array(hr2-hr1+1,value=0) for i=0,4 do ips=ips+float(oblast(*,i)) ips=ips/5 ;prumer profilu myprofiles(*,profil-1)=round(ips) ymyprof(profil-1)=event.y if profil ne 6 then klin(profil-1)=1 ;pokud profil klinu case profil of ;nakresleni profilu 1:widget_control,prof11,get_value=nastav1 2:widget_control,prof12,get_value=nastav1 3:widget_control,prof13,get_value=nastav1 4:widget_control,prof14,get_value=nastav1 5:widget_control,prof15,get_value=nastav1 6:widget_control,prof16,get_value=nastav1 endcase wset,nastav1 plot,ips,pos=[0,0,1,1],xstyle=4,ystyle=4 endif endif END ;---------------------------2nd screen (position)----------------- 'OBR2':BEGIN coord=convert_coord(event.x,event.y,/device,/to_data) ;data coord. iks=round(coord(0)) & ips=round(coord(1)) widget_control,poloha2,set_value=STRCOMPRESS('('+string(iks)+','+string(ips)+')',/rem) END ;--------------------------nahrani druhe obrazovky------------------- 'DRUHA':BEGIN test=1 ;kontrola zda spravne hodnoty coordinates, zda aspon dva klinove ;profily, zda profil klidneho slunce, zda profily poporade if jedna eq 1 then begin ;pokud z prvni obrazovky if zavedeno eq 1 then begin ;je-li zavedeno pole myprofiles if (total(klin) le 2) or (total(myprofiles(*,5)) eq 0) then test=0 ;mene nez 2 kliny nebo neni klidny slunce if (fix(longt(0)) gt 90) or (fix(longt(0)) lt -90) or (fix(lat(0)) gt 90) or (fix(longt(0)) lt -90) then test=0 if (center(0) eq '') or (longt(0) eq '') or (lat(0) eq '') then test=0 ;zadne hodnoty endif else test=0 endif if test eq 1 then begin ;pokud v poradku, nahraj druhou obrazovku if jedna eq 1 then widget_control,base1,/destroy ;z prvni obrazovky if tri eq 1 then widget_control,base3,/destroy ;z druhy obrazovky if (dva eq 0) then begin ;nacteni atlasu pro stanoveni disperzni krivky case cara of 1:nazev='ha' 2:nazev='hb' 3:nazev='caii' 4:nazev='cak' 5:nazev='cah' endcase openr,unit,'atlas_'+nazev+'.dat',/get_lun i=0 & wave=0.0 & intensity=0.0 & data=fltarr(2,2000) while not eof(unit) do begin readf,unit,wave,intensity data(0,i)=wave data(1,i)=intensity i=i+1 endwhile free_lun,unit data=data(*,0:i-1) ;----------------------------------------------- zac2=1 base2=widget_base(base,/column) dr12=widget_draw(base2,xsize=935,ysize=400,/motion_events,uvalue='OBR2') base21=widget_base(base2,/row) base211=widget_base(base21,/column,/frame) displab=widget_label(base211,value='DISPERSION',/align_left) base211_1=widget_base(base211,/row) base211_1_1=widget_base(base211_1,/column) sl1=widget_slider(base211_1_1,title='position',value=0,minimum=-300,maximum=300,uvalue='SL1') sl2=widget_slider(base211_1_1,title='extension',value=0,minimum=-300,maximum=300,uvalue='SL2') sl3=widget_slider(base211_1_1,title='intensity',value=0,minimum=-1000,maximum=1000,uvalue='SL3') mezera1=widget_base(base211_1,xsize=20) base211_1_2=widget_base(base211_1,/column) coeflab0=widget_label(base211_1_2,value='coef0',/align_left,xsize=80) coef0_lab=widget_label(base211_1_2,value='coef0',/align_left,xsize=80) coeflab1=widget_label(base211_1_2,value='coef1',/align_left,xsize=80) coef1_lab=widget_label(base211_1_2,value='coef1',/align_left,xsize=80) mezera2=widget_base(base21,xsize=20) base212=widget_base(base21,/column,/frame) kontlab=widget_label(base212,value='POSITIONS FOR CALIBRATION',/align_left) kont1=cw_field(base212,title='1st x position') kont2=cw_field(base212,title='2nd x position') kont3=cw_field(base212,title='3rd x position') posbase=widget_base(base212,/row) poloha2lab=widget_label(posbase,value='position',/align_left,xsize=50) poloha2=widget_label(posbase,value='position',xsize=80,/align_left) mezera3=widget_base(base2,ysize=30) base22=widget_base(base2,/row) prev2=widget_button(base22,value='PREVIOUS',uvalue='START1') next2=widget_button(base22,value='CALIBRATE',uvalue='TRETI') widget_control,dr12,get_value=nastav2 & wset,nastav2 plot,myprofiles(*,5) ;profil klidneho slunce if dispcoef0 eq 0.0 then begin ;prisli jsme z prvni obrazovky, disp. koef. jeste nebyly spocitany dispcoef0=data(0,0) osax=data(0,*)-dispcoef0 dispcoef1=n_elements(myprofiles(*,5))/osax(n_elements(osax)-1) intens=max(myprofiles(*,5))/100.0 oplot,osax*dispcoef1,data(1,*)*intens,color=150 dispcoef0_n=dispcoef0 dispcoef1_n=dispcoef1 intens_n=0.0 endif else begin oplot,(data(0,*)-dispcoef0_n)*dispcoef1_n,data(1,*)*intens+intens_n,color=150 endelse widget_control,coef0_lab,set_value=strcompress(string(dispcoef0_n),/remove_all) widget_control,coef1_lab,set_value=strcompress(string(1.0/dispcoef1_n),/remove_all) widget_control,sl1,set_value=round((dispcoef0-dispcoef0_n)*10.0) widget_control,sl2,set_value=round((dispcoef1_n-dispcoef1)*10.0) widget_control,sl3,set_value=intens_n if cont(0) ne 0 then widget_control,kont1,set_value=strcompress(string(cont(0)),/remove_all) if cont(1) ne 0 then widget_control,kont2,set_value=strcompress(string(cont(1)),/remove_all) if cont(2) ne 0 then widget_control,kont3,set_value=strcompress(string(cont(2)),/remove_all) endif tri=0 & jedna=0 & dva=1 endif else begin ;ohlaseni chyb chyba1=widget_base(/column) mez11=widget_base(chyba1,ysize=10) chyba11=widget_label(chyba1,value='Missing some information') chyba12=widget_label(chyba1,value='or data incorrect!') mez12=widget_base(chyba1,ysize=10) widget_control,chyba1,/realize wait,2 widget_control,chyba1,/destroy endelse END ;-------------------------------nahrani treti obrazovky--------------------- 'TRETI':BEGIN cont=intarr(3) widget_control,kont1,get_value=Val & cont(0)=fix(Val(0)) widget_control,kont2,get_value=Val & cont(1)=fix(Val(0)) widget_control,kont3,get_value=Val & cont(2)=fix(Val(0)) test=1 if fix(cont(0)) eq 0 then test=0 ;pokud neni zadane prvni kontinuum s=size(myprofiles) if (fix(cont(0)) lt 0) or (fix(cont(0)) gt s(1)) then test=0 ;pokud kontinuua lezou jsou mimo rozsah if (fix(cont(1)) lt 0) or (fix(cont(1)) gt s(1)) then test=0 if (fix(cont(2)) lt 0) or (fix(cont(2)) gt s(1)) then test=0 if test eq 1 then begin zac3=1 & tri=1 & dva=0 & jedna=0 widget_control,base2,/destroy base3=widget_base(base,/column) coef=dblarr(2) ;& coef(0)=result(0) & coef(1)=result(1) coef(0)=dispcoef0_n & coef(1)=1.0/dispcoef1_n case cara of 1:begin ;disp1(0)=6560.555 & disp1(1)=6562.808 tabulka='halpha.tab' end 2:begin ;disp1(0)=4859.747 & disp1(1)=4862.598 tabulka='hbeta.tab' end 3:begin ;disp1(0)=8540.817 & disp1(1)=8542.144 tabulka='caii.tab' end 4:begin tabulka='cak.tab' end 5:begin tabulka='cah.tab' ;******************** end endcase ;vstupni pole pro clb_curv myprofiles1=make_array(s(1),total(klin)+1) myprofiles1(*,0:total(klin)-1)=myprofiles(*,where(klin)) ;kliny myprofiles1(*,total(klin))=myprofiles(*,5) ;klidne slunce tab=get_tab(tabulka,float(center(0)),fix(longt(0)),fix(lat(0))) clb_curv,myprofiles1,a,Id_klin=klin endif else begin ;ohlaseni chyb chyba2=widget_base(/column) mez21=widget_base(chyba2,ysize=10) chyba21=widget_label(chyba2,value='Missing some information') chyba22=widget_label(chyba2,value='or data incorrect!') mez22=widget_base(chyba2,ysize=10) widget_control,chyba2,/realize wait,2 widget_control,chyba2,/destroy endelse END ;-----------------------brightness-------------------- 'BRI':begin widget_control,jas,get_value=jasnost widget_control,im,get_value=nastavjas wset,nastavjas & tv,bytscl(image)+jasnost end ;-----------------------spectral line------------------ 'HALFA':begin widget_control,button114,set_value='Halpha' cara=1 end 'HBETA':begin widget_control,button114,set_value='Hbeta' cara=2 end 'CAII':begin widget_control,button114,set_value='CaII' cara=3 end 'CAK':begin widget_control,button114,set_value='CaK' cara=4 end 'CAH':begin widget_control,button114,set_value='CaH' cara=5 end ;*************************** ;----------------------store number of profile to variable profil------ ELSE:begin widget_control,event.id,get_value=pom widget_control,widget_info(event.id,/parent),set_value=pom(0) cisloprofilu=fix(strmid(uvalue,0,1)) profil=cisloprofilu end ENDCASE END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ;--------------------------calib--------------------------------- PRO calib_large_dispersion COMMON udaje12,t13,t14,longt,lat,t15,center COMMON udaje23,iksm11,iksm12,iksm21,iksm22,reg11,reg12,reg21,reg22 COMMON udaje22,kont1,kont2,kontinuum1,kontinuum2 COMMON udaje21,voda2,alfa2,posvoda,posalfa COMMON vse,base,poloha,zac,im,zac2,w2,g1,zac3,jedna,dva,tri,basepoc,f1 COMMON udaje11,t11,t12,hranice1,hranice2 zac=0 & hranice1='' & hranice2='' & zac2=0 & zac3=0 posvoda='' & posalfa='' & kontinuum1='' & kontinuum2='' reg11='' & reg12='' & reg21='' & reg22='' & longt='' & lat='' jedna=0 & dva=0 & tri=0 & center='' base=widget_base(title='CALIB',xsize=940,ysize=650,/row,mbar=bar) fmenu=widget_button(bar,value='FILE',/menu) f1=widget_button(fmenu,value='LOAD',uvalue='START1') f2=widget_button(fmenu,value='QUIT',uvalue='QUIT') basepoc=widget_base(base,xsize=970,ysize=650) vstup=widget_button(basepoc,value='ENTER',uvalue='START1',xsize=970,ysize=650) WIDGET_CONTROL,base,/REALIZE widget_control,f1,sensitive=0 XMANAGER,'fotocalib',base END