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 GFUNCT,x,a,f,pder da=(x)^a(1) f=da*a(0)+a(2) IF N_PARAMS() GE 4 THEN $ pder= [[da],[a(0)*da*alog(x)],[replicate(1.0, N_ELEMENTS(X))]] END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! FUNCTION BROYFUNC,x COMMON SHARE,XX,YY,pr,Isl,In COMMON SUM,sumxy,sumx2,sumx,sumy,sumxylx,sumx2lx,sumxlx,a,c N = n_elements(XX) sumxy = 0d & sumx2 = 0d & sumx = 0d & sumy = 0d & sumxylx = 0d & sumx2lx = 0d & sumxlx = 0d for i=0,N-1 do begin sumxy = sumxy + YY(i)*XX(i)^x(0) sumx2 = sumx2 + XX(i)^(2*x(0)) sumx = sumx + XX(i)^x(0) sumy = sumy + YY(i) sumxylx = sumxylx + YY(i)*XX(i)^x(0)*alog(XX(i)) sumx2lx = sumx2lx + XX(i)^(2*x(0))*alog(XX(i)) sumxlx = sumxlx + XX(i)^x(0)*alog(XX(i)) endfor mat = dblarr(2,2) mat(0,0) = sumx2 mat(1,0) = sumx mat(1,1) = N mat(0,1) = mat(1,0) column = [sumxy,sumy] res = CRAMER(mat,column,/double) a = res(0) & c = res(1) RETURN,[-sumxylx + a * sumx2lx + c * sumxlx] END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! FUNCTION PARAMS,b COMMON SHARE,XX,YY,pr,Isl,In COMMON SUM RETURN,[a,b(0),c] END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! PRO KORELMAT,a,H COMMON SHARE,XX,YY,pr,Isl,In dim = n_elements(a) N = n_elements(XX) sumx2 = 0d & sumx = 0d & sumxylx = 0d & sumx2lx = 0d & sumxlx = 0d sumxylx2 = 0d & sumx2lx2 = 0d & sumxlx2 = 0d sumy = 0d & sumxy = 0d for i=0,N-1 do begin sumx2 = sumx2 + XX(i)^(2*a(1)) sumx = sumx + XX(i)^a(1) sumxy = sumxy + YY(i)*XX(i)^a(1) sumy = sumy + YY(i) sumxylx = sumxylx + YY(i)*XX(i)^a(1)*alog(XX(i)) sumx2lx = sumx2lx + XX(i)^(2*a(1))*alog(XX(i)) sumxlx = sumxlx + XX(i)^a(1)*alog(XX(i)) sumxylx2 = sumxylx2 + YY(i)*XX(i)^a(1)*(alog(XX(i)))^2 sumx2lx2 = sumx2lx2 + (XX(i)^a(1)*alog(XX(i)))^2 sumxlx2 = sumxlx2 + XX(i)^a(1)*(alog(XX(i)))^2 endfor H=fltarr(dim,dim) H(0,0) = - sumx2 H(1,0) = sumxylx - 2 * a(0) * sumx2lx - a(2) * sumxlx H(2,0) = - sumx H(1,1) = a(0) * (sumxylx2 - 2 * a(0) * sumx2lx2 - a(2) * sumxlx2) H(1,2) = - a(0) * sumxlx H(2,2) = - N H(0,1) = H(1,0) H(0,2) = H(2,0) H(2,1) = H(1,2) END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! FUNCTION POWFUNC, koef COMMON universal,tab,coef,cont COMMON SHARE COMMON HELP,pom,f,chyba TInt = T_INT(koef,pom) result = TOTAL(((f - pr(0)*TInt)/chyba)^2) koef = coef RETURN, result END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! FUNCTION MYSIGMAY,x,a,s pder = [[x^a(1)],[a(0)*alog(x)*x^a(1)],[replicate(1.0,n_elements(x))]] mat = pder # s # transpose(pder) result = fltarr(n_elements(x)) for i=0,n_elements(x)-1 do result(i) = sqrt(mat(i,i)) RETURN,result END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! PRO CALCUL,myprof1,index,pocet_klinu,b,a,S2 COMMON universal,tab,coef,cont COMMON SHARE,X,Y,pr,Isl,In Nindex = N_ELEMENTS(index) Int = T_INT(coef,index) ;!!!!!!!!!!!!!!!!!!!!!!! Isl = TOTAL(Int)/Nindex In = TOTAL(myprof1(index,*),1)/DOUBLE(Nindex) ;prum. hod. kont. pro kl. sl. a kliny m = DBLARR(pocet_klinu) for j=0,pocet_klinu - 1 do m(j) = MIN(myprof1(*,j)) I_HA = TOTAL(T_INT(coef,(tab.line-coef(0))/coef(1))) X = dblarr(2*pocet_klinu) & Y =dblarr(2*pocet_klinu) X(0:pocet_klinu-1) = In(0:pocet_klinu-1) & Y(0:pocet_klinu-1) = pr*Isl X(pocet_klinu:*) = m(0:pocet_klinu-1) & Y(pocet_klinu:*) = I_HA*pr res = BROYDEN(b,'BROYFUNC',/double,check=check,stepmax=5) a = PARAMS(res) if check then begin MESSAGE,'I did not find true parameters, try different starting point!',/noprefix,/informational,/continue MESSAGE,'Use keyword to set different starting point. See help or manual',/noprefix endif KORELMAT,a,H GFUNCT,X,a,f chi2 = TOTAL((Y-f)^2) sigma2 = chi2/(N_ELEMENTS(X)-1) H = H/sigma2 S2 = -INVERT(H,/double) END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! PRO CLB_CURV,myprof,a,S2,reg_bounds,A_K,Id_klin = Id_klin,Start_point = Start_point,$ Draw = Draw 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 case cara of 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] ;pr=[0.5420d,0.4017d,0.2924d,0.2070d,0.1432d,0.0986d,0.0661d,0.0442d] end 3:begin pr=[0.8736d,0.6143d,0.4140d,0.2695d,0.1810d,0.1185d,0.0826d,0.0565d] ;ziskane interpolaci end endcase if KEYWORD_SET(Start_point) then b = [DOUBLE(Start_point)] pocet_klinu = TOTAL(Id_klin) pr = pr(where(pr * Id_klin)) down = MIN(myprof(cont(0):cont(1),0),max=up) index = where ((myprof(*,0) GE down) AND (myprof(*,0) LE up)) CALCUL,myprof,index,pocet_klinu,b,a,S2 ;zde se spocitaji kalibracni koeficienty a nula3=widget_base(base3,/row) & jedna3=widget_base(nula3,/column) ; jedna31=widget_label(jedna3,value='COMPUTING...!!!',/align_left) 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=comp & wset,comp xyouts,200,200,'WAIT...',alignment=0.5,charsize=2,/device ;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)+a(2) if (N_PARAMS() EQ 5) then begin ;zde se zjisti disperzni koeficienty fitovani naseho profilu na teoreticky A_K = DBLARR(2) A_K(1) = Isl/(a(0)*In(pocet_klinu)^a(1)+a(2)) GFUNCT,myprof(*,0),a,f chyba = MYSIGMAY(myprof(*,0),a,S2) ftol = 1.0e-4 xi = TRANSPOSE([[0.01,0.0],[0.0,0.001]]) pom1 = DINDGEN(N_ELEMENTS(myprof(*,0))) no_reg = N_ELEMENTS(reg_bounds(0,*)) no_points = 0 for j = 0, no_reg - 1 do begin no_points = no_points + reg_bounds(1,j) - reg_bounds(0,j) + 1 endfor pom = DINDGEN(no_points) pos = 0 for j = 0,no_reg - 1 do begin pom(pos) = pom1(reg_bounds(0,j):reg_bounds(1,j)) pos = pos + reg_bounds(1,j)-reg_bounds(0,j) + 1 endfor f = f(pom) & chyba = chyba(pom) ;coefdrive=coef POWELL,coef,xi,ftol,fmin,'POWFUNC',ITER=ITER,/double ;minimalizacni procedura ; widget_control,jedna31,set_value='' ;zobrazeni fitovanych profilu (nas prepocteny na teoreticky a teoreticky) chyba3=widget_base(/column) ;pred upravou koeficientu 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 ;GFUNCT,myprof(*,0),a,f ;PLOT,coef(0)+coef(1)*pom1,f,psym=3 ;OPLOT,coef(0)+coef(1)*pom1,pr(0)*T_INT(coefdrive,pom1) ;wait,3 A_K(0) = coef(1) CALCUL,myprof,index,pocet_klinu,b,a,S2 ;znovu se provede kalibrace s novymi disperznimi koeficienty A_K(1) = Isl/(a(0)*In(pocet_klinu)^a(1)+a(2)) widget_control,jedna33,get_value=nastav33 wset,nastav33 PLOT,X,Y,psym=2,xtitle = 'Instrumental intensity',ytitle='I/Icont [%]' ;zobrazeni nove kalibracni krivky OPLOT,X,a(0)*X^a(1)+a(2) widget_control,chybadraw,get_value=nastavchyba ;zobrazeni nafitovanych profilu s novymi kalibr. koef. wset,nastavchyba GFUNCT,myprof(*,0),a,f ;prvni klin PLOT,coef(0)+coef(1)*pom1,f,psym=3,title='1st wedge' OPLOT,coef(0)+coef(1)*pom1,pr(0)*T_INT(coef,pom1) ; GFUNCT,myprof(*,pocet_klinu),a,fklid ;klidne slunce ; PLOT,coef(0)+coef(1)*pom1,fklid*A_K(1),psym=3 ; OPLOT,coef(0)+coef(1)*pom1,T_INT(coef,pom1) coefup=fltarr(2) ;vypis vysledku hran1=float(hranice1(0)) coefup(0)=coef(0)-coef(1)*hran1 coefup(1)=coef(1) ;widget_control,jedna31,set_value='' 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: '+string(fmin),/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='a '+string(a(0)*A_K(1)),/align_left) blab=widget_label(dvapom2,value='b '+string(a(1)),/align_left) clab=widget_label(dvapom2,value='c '+string(a(2)*A_K(1)),/align_left) mez36=widget_base(dva3,ysize=40) dvapom3=widget_base(dva3,/column,/frame) co1lab=widget_label(dvapom3,value='c1 '+string(coefup(0)),/align_left) co2lab=widget_label(dvapom3,value='c2 '+string(coefup(1)),/align_left) pomzpet=widget_base(jedna3,/column) zpet3=widget_button(pomzpet,value='PREVIOUS',uvalue='DRUHA',xsize=150) case cara of 1:pripona='ha' 2:pripona='hb' 3:pripona='ca' endcase lastocc=rstrpos(nazevsouboru,'\') if lastocc eq -1 then lastocc=rstrpos(nazevsouboru,'/') kolik=strlen(nazevsouboru)-lastocc-5 cesta=strmid(nazevsouboru,lastocc+1,kolik)+'_'+pripona+'.cfs' openw,unit,cesta,/get_lun printf,unit,'a ',a(0)*A_K(1) printf,unit,'b ',a(1) printf,unit,'c ',a(2)*A_K(1) printf,unit,'c1 ',coefup(0) printf,unit,'c2 ',coefup(1) printf,unit,'chi2 ',fmin free_lun,unit mez37=widget_base(dva3,ysize=20) ulozlab=widget_label(dva3,value='The coefficients have been writen to the '+cesta) endif END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ;pro pokrac_event,event ;COMMON udaje11,t11,t12,hranice1,hranice2,button1 ;COMMON universal,tab,coef,cont ;COMMON clb,A_K1,myprofd,index1,pocet_klinu1,b1,a1,S21,nula3,fmin,iter,jedna3 ;COMMON share ;COMMON scal,cekat,base3 ;COMMON cesta,nazevsouboru ;widget_control,event.id,get_uvalue=uvalue ;case uvalue of ;'ANO':BEGIN ; widget_control,event.top,/destroy ; A_K1(0) = coef(1) ; CALCUL,myprofd,index1,pocet_klinu1,b1,a1,S21 ; A_K1(1) = Isl/(a1(0)*In(pocet_klinu1)^a1(1)+a1(2)) ;coefup=fltarr(2) ;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: '+string(fmin),/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='a '+string(a1(0)*A_K1(1)),/align_left) ; blab=widget_label(dvapom2,value='b '+string(a1(1)),/align_left) ; clab=widget_label(dvapom2,value='c '+string(a1(2)*A_K1(1)),/align_left) ; mez36=widget_base(dva3,ysize=40) ; dvapom3=widget_base(dva3,/column,/frame) ; co1lab=widget_label(dvapom3,value='c1 '+string(coefup(0)),/align_left) ; co2lab=widget_label(dvapom3,value='c2 '+string(coefup(1)),/align_left) ; pomzpet=widget_base(jedna3,/column) ; zpet3=widget_button(pomzpet,value='PREVIOUS',uvalue='DRUHA',xsize=150) ;lastocc=rstrpos(nazevsouboru,'\') ;if lastocc eq -1 then lastocc=rstrpos(nazevsouboru,'/') ;kolik=strlen(nazevsouboru)-lastocc-5 ;cesta=strmid(nazevsouboru,lastocc+1,kolik)+'.cfs' ;openw,unit,cesta,/get_lun ;printf,unit,'a ',a1(0)*A_K1(1) ;printf,unit,'b ',a1(1) ;printf,unit,'c ',a1(2)*A_K1(1) ;printf,unit,'c1 ',coefup(0) ;printf,unit,'c2 ',coefup(1) ;printf,unit,'chi2 ',fmin ;free_lun,unit ;mez37=widget_base(dva3,ysize=20) ;ulozlab=widget_label(dva3,value='The coefficients have been writen to the '+cesta) ; END ;'NE':BEGIN ; widget_control,event.top,/destroy ; pomzpet=widget_base(jedna3,/column) ; zpet3=widget_button(pomzpet,value='PREVIOUS',uvalue='DRUHA',xsize=150) ; END ;endcase ;END ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! PRO info11_event,event ;oblast profilu COMMON inner,myprofiles,image,profil,prof11,prof12,prof13,prof14,prof15,$ base1,prof16,base2,poloha2,ymyprof,zavedeno,jas,klin,jasnost COMMON udaje11,t11,t12,hranice1,hranice2,button1 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) for i=0,5 do begin if total(myprofiles(*,i)) ne 0 then begin oblast1=image(fix(hranice11(0)):fix(hranice22(0)),ymyprof(i)-2:ymyprof(i)+2) 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 PRO info21_event,event ;disperse COMMON udaje21,voda2,alfa2,posvoda,posalfa widget_control,event.id,get_uvalue=uvalue case uvalue of 'ZAVRI':BEGIN widget_control,voda2,get_value=posvoda widget_control,alfa2,get_value=posalfa widget_control,event.top,/destroy END endcase END PRO info22_event,event ;kontinuum COMMON udaje22,kont1,kont2,kontinuum1,kontinuum2 widget_control,event.id,get_uvalue=uvalue case uvalue of 'ZAVRI':BEGIN widget_control,kont1,get_value=kontinuum1 widget_control,kont2,get_value=kontinuum2 widget_control,event.top,/destroy END endcase END PRO info23_event,event ;minimizing COMMON udaje23,iksm11,iksm12,iksm21,iksm22,reg11,reg12,reg21,reg22 widget_control,event.id,get_uvalue=uvalue case uvalue of 'ZAVRI':BEGIN widget_control,iksm11,get_value=reg11 & widget_control,iksm12,get_value=reg12 widget_control,iksm21,get_value=reg21 & widget_control,iksm22,get_value=reg22 widget_control,event.top,/destroy END endcase END ;-------------------calib_event--------------------------- PRO calib_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 vse,base,poloha,zac,im,zac2,w2,g1,zac3,jedna,dva,tri,basepoc,f1 COMMON inner,myprofiles,image,profil,prof11,prof12,prof13,prof14,prof15,$ base1,prof16,base2,poloha2,ymyprof,zavedeno,jas,klin,jasnost COMMON scal,cekat,base3 COMMON cesta,nazevsouboru COMMON obecny,cara,button114 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 widget_control,base2,/destroy ;z druhe obrazovky 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='' klin=make_array(8,value=0) cara=1 profil=1 nazevsouboru=pickfile(/read,filter='*.fts') image=readfits(nazevsouboru,header) endif rozmer=size(image) base1=widget_base(base,/column) base11=widget_base(base1,/row) base111=widget_base(base11,/column) oznobr=widget_label(base111,value='Image for calibration') im=widget_draw(base111,xsize=rozmer(1),ysize=rozmer(2),x_scroll_size=500,y_scroll_size=500,$ /motion_events,/button_events,uvalue='OBR') base12=widget_base(base11,/column) basemezera1=widget_base(base11,xsize=50) base13=widget_base(base11,/column) mez1=widget_base(base12,ysize=20) lab1=widget_label(base12,value='range for profiles',/align_left) button112=widget_button(base12,value='range',uvalue='INFO11',xsize=110) mez2=widget_base(base12,ysize=20) lab2=widget_label(base12,value='number of profile',/align_left) ;base12 button1=widget_button(base12,value='1',/menu,xsize=110) 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') ; button17=widget_button(button1,value='delete 3',uvalue='7jedna') ; button18=widget_button(button1,value='delete 4',uvalue='8jedna') ; button19=widget_button(button1,value='delete 5',uvalue='9jedna') mez3=widget_base(base12,ysize=20) lab3=widget_label(base12,value='coordinates',/align_left) button113=widget_button(base12,value='coordinates of region',uvalue='INFO12',xsize=110) mez4=widget_base(base12,ysize=20) lab2=widget_label(base12,value='spectral line',/align_left) button114=widget_button(base12,value='Halpha',/menu,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') ; widget_control,button1143,sensitive=0 mezer1=widget_base(base12,ysize=150) pollab=widget_label(base12,value='position',/align_left) poloha=widget_label(base12,value='position',/frame,xsize=110,/align_left) mezer2=widget_base(base12,ysize=20) jaslab=widget_label(base12,value='brightness',/align_left) jas=widget_slider(base12,uvalue='BRI',value=jasnost,min=0,max=50) case cara of 1:begin widget_control,button114,set_value='Halpha' end 2:begin widget_control,button114,set_value='Hbeta' end 3:begin widget_control,button114,set_value='CaII' end endcase profmez=widget_base(base13,ysize=20) ozn11=widget_label(base13,value='Profile from 1st wedge step') & prof11=widget_draw(base13,xsize=200,ysize=62) ozn12=widget_label(base13,value='Profile from 2nd wedge step') & prof12=widget_draw(base13,xsize=200,ysize=62) ozn13=widget_label(base13,value='Profile from 3rd wedge step') & prof13=widget_draw(base13,xsize=200,ysize=62) ozn14=widget_label(base13,value='Profile from 4th wedge step') & prof14=widget_draw(base13,xsize=200,ysize=62) ozn15=widget_label(base13,value='Profile from 5th wedge step') & prof15=widget_draw(base13,xsize=200,ysize=62) ozn16=widget_label(base13,value='Profile of quiet sun') & prof16=widget_draw(base13,xsize=200,ysize=62) base14=widget_base(base1,/row) dalsi1=widget_button(base14,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,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 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 'DISP':BEGIN ;disperse case cara of 1:begin napis1='6560.555' & napis2='6564.206' end 2:begin napis1='4859.747' & napis2='4862.598' end 3:begin napis1='8540.817' & napis2='8542.144' ;dodelat end endcase dispbase2=widget_base(/column) dis1=widget_base(dispbase2,/row) & dis2=widget_base(dispbase2,/row) ;& dis3=widget_base(dispbase2,/row) alfa2=cw_field(dis1,title='position of '+napis1+' line') voda2=cw_field(dis2,title='position of '+napis2+' line') okbut21=widget_button(dispbase2,value='OK',uvalue='ZAVRI') widget_control,alfa2,set_value=posalfa & widget_control,voda2,set_value=posvoda widget_control,dispbase2,/realize xmanager,'info21',dispbase2 END 'CONT':BEGIN ;kontinuum kontbase2=widget_base(/column) kon1=widget_base(kontbase2,/row) & kon2=widget_base(kontbase2,/row) kont1=cw_field(kon1,title='left x position of continuum') kont2=cw_field(kon2,title='right x position of continuum') okbut22=widget_button(kontbase2,value='OK',uvalue='ZAVRI') widget_control,kont1,set_value=kontinuum1 & widget_control,kont2,set_value=kontinuum2 widget_control,kontbase2,/realize xmanager,'info22',kontbase2 END 'MINIMIZING':BEGIN ;fitting minbase2=widget_base(/column) zn1=widget_label(minbase2,value='1st region for fitting',/frame,/align_left) minim1=widget_base(minbase2,/row) iksm11=cw_field(minim1,title='left x position') iksm12=cw_field(minim1,title='right x position') zn2=widget_label(minbase2,value='2nd region for fitting',/frame,/align_left) minim2=widget_base(minbase2,/row) iksm21=cw_field(minim2,title='left x position') iksm22=cw_field(minim2,title='right x position') okbut31=widget_button(minbase2,value='OK',uvalue='ZAVRI') widget_control,iksm11,set_value=reg11 & widget_control,iksm12,set_value=reg12 widget_control,iksm21,set_value=reg21 & widget_control,iksm22,set_value=reg22 widget_control,minbase2,/realize xmanager,'info23',minbase2 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) 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 (fix(longt(0)) eq 0) or (fix(lat(0)) eq 0) then test=0 ;if (total(myprofiles(*,0)) eq 0) or (total(myprofiles(*,1)) eq 0) or (total(myprofiles(*,5)) eq 0) then test=0 ;if (total(myprofiles(*,0)) eq 0) or (total(myprofiles(*,5)) eq 0) then test=0 ;if total(klin(0:total(klin)-1)) ne total(klin) then test=0 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 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 zac2=1 base2=widget_base(base,/column) base21=widget_base(base2,/row) dr12=widget_draw(base21,xsize=500,ysize=500,/motion_events,uvalue='OBR2') base23=widget_base(base21,/column) displab=widget_label(base23,value='dispersion curve',/align_left) disp=widget_button(base23,value='position of lines',uvalue='DISP',xsize=110) dispmez=widget_base(base23,ysize=20) kontlab=widget_label(base23,value='continuum',/align_left) kont=widget_button(base23,value='position of continuum',uvalue='CONT',xsize=110) kontmez=widget_base(base23,ysize=20) minimlab=widget_label(base23,value='fitting',/align_left) minim=widget_button(base23,value='regions for fitting',uvalue='MINIMIZING',xsize=110) minimmez=widget_base(base23,ysize=250) poloha2lab=widget_label(base23,value='position',/align_left) poloha2=widget_label(base23,value='position',/frame,xsize=110) 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 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 test=1 ;neni zadane if (fix(posvoda(0)) eq 0) or (fix(posalfa(0)) eq 0) then test=0 if (fix(kontinuum1(0)) eq 0) or (fix(kontinuum2(0)) eq 0) then test=0 if (fix(reg11(0)) eq 0) or (fix(reg12(0)) eq 0) or (fix(reg21(0)) eq 0) or (fix(reg22(0)) eq 0) then test=0 s=size(myprofiles) ;neni v poli myprofiles if (fix(posvoda(0)) lt 0) or (fix(posvoda(0)) gt s(1)) then test=0 if (fix(posalfa(0)) lt 0) or (fix(posalfa(0)) gt s(1)) then test=0 if (fix(kontinuum1(0)) lt 0) or (fix(kontinuum1(0)) gt s(1)) then test=0 if (fix(kontinuum2(0)) lt 0) or (fix(kontinuum2(0)) gt s(1)) then test=0 if (fix(reg11(0)) lt 0) or (fix(reg11(0)) gt s(1)) then test=0 if (fix(reg12(0)) lt 0) or (fix(reg12(0)) gt s(1)) then test=0 if (fix(reg21(0)) lt 0) or (fix(reg21(0)) gt s(1)) then test=0 if (fix(reg22(0)) lt 0) or (fix(reg22(0)) gt s(1)) then test=0 ;prehozene hodnoty if (fix(posalfa(0)) ge fix(posvoda(0))) or (fix(kontinuum1(0)) ge fix(kontinuum2(0))) then test=0 if (fix(reg11(0)) ge fix(reg12(0))) or (fix(reg12(0)) ge fix(reg21(0))) then test=0 if (fix(reg21(0)) ge fix(reg22(0))) 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) ;disperse disp1=make_array(2,/float) & disp2=make_array(2,/float) disp2(0)=fix(posalfa(0)) & disp2(1)=fix(posvoda(0)) case cara of 1:begin disp1(0)=6560.555 & disp1(1)=6564.206 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 ;neni udelane tabulka='caii.tab' end endcase result=poly_fit(double(disp2),disp1,1) coef=dblarr(2) & coef(0)=result(0) & coef(1)=result(1) ;kontinuum cont=make_array(2,/int) & cont(0)=fix(kontinuum1(0)) & cont(1)=fix(kontinuum2(0)) ;vstupni pole pro clb_curv myprofiles1=make_array(s(1),total(klin)+1) myprofiles1(*,0:total(klin)-1)=myprofiles(*,where(klin)) myprofiles1(*,total(klin))=myprofiles(*,5) ;klidne slunce ;oblasti minimalizace reg=make_array(2,2,/int) reg(0,0)=fix(reg11(0)) & reg(0,1)=fix(reg21(0)) & reg(1,0)=fix(reg12(0)) & reg(1,1)=fix(reg22(0)) Draw=1 & Start_point=1.8 & stred=float(center(0)) tab=get_tab(tabulka,stred,fix(longt(0)),fix(lat(0))) clb_curv,myprofiles1,a,s2,reg,a_k,Id_klin=klin,Start_point=Start_point,/Draw 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,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 ;-----------------------deleting of profile------------------- ;'7jedna':begin ; myprofiles(*,2)=0 ; ymyprof(2)=0 & klin(2)=0 ; widget_control,prof13,get_value=nastavsmazat ; wset,nastavsmazat & erase ; end ;'8jedna':begin ; myprofiles(*,3)=0 ; ymyprof(3)=0 & klin(3)=0 ; widget_control,prof14,get_value=nastavsmazat ; wset,nastavsmazat & erase ; end ;'9jedna':begin ; myprofiles(*,4)=0 ; ymyprof(4)=0 & klin(4)=0 ; widget_control,prof15,get_value=nastavsmazat ; wset,nastavsmazat & erase ; 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 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,'calib',base END