dustem_run_plugins.pro 11.4 KB
PRO dustem_run_plugins, p_dim ,$
                        param_descs,$
                        param_values,$
                        param_func,$
                        scopes,$
                        st=st,$
                        avoid=avoid,$
                        dustem_run=dustem_run,$
                        help=help

;+
; NAME:
;    dustem_run_plugins
;  
; PURPOSE:
;    runs the plugins according to their scopes
;    a N_ELEMENTS(PLUGINS)X N_ELEMENTS(SCOPES) matrix is created to achieve this 
;
; CATEGORY:
;    DustEMWrap, Distributed, Mid-Level, Plugins
;
; CALLING SEQUENCE:
;    dustem_run_plugins,p_dim,param_descs,param_values,scopes,[,st][,avoid][,dustem_run][,/help] 
;
; INPUTS:
;    p_dim  = parameter values 
;    param_descs = parameter description vector
;    param_values = current parameter values
;    param-func   = plugin indices array 
;    scopes       = scopes of plugins 
;
; OPTIONAL INPUT PARAMETERS:
;    avoid      = scopes should be avoided
;    dustem_run = Dustem should be run
;
; OUTPUTS:
;    None
;
; OPTIONAL OUTPUT PARAMETERS:
;    st         = Dustem output structure
;
; ACCEPTED KEY-WORDS:
;    help                  = if set, print this help
;
; COMMON BLOCKS:
;    None
;
; SIDE EFFECTS:
;    None
;
; RESTRICTIONS:
;    The DustEM fortran code must be installed
;    The DustEMWrap IDL code must be installed
;
; PROCEDURES AND SUBROUTINES USED:
;
; EXAMPLES
;    dustem_activate_plugins, p_min, pram_descs, param_values, param_func, scopes, st=st, avoid=avoid, dustem_run=dustem_run 
;
; MODIFICATION HISTORY:
;    Written by IC 
;    Evolution details on the DustEMWrap gitlab.
;    See http://dustemwrap.irap.omp.eu/ for FAQ and help.  
;-



;Because I don't want to run this block each time the procedure is run I will test on the presence of all the scope tags in !dustem_plugin
;if all of them are present then this block has been run. 

;stop 

dew_prefix='dustem_plugin_' ; we assume that this prefix is at the start of all plugin routines

IF (tag_names(*!dustem_plugin))(0) EQ 'NONE' THEN goto, the_end 

;Just to be sure 
if not keyword_set(avoid) then avoid=0
if not keyword_set(dustem_run) then dustem_run=0

;stop

test_all_scopes = 1. 
FOR i=0L,n_tags(*!dustem_plugin)-1 DO BEGIN

	IF isa(((*!dustem_plugin).(i).scope)) then test=1 else test=0
	test_all_scopes*=test 

ENDFOR

;stop

IF ~test_all_scopes THEN BEGIN
	;FIRST LOOP TO RETRIEVE THE SCOPES OF ALL THE PLUGINS
	f=1 ; Initializing the index that is associated to each plugin 
	FOR i=0L,n_elements(param_descs)-1 DO BEGIN
	   
	   parameter_type=dustem_parameter_description2type(param_descs[i],string_name=string_name) ; Looping over the parameter description vector (here saved in a system variable) to sort out its different elements with repect to their types
	   
	   IF parameter_type EQ 'PLUGIN' THEN BEGIN   ; Selecting the plugins
	        
	        ftn = strmid(param_descs[i],0) ; String containing the name of the plugin and the keyword used (ie: dustem_create_continuum_2)    
	        ii = strsplit(ftn,'_',count=countx) & ii = ii[countx-1]-1 ; Locating the last underscore to automate the extraction of the plugin's keyword
	        ftn = strmid(ftn,0,ii) ; String containing the name of the plugin without the associated keyword
                this_plugin = strupcase(strmid(ftn,strlen(dew_prefix)))

