Blame view

src/idl/dustem_sort_params.pro 3.2 KB
427f1205   Jean-Michel Glorian   version 4.2 merged
1
2
3
4
5
PRO dustem_sort_params

;+
; NAME:
;       dustem_sort_params
93cd417b   Annie Hughes   updated help
6
7
8
9
;
; CATEGORY:
;    DustEMWrap, Distributed, Low-Level
;
427f1205   Jean-Michel Glorian   version 4.2 merged
10
11
; CALLING SEQUENCE:
;       dustem_sort_params
93cd417b   Annie Hughes   updated help
12
;
427f1205   Jean-Michel Glorian   version 4.2 merged
13
14
15
; PURPOSE:
;	Sorts the parameter descriptions and values the way they must
;	be processed.
93cd417b   Annie Hughes   updated help
16
;
427f1205   Jean-Michel Glorian   version 4.2 merged
17
18
; INPUTS:
;       None
93cd417b   Annie Hughes   updated help
19
;
427f1205   Jean-Michel Glorian   version 4.2 merged
20
21
; OPTIONAL INPUT:
;       None
93cd417b   Annie Hughes   updated help
22
;
427f1205   Jean-Michel Glorian   version 4.2 merged
23
24
; OUTPUTS:
;       None
93cd417b   Annie Hughes   updated help
25
;
427f1205   Jean-Michel Glorian   version 4.2 merged
26
27
28
29
30
31
; 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.
93cd417b   Annie Hughes   updated help
32
;
427f1205   Jean-Michel Glorian   version 4.2 merged
33
34
35
36
; SIDE EFFECTS:
;       !PDO and !IDO variables are set.
;       Optionally !ionfrac is set.
;       The !func_ind variable is set.
93cd417b   Annie Hughes   updated help
37
38
39
40
41
;
; RESTRICTIONS:
;    The DustEM fortran code must be installed
;    The DustEMWrap IDL code must be installed
;  
427f1205   Jean-Michel Glorian   version 4.2 merged
42
; MODIFICATION HISTORY:
93cd417b   Annie Hughes   updated help
43
44
45
;    Written by NF,JPB,DP Jan-2007
;    Evolution details on the DustEMWrap gitlab.
;    See http://dustemwrap.irap.omp.eu/ for FAQ and help.  
427f1205   Jean-Michel Glorian   version 4.2 merged
46
47
;-

93cd417b   Annie Hughes   updated help
48
49
50
51
52
  IF keyword_set(help) THEN BEGIN
     doc_library,'dustem_sort_params'
     goto,the_end
  END

427f1205   Jean-Michel Glorian   version 4.2 merged
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
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