69 TYPE(t_region
),
DIMENSION(:),
POINTER :: regions
75 CHARACTER(CHRLEN) :: rcsidentstring
80 TYPE(t_region
),
POINTER :: pregion
83 INTEGER :: contcntr,ispec
91 rcsidentstring =
'$RCSfile: RFLU_SetDerivedUserInput.F90,v $ $Revision: 1.12 $'
93 global => regions(1)%global
96 'RFLU_SetDerivedUserInput.F90')
102 DO ireg = lbound(regions,1),ubound(regions,1)
103 pregion => regions(ireg)
104 pmixtinput => pregion%mixtInput
105 pspecinput => pregion%specInput
115 IF ( pmixtinput%gasModel == gas_model_mixt_tcperf )
THEN
116 IF ( global%specUsed .EQV. .false. )
THEN
117 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
118 'Species module must be active.')
121 IF ( pspecinput%nSpecies <= 1 )
THEN
122 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
123 'Must have at least one species.')
126 DO ispec = 1,pspecinput%nSpecies
127 pspectype => pregion%specInput%specType(ispec)
129 IF ( pspectype%discreteFlag .EQV. .true. )
THEN
130 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
131 'Can only have gaseous species.')
135 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
136 'Can only be used with species module.')
144 ELSE IF ( pmixtinput%gasModel == gas_model_mixt_pseudo )
THEN
145 IF ( global%specUsed .EQV. .false. )
THEN
146 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
147 'Species module must be active.')
150 IF ( pspecinput%nSpecies <= 1 )
THEN
151 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
152 'Must have at least one species.')
157 DO ispec = 1,pspecinput%nSpecies
158 pspectype => pregion%specInput%specType(ispec)
160 IF ( pspectype%discreteFlag .EQV. .false. )
THEN
161 contcntr = contcntr + 1
165 IF ( contcntr == 0 )
THEN
166 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
167 'Must have at least one gaseous species.')
170 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
171 'Can only be used with species module.')
179 ELSE IF ( pmixtinput%gasModel == gas_model_mixt_gasliq )
THEN
180 IF ( global%specUsed .EQV. .false. )
THEN
181 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
182 'Species module must be active.')
185 IF ( pspecinput%nSpecies <= 1 )
THEN
186 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
187 'Must have two species.')
190 DO ispec = 1,pspecinput%nSpecies
191 pspectype => pregion%specInput%specType(ispec)
193 IF ( pspectype%discreteFlag .EQV. .true. )
THEN
194 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
195 'Can only have gaseous species.')
199 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
200 'Can only be used with species module.')
209 IF ( global%specUsed .EQV. .true. )
THEN
210 pmixtinput%indMfMixt = 1
212 pmixtinput%indMfMixt = 0
220 IF ( global%specUsed .EQV. .true. )
THEN
221 DO ispec = 1,pspecinput%nSpecies
222 IF ( pspecinput%specType(ispec)%velocityMethod == &
223 spec_methv_eqeul )
THEN
235 IF ( global%specUsed .EQV. .true. )
THEN
236 IF ( (pmixtinput%gasModel == gas_model_mixt_gasliq) .AND. &
237 (pspecinput%sourceFlag .EQV. .true.) )
THEN
238 DO ispec = 1,pspecinput%nSpecies
239 IF ( pspecinput%specType(ispec)%sourceType /= &
240 spec_source_type_cavi )
THEN
241 CALL
errorstop(global,err_spec_source_type_invalid,__line__)
subroutine registerfunction(global, funName, fileName)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)