dustem_sort_params.pro 2.84 KB
PRO dustem_sort_params

;+
; NAME:
;       dustem_sort_params
; CALLING SEQUENCE:
;       dustem_sort_params
; PURPOSE:
;	Sorts the parameter descriptions and values the way they must
;	be processed.
; INPUTS:
;       None
; OPTIONAL INPUT:
;       None
; OUTPUTS:
;       None
; PROCEDURE AND SUBROUTINE USED
;       Parameter description (!param_desc) and values (!init_value) are
;       ordered the way they should be processed. The ordered information
;       is put into system variables !PDO and !IDO respectively
;       If the isrf is being modified, then, PAH ionization fraction
;       is set to be updated as well.
; SIDE EFFECTS:
;       !PDO and !IDO variables are set.
;       Optionally !ionfrac is set.
;       The !func_ind variable is set.
; MODIFICATION HISTORY:
;       See cvs logs
;       Written by NF,JPB,DP Jan-2007
;-

nparam = n_elements(*!param_desc)
!func_ind=ptr_new(fltarr(nparam))

;SORT THE PARAMETERS
ord = sort(*!param_desc)
!PDO = ptr_new((*!param_desc)(ord))     ;param_desc ordered (PDO)
!IDO = ptr_new((*!init_value)(ord))     ;init_desc ordered (IDO)

;DEAL WITH THE ISRF<->IONFRAC DEPENDENCY
fct = strarr(nparam)
FOR i=0L,nparam-1 DO BEGIN
   fct(i) = strmid((*!PDO)(i),0,strlen((*!PDO)(i))-2.)
ENDFOR
wisrf = where(fct eq 'dustem_create_isrf' or fct eq 'dustem_create_isrf2',cisrf) ;DUSTEM_CREATE_ISRF is being called as a param ?
IF cisrf NE 0 THEN BEGIN
   wionf = where(fct EQ 'dustem_create_ionfrac',cionf) ; DUSTEM_CREATE_IONFRAC is being called as a param ?
; ISRF(yes), IONFRAC(no) => then everything is set by the IONFRACPAH in GRAIN.DAT
; ISRF(yes), IONFRAC(yes) => make sure DUSTEM_CREATE_IONFRAC is called after DUSTEM_CREATE_ISRF
   IF cionf NE 0 THEN BEGIN
      IF (wisrf(cisrf-1)) NE (nparam-1) THEN BEGIN ;ISRF was not the last in the list
         (*!PDO) = [(*!PDO)(0:wionf(0)-1), (*!PDO)(wisrf(0):wisrf(cisrf-1)), (*!PDO)(wionf(0):wionf(cionf-1)), (*!PDO)(wisrf(cisrf-1)+1:*)]
         (*!IDO) = [(*!IDO)(0:wionf(0)-1), (*!IDO)(wisrf(0):wisrf(cisrf-1)), (*!IDO)(wionf(0):wionf(cionf-1)), (*!IDO)(wisrf(cisrf-1)+1:*)]
      ENDIF ELSE BEGIN          ;ISRF was the last in the list
         (*!PDO) = [(*!PDO)(0:wionf(0)-1), (*!PDO)(wisrf(0):wisrf(cisrf-1)), (*!PDO)(wionf(0):wionf(cionf-1))]
         (*!IDO) = [(*!IDO)(0:wionf(0)-1), (*!IDO)(wisrf(0):wisrf(cisrf-1)), (*!IDO)(wionf(0):wionf(cionf-1))]
      ENDELSE
   ENDIF
ENDIF

;SET !FUNC_IND VALUES
; !FUNC_IND = 0 for the DUSTEM_PARAMS
; !FUNC_IND = 1 for the first DUSTEM_CREATE function, !FUNC_IND = 2 for the second DUSTEM_CREATE function ...
ind = 1.
fct_prev = ''
FOR i=0L,nparam-1 DO BEGIN
  IF (strmid((*!PDO)(i),0,3) NE '(*!') THEN BEGIN
    fct = strmid((*!PDO)(i),14,strlen((*!PDO)(i))-16)
    IF (fct EQ fct_prev) THEN BEGIN
      (*!func_ind)(i)=(*!func_ind)(i-1)
    ENDIF ELSE BEGIN
      (*!func_ind)(i)=ind
      ind=ind+1
    ENDELSE
    fct_prev=fct
  ENDIF
ENDFOR

END