;                end_char=strlen(this_plugin)
;	        k=where(tag_names(*!dustem_plugin) eq strmid(this_plugin,0,end_char),counte) ; Selecting a plugin through matching the string name of the plugin from the scope system variable with the one read from the parameter description vector
	        k=where(tag_names(*!dustem_plugin) eq this_plugin,counte) ; Selecting a plugin through matching the string name of the plugin from the scope system variable with the one read from the parameter description vector
                
	        tmp = where(param_func eq f, count) ; Array of indices helping with the sorting out of the different plugins (as a plugin can be called several times with different keywords so as to fit several quantities) 
	        PDO_tmp = param_descs(tmp) ; Array containing the different calls of each plugin at a time
	         
	        p_dim_tmp = param_values(tmp) ; Array containing the values of the fitted parameters
	        
	        vari = strmid(PDO_tmp(0),ii+1) ; Test variable to be used to alter the initialization of the index and value arrays below as a keyword can be a scalar or a string
	        
	        ; Initialization of the index and value arrays. These arrays will be used (below) when calling the plugins (with the default key=key and val=val keywords)
	        ;JPB: I have seen cases where count=0 there, which makes the code fail. So including that test below
	        IF count EQ 0 THEN BEGIN
	        	message, 'something went wrong, signé JPB',/continue
	        	stop
	        ENDIF
	        if strlen(strtrim(string(vari),2)) gt 1 then begin
	            index = strarr(count) & value = fltarr(count)  
	        endif else  begin
	            index = fltarr(count) & value = fltarr(count)
	        endelse
	        
	        ; Filling the index and value arrays for one plugin at a time  
	        FOR l=0, count-1 DO BEGIN
	           index[l] = strmid(PDO_tmp[l],ii+1) 
	           value[l] = p_dim_tmp[l]                      
	        ENDFOR    
	        
	        ;==============Dry run of the plugins to obtain their scopes and run them accordingly==============
                
	        str='toto='+ftn+'(scope=scope)' & str=str(0)        
                toto=execute(str)
	        ((*!dustem_plugin).(k).scope)=ptr_new(scope)
	           
                str='toto='+ftn+'(paramtag=paramtag)' & str=str(0)        
                toto=execute(str)            
                ((*!dustem_plugin).(k).paramtag)=ptr_new(paramtag)    
	            
	        f=f+1 & i=i+count-1 ; Incrementing the parameter and same-type plugin indices  
	  ENDIF
	ENDFOR
ENDIF

;stop

;LOCATING THE PLUGINS THAT SHOULD BE RUN

indices = fltarr(n_tags(*!dustem_plugin),n_elements(scopes)) ;


FOR i=0L,n_elements(scopes)-1 DO BEGIN

	;test if there is a '*' string. This means that all scopes containing that string will be either avoided or chosen.
	;this means that we need the index of the scope corresponding to this string.
		
	;first we need to extract the string between the two '*' and then match it with the existing plugin 
	; this enables us to get the indices of the plugins to run...

	IF strmid(scopes(i),0,1) EQ '*' THEN BEGIN

		;Now I need to locate the second '*': 
		ind_ast = STRPOS(scopes(i), '*', /REVERSE_SEARCH)
		scope_to_match = strmid(scopes(i),1,ind_ast-1) 
		;
	ENDIF ELSE BEGIN ;assuming the string is identical to the plugin's scope
	
    	scope_to_match = strupcase(scopes(i))  
        
	ENDELSE	
	;Now locating the indices of this scope in !dustem_plugin. 
        
	FOR j=0L,n_tags(*!dustem_plugin)-1 DO BEGIN
        
        test = strcmp((*((*!dustem_plugin).(j).scope)),scope_to_match,strlen(scope_to_match),/FOLD_CASE) EQ 1
        
        IF test and keyword_set(avoid) THEN BEGIN
            if (size(indices))[0] GT 1 then indices[j,i] *= 0 ELSE indices[j] *= 0
 		ENDIF ;ELSE BEGIN
;     		if (size(indices))[0] GT 1 then indices[j,i] = 1 ELSE indices[j] = 1
; 		ENDELSE 
; 		
		IF test and not keyword_set(avoid)then  BEGIN
    		if (size(indices))[0] GT 1 then indices[j,i] += 1 ELSE indices[j] += 1
    		
		ENDIF
		
		if ~test and keyword_set(avoid) then begin
            if (size(indices))[0] GT 1 then indices[j,i] += 1 ELSE indices[j] += 1

        endif
        		
	ENDFOR		

ENDFOR

;stop
;RUNNING THE PLUGINS ACCORDING TO THEIR SCOPES

f=1 ; Initializing the index that is associated to each plugin 
FOR i=0L,n_elements(param_descs)-1 DO BEGIN
	   
	parameter_type=dustem_parameter_description2type(param_descs[i],string_name=string_name) ; Looping over the parameter description vector (here saved in a system variable) to sort out its different elements with repect to their types
	  
	IF parameter_type EQ 'PLUGIN' THEN BEGIN   ; Selecting the plugins
	    ;stop
       ftn = strmid(param_descs(i),0) ; String containing the name of the plugin and the keyword used (ie: dustem_create_continuum_2)    
       ii = strsplit(ftn,'_',count=countx) & ii = ii(countx-1)-1 ; Locating the last underscore to automate the extraction of the plugin's keyword
       ftn = strmid(ftn,0,ii) ; String containing the name of the plugin without the associated keyword
       this_plugin = strupcase(strmid(ftn,strlen(dew_prefix)))

;                end_char=strlen(this_plugin)
;	        k=where(tag_names(*!dustem_plugin) eq strmid(this_plugin,0,end_char),counte) ; Selecting a plugin through matching the string name of the plugin from the scope system variable with the one read from the parameter description vector
	        k=where(tag_names(*!dustem_plugin) eq this_plugin,counte) ; Selecting a plugin through matching the string name of the plugin from the scope system variable with the o

       
;       k=where(strmid(tag_names(*!dustem_plugin),0,8) eq strmid(strupcase(strmid(ftn,14)),0,8),counte) ; Selecting a plugin through matching the string name of the plugin from the scope system variable with the one read from the parameter description vector
       ;help,f
       ;stop
       tmp = where(param_func eq f, count) ; Array of indices helping with the sorting out of the different plugins (as a plugin can be called several times with different keywords so as to fit several quantities) 
       PDO_tmp = param_descs(tmp) ; Array containing the different calls of each plugin at a time
         
       p_dim_tmp = param_values(tmp) ; Array containing the values of the parameters used for the run
        
       vari = strmid(PDO_tmp(0),ii+1) ; Test variable to be used to alter the initialization of the index and value arrays below for a keyword can be a scalar or a string
        
        ; Initialization of the index and value arrays. These arrays will be used (below) when calling the plugins (with the default key=key and val=val keywords)
       ;print,ftn,ii,ftn,counte
       ;print,PDO_tmp,p_dim_tmp,vari
       if strlen(strtrim(string(vari),2)) gt 1 then begin
           index = strarr(count) & value = fltarr(count)  
       endif else  begin
           index = fltarr(count) & value = fltarr(count)
       endelse
       ;help,'<<<<',index,count

        ; Filling the index and value arrays for one plugin at a time  
       FOR l=0, count-1 DO BEGIN
          index[l] = strmid(PDO_tmp[l],ii+1) 
          value[l] = p_dim_tmp[l]                      
       ENDFOR    
        
       ;==============Running of the plugins according to their scopes==============
   
       ;stop
       if keyword_set(avoid) then idd=product(indices[k,*]) else idd=total(indices[k,*])
        	   
       IF  idd GE 1 THEN BEGIN
           str='((*!dustem_plugin).('+strtrim(k,2)+').spec)=ptr_new('+ftn+'(key=index,val=value)'+')' & str=str(0)
           ;print,'>>>>>',str
           ;stop
           ;plante fawlty quand
           ;((*!dustem_plugin).(1).spec)=ptr_new(dustem_plugin_stellar_population(key=index,val=value))
           toto=execute(str)
           ;stop
           IF !dustem_verbose NE 0 THEN message,strupcase(strmid(ftn,7)),/info
       ENDIF
	   
	     
          
      f=f+1 & i=i+count-1 ; Incrementing the parameter and same-type plugin indices  
    	  
	ENDIF
ENDFOR


the_end:
if keyword_set(dustem_run) then begin ;and idd gt 0. : remved this so that dustem is always run when the keyword is mentioned.
   st = dustem_run(p_dim)
   !dustem_current = ptr_new(st)
endif 


END