70 INTEGER,
INTENT(IN) :: ispectype
71 TYPE(t_region
),
DIMENSION(:),
POINTER :: regions
77 INTEGER,
PARAMETER :: nkeys = 8, nstrkeys = 1
79 CHARACTER(CHRLEN) :: keys(nkeys),strkeys(nstrkeys),strvals(nstrkeys)
80 CHARACTER(CHRLEN) :: rcsidentstring
81 LOGICAL :: defined(nkeys),strdefined(nstrkeys)
82 REAL(RFREAL) :: vals(nkeys)
94 rcsidentstring =
'$RCSfile: SPEC_ReadSpecTypeSection.F90,v $ $Revision: 1.10 $'
96 global => regions(1)%global
99 'SPEC_ReadSpecTypeSection.F90')
105 keys(1) =
'FROZENFLAG'
107 keys(3) =
'SOURCETYPE'
108 keys(4) =
'SCHMIDTNO'
110 keys(6) =
'PUFFFACTOR'
111 keys(7) =
'VELOCITYMETHOD'
112 keys(8) =
'SETTLINGFLAG'
114 strkeys(1) =
'MATERIAL'
121 CALL
readbothsection(global,if_input,nkeys,nstrkeys,keys,strkeys,vals, &
122 strvals,defined,strdefined)
133 IF ( defined(1) .EQV. .true. )
THEN
134 DO ireg = lbound(regions,1),ubound(regions,1)
135 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
136 IF ( nint(vals(1)) == 0 )
THEN
137 regions(ireg)%specInput%specType(ispectype)%frozenFlag = .false.
139 regions(ireg)%specInput%specType(ispectype)%frozenFlag = .true.
149 IF ( defined(2) .EQV. .true. )
THEN
150 DO ireg = lbound(regions,1),ubound(regions,1)
151 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
152 regions(ireg)%specInput%specType(ispectype)%initVal = vals(2)
161 IF ( defined(3) .EQV. .true. )
THEN
162 DO ireg = lbound(regions,1),ubound(regions,1)
163 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
164 regions(ireg)%specInput%specType(ispectype)%sourceType = nint(vals(3))
173 IF ( defined(4) .EQV. .true. )
THEN
174 DO ireg = lbound(regions,1),ubound(regions,1)
175 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
176 regions(ireg)%specInput%specType(ispectype)%schmidtNumber = vals(4)
185 IF ( defined(5) .EQV. .true. )
THEN
186 DO ireg = lbound(regions,1),ubound(regions,1)
187 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
188 regions(ireg)%specInput%specType(ispectype)%diameter = vals(5)
197 IF ( defined(6) .EQV. .true. )
THEN
198 DO ireg = lbound(regions,1),ubound(regions,1)
199 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
200 regions(ireg)%specInput%specType(ispectype)%puffFactor = vals(6)
209 IF ( defined(7) .EQV. .true. )
THEN
210 DO ireg = lbound(regions,1),ubound(regions,1)
211 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
212 regions(ireg)%specInput%specType(ispectype)%velocityMethod = &
222 IF ( defined(8) .EQV. .true. )
THEN
223 DO ireg = lbound(regions,1),ubound(regions,1)
224 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
225 IF ( nint(vals(8)) == 0 )
THEN
226 regions(ireg)%specInput%specType(ispectype)%settlingFlag = .false.
228 regions(ireg)%specInput%specType(ispectype)%settlingFlag = .true.
238 IF ( strdefined(1) .EQV. .true. )
THEN
239 DO ireg = lbound(regions,1),ubound(regions,1)
240 IF ( ispectype <= regions(ireg)%specInput%nSpecies )
THEN
241 pspectype => regions(ireg)%specInput%specType(ispectype)
subroutine readbothsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, defined, strDefined)
subroutine spec_readspectypesection(regions, iSpecType)
subroutine inrt_setmaterial(global, material, name)
subroutine registerfunction(global, funName, fileName)
subroutine readsection(global, fileID, nvals, keys, vals, defined)
subroutine deregisterfunction(global)