60 CHARACTER(CHRLEN),
PRIVATE :: &
119 INTEGER,
INTENT(IN) :: ipatch,ifile1,ifile2
126 CHARACTER(CHRLEN) :: ifilename1,ifilename2
134 'RFLU_ModThrustSpecImpulse.F90')
140 IF ( global%verbLevel > verbose_low )
THEN
141 WRITE(stdout,
'(A,1X,A,I4.4)') solver_name,
'Closing thrust and '// &
142 'specific impulse files for iPatch =',ipatch
149 WRITE(ifilename1,
'(A,I4.4)') trim(global%outDir)// &
150 trim(global%casename)//
'.thr_',ipatch
152 WRITE(ifilename2,
'(A,I4.4)') trim(global%outDir)// &
153 trim(global%casename)//
'.isp_',ipatch
159 CLOSE(ifile1,iostat=errorflag)
160 IF (global%error /= err_none )
THEN
161 CALL
errorstop(global,err_file_close,__line__,
'File: '// &
164 CLOSE(ifile2,iostat=errorflag)
165 IF (global%error /= err_none )
THEN
166 CALL
errorstop(global,err_file_close,__line__,
'File: '// &
174 IF ( global%verbLevel > verbose_low )
THEN
175 WRITE(stdout,
'(A,1X,A)') solver_name,
'Closing thrust and '// &
176 'specific impulse files done.'
219 TYPE(t_region
),
POINTER :: pregion
225 INTEGER :: errorflag,ipatch,ipatchglobal
226 REAL(RFREAL) :: forcecoeff2thrust,thrust2isp,masscoeffin,masscoeffout, &
228 REAL(RFREAL),
DIMENSION(:,:,:),
POINTER :: pforcecoeff,pforcecoeffvac
229 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pspecimpulse,pspecimpulsevac, &
237 global => pregion%global
240 'RFLU_ModThrustSpecImpulse.F90')
242 pforcecoeff => pregion%forceCoeffsGlobal
243 pforcecoeffvac => pregion%forceVacCoeffsGlobal
244 pspecimpulse => pregion%specImpulseGlobal
245 pspecimpulsevac => pregion%specImpulseVacGlobal
246 pthrust => pregion%thrustGlobal
247 pthrustvac => pregion%thrustVacGlobal
257 masscoeffin = 0.0_rfreal
258 masscoeffout = 0.0_rfreal
262 DO ipatch = 1,pregion%global%nPatches
263 masscoeffin = masscoeffin + pregion%massCoeffsGlobal(mass_in ,ipatch)
264 masscoeffout = masscoeffout + pregion%massCoeffsGlobal(mass_out,ipatch)
267 massin = masscoeffin*global%refDensity*global%refVelocity*global%forceRefArea
268 massout = masscoeffout*global%refDensity*global%refVelocity*global%forceRefArea
274 forcecoeff2thrust = 0.5_rfreal*global%refDensity*global%refVelocity &
275 *global%refVelocity*global%forceRefArea
277 DO ipatch = 1,pregion%global%nPatches
278 pthrust(xcoord,ipatch) = forcecoeff2thrust &
279 *(pforcecoeff(xcoord,comp_mom ,ipatch) &
280 + pforcecoeff(xcoord,comp_pres,ipatch) &
281 + pforcecoeff(xcoord,comp_visc,ipatch))
282 pthrust(ycoord,ipatch) = forcecoeff2thrust &
283 *(pforcecoeff(ycoord,comp_mom ,ipatch) &
284 + pforcecoeff(ycoord,comp_pres,ipatch) &
285 + pforcecoeff(ycoord,comp_visc,ipatch))
286 pthrust(zcoord,ipatch) = forcecoeff2thrust &
287 *(pforcecoeff(zcoord,comp_mom ,ipatch) &
288 + pforcecoeff(zcoord,comp_pres,ipatch) &
289 + pforcecoeff(zcoord,comp_visc,ipatch))
291 pthrustvac(xcoord,ipatch) = forcecoeff2thrust &
292 *(pforcecoeffvac(xcoord,comp_mom ,ipatch) &
293 + pforcecoeffvac(xcoord,comp_pres,ipatch) &
294 + pforcecoeffvac(xcoord,comp_visc,ipatch))
295 pthrustvac(ycoord,ipatch) = forcecoeff2thrust &
296 *(pforcecoeffvac(ycoord,comp_mom ,ipatch) &
297 + pforcecoeffvac(ycoord,comp_pres,ipatch) &
298 + pforcecoeffvac(ycoord,comp_visc,ipatch))
299 pthrustvac(zcoord,ipatch) = forcecoeff2thrust &
300 *(pforcecoeffvac(zcoord,comp_mom ,ipatch) &
301 + pforcecoeffvac(zcoord,comp_pres,ipatch) &
302 + pforcecoeffvac(zcoord,comp_visc,ipatch))
309 thrust2isp = 1.0_rfreal/(massin*global%gravity)
311 DO ipatch = 1,pregion%global%nPatches
312 pspecimpulse(xcoord,ipatch) = thrust2isp*pthrust(xcoord,ipatch)
313 pspecimpulse(ycoord,ipatch) = thrust2isp*pthrust(ycoord,ipatch)
314 pspecimpulse(zcoord,ipatch) = thrust2isp*pthrust(zcoord,ipatch)
316 pspecimpulsevac(xcoord,ipatch) = thrust2isp*pthrustvac(xcoord,ipatch)
317 pspecimpulsevac(ycoord,ipatch) = thrust2isp*pthrustvac(ycoord,ipatch)
318 pspecimpulsevac(zcoord,ipatch) = thrust2isp*pthrustvac(zcoord,ipatch)
366 INTEGER,
INTENT(IN) :: ipatch
369 INTEGER,
INTENT(OUT) :: ifile1,ifile2
375 LOGICAL :: fileexists1,fileexists2
376 CHARACTER(CHRLEN) :: ifilename1,ifilename2
384 'RFLU_ModThrustSpecImpulse.F90')
390 IF ( global%verbLevel > verbose_low )
THEN
391 WRITE(stdout,
'(A,1X,A,I4.4)') solver_name,
'Opening thrust and '// &
392 'specific impulse files for iPatch =',ipatch
402 WRITE(ifilename1,
'(A,I4.4)') trim(global%outDir)// &
403 trim(global%casename)//
'.thr_',ipatch
405 WRITE(ifilename2,
'(A,I4.4)') trim(global%outDir)// &
406 trim(global%casename)//
'.isp_',ipatch
412 IF ( global%restartFromScratch .EQV. .false. )
THEN
413 INQUIRE(file=ifilename1,exist=fileexists1)
415 IF ( fileexists1 .EQV. .true. )
THEN
416 OPEN(ifile1,file=ifilename1,
form=
'FORMATTED',
status=
'OLD', &
417 position=
'APPEND',iostat=errorflag)
419 OPEN(ifile1,file=ifilename1,
form=
'FORMATTED',
status=
'NEW', &
423 INQUIRE(file=ifilename2,exist=fileexists2)
425 IF ( fileexists2 .EQV. .true. )
THEN
426 OPEN(ifile2,file=ifilename2,
form=
'FORMATTED',
status=
'OLD', &
427 position=
'APPEND',iostat=errorflag)
429 OPEN(ifile1,file=ifilename2,
form=
'FORMATTED',
status=
'NEW', &
433 IF ( global%thrustWriteCntr == 1 )
THEN
434 OPEN(ifile1,file=ifilename1,
form=
'FORMATTED',
status=
'UNKNOWN', &
436 OPEN(ifile2,file=ifilename2,
form=
'FORMATTED',
status=
'UNKNOWN', &
439 OPEN(ifile1,file=ifilename1,
form=
'FORMATTED',
status=
'OLD', &
440 position=
'APPEND',iostat=errorflag)
441 OPEN(ifile2,file=ifilename2,
form=
'FORMATTED',
status=
'OLD', &
442 position=
'APPEND',iostat=errorflag)
446 global%error = errorflag
448 IF ( global%error /= err_none )
THEN
449 CALL
errorstop(global,err_file_open,__line__,
'File: '// &
450 trim(ifilename1)//
' and '//trim(ifilename2))
457 IF ( global%verbLevel > verbose_low )
THEN
458 WRITE(stdout,
'(A,1X,A)') solver_name,
'Opening thrust and '// &
459 'specific impulse files done.'
505 TYPE(t_region
),
POINTER :: pregion
518 global => pregion%global
521 'RFLU_ModThrustSpecImpulse.F90')
527 IF ( global%myProcid == masterproc .AND. &
528 global%verbLevel > verbose_low )
THEN
529 WRITE(stdout,
'(A,1X,A)') solver_name,
'Printing thrust and '// &
530 'specific impulse...'
532 DO ipatch = 1,pregion%global%nPatches
533 IF ( pregion%thrustFlagsGlobal(ipatch) .EQV. .true. )
THEN
534 WRITE(stdout,
'(A,5X,A,1X,I2)') solver_name,
'Patch:',ipatch
535 WRITE(stdout,
'(A,7X,A,7X,A,6X,A,8X,A,8X,A)') solver_name, &
536 'Component',
'Thrust',
'Thrust vacuum',
'Isp',
'Isp vacuum'
537 WRITE(stdout,
'(A,7X,A,4(1X,E13.6))') solver_name,
'x-direction:', &
538 pregion%thrustGlobal(xcoord,ipatch), &
539 pregion%thrustVacGlobal(xcoord,ipatch), &
540 pregion%specImpulseGlobal(xcoord,ipatch), &
541 pregion%specImpulseVacGlobal(xcoord,ipatch)
542 WRITE(stdout,
'(A,7X,A,4(1X,E13.6))') solver_name,
'y-direction:', &
543 pregion%thrustGlobal(ycoord,ipatch), &
544 pregion%thrustVacGlobal(ycoord,ipatch), &
545 pregion%specImpulseGlobal(ycoord,ipatch), &
546 pregion%specImpulseVacGlobal(ycoord,ipatch)
547 WRITE(stdout,
'(A,7X,A,4(1X,E13.6))') solver_name,
'z-direction:', &
548 pregion%thrustGlobal(zcoord,ipatch), &
549 pregion%thrustVacGlobal(zcoord,ipatch), &
550 pregion%specImpulseGlobal(zcoord,ipatch), &
551 pregion%specImpulseVacGlobal(zcoord,ipatch)
555 WRITE(stdout,
'(A,1X,A)') solver_name,
'Printing thrust and '// &
556 'specific impulse done.'
605 TYPE(t_region
),
POINTER :: pregion
611 LOGICAL :: fileexists1,fileexists2
612 CHARACTER(CHRLEN) :: ifilename1,ifilename2
613 INTEGER :: errorflag,ifile1,ifile2,ipatch
620 global => pregion%global
623 'RFLU_ModThrustSpecImpulse.F90')
629 global%thrustWriteCntr = global%thrustWriteCntr + 1
635 IF ( global%myProcid == masterproc )
THEN
636 IF ( global%verbLevel > verbose_low )
THEN
637 WRITE(stdout,
'(A,1X,A)') solver_name,
'Writing thrust and '// &
638 'specific impulse...'
645 DO ipatch = 1,global%nPatches
646 IF ( pregion%thrustFlagsGlobal(ipatch) .EQV. .true. )
THEN
647 IF ( global%verbLevel > verbose_low )
THEN
648 WRITE(stdout,
'(A,3X,A,1X,I2)') solver_name,
'Patch:',ipatch
661 IF ( global%flowType == flow_steady )
THEN
662 WRITE(ifile1,
'(I6,6(1X,E13.6))') global%currentIter, &
663 pregion%thrustGlobal(xcoord,ipatch), &
664 pregion%thrustVacGlobal(xcoord,ipatch), &
666 pregion%thrustGlobal(ycoord,ipatch), &
667 pregion%thrustVacGlobal(ycoord,ipatch), &
669 pregion%thrustGlobal(zcoord,ipatch), &
670 pregion%thrustVacGlobal(zcoord,ipatch)
672 WRITE(ifile1,
'(1PE12.5,6(1X,E13.6))') global%currentTime, &
673 pregion%thrustGlobal(xcoord,ipatch), &
674 pregion%thrustVacGlobal(xcoord,ipatch), &
676 pregion%thrustGlobal(ycoord,ipatch), &
677 pregion%thrustVacGlobal(ycoord,ipatch), &
679 pregion%thrustGlobal(zcoord,ipatch), &
680 pregion%thrustVacGlobal(zcoord,ipatch)
683 IF ( global%flowType == flow_steady )
THEN
684 WRITE(ifile2,
'(I6,6(1X,E13.6))') global%currentIter, &
685 pregion%specImpulseGlobal(xcoord,ipatch), &
686 pregion%specImpulseVacGlobal(xcoord,ipatch), &
688 pregion%specImpulseGlobal(ycoord,ipatch), &
689 pregion%specImpulseVacGlobal(ycoord,ipatch), &
691 pregion%specImpulseGlobal(zcoord,ipatch), &
692 pregion%specImpulseVacGlobal(zcoord,ipatch)
694 WRITE(ifile2,
'(1PE12.5,6(1X,E13.6))') global%currentTime, &
695 pregion%specImpulseGlobal(xcoord,ipatch), &
696 pregion%specImpulseVacGlobal(xcoord,ipatch), &
698 pregion%specImpulseGlobal(ycoord,ipatch), &
699 pregion%specImpulseVacGlobal(ycoord,ipatch), &
701 pregion%specImpulseGlobal(zcoord,ipatch), &
702 pregion%specImpulseVacGlobal(zcoord,ipatch)
717 IF ( global%verbLevel > verbose_low )
THEN
718 WRITE(stdout,
'(A,1X,A)') solver_name,
'Writing thrust and '// &
719 'specific impulse done.'
subroutine, public rflu_tsi_printglobalvals(pRegion)
subroutine registerfunction(global, funName, fileName)
int status() const
Obtain the status of the attribute.
subroutine, private rflu_tsi_closeglobalvals(global, iPatch, iFile1, iFile2)
subroutine, public rflu_tsi_computeglobalthrustsi(pRegion)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE form
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine, private rflu_tsi_openglobalvals(global, iPatch, iFile1, iFile2)
subroutine deregisterfunction(global)
subroutine, public rflu_tsi_writeglobalvals(pRegion)