Skip to content
Permalink
master
Switch branches/tags

Name already in use

A tag already exists with the provided branch name. Many Git commands accept both tag and branch names, so creating this branch may cause unexpected behavior. Are you sure you want to create this branch?
Go to file
 
 
Cannot retrieve contributors at this time
!vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
! !
! Module name: URS0_DES !
! !
! Purpose: This routine is called before the discrete phase time loop !
! and is user-definable. The user may insert code in this routine or !
! call appropriate user defined subroutines. !
! !
! This routine is not called from a loop, hence all indicies are !
! undefined. !
! !
! Author: J.Musser Date: 06-Nov-12 !
! !
! Comments: !
! !
!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
SUBROUTINE USR0_DES
Use des_rxns
Use des_thermo
Use discretelement
Use run
Use usr
Use functions, only : is_nonexistent, is_ghost, is_entering_ghost, is_exiting_ghost
Use constant, only: pi
Use fldvar
Use particle_filter, only: DES_INTERP_ON, DES_INTERP_MEAN_FIELDS
IMPLICIT NONE
INTEGER :: LL, L, ios
DOUBLE PRECISION :: a
open(UNIT=79, FILE='part_diameter.txt', STATUS='old', &
ACTION='read') ! Read particle diameters from file
!write(*,*) "Particle volume before updating radius"
!write(*,*) "NP: ", 2*DES_RADIUS(100)
!write(*,*) "PVOL(100): ", PVOL(100)
!write(*,*) "DES_INTERP: ",DES_INTERP_ON
!write(*,*) "DES_INTERP_MEAN_FIELDS: ", DES_INTERP_MEAN_FIELDS
!write(*,*) "EP_S(134,1): ", EP_S(134,1)
!read(*,*)
!write(*,*) "Particle 38 position: ", DES_POS_NEW(38,:3)
DO LL=1, MAX_PIP
IF(IS_NONEXISTENT(LL)) CYCLE
read(79, *,IOSTAT=ios) a
IF(ios<0) THEN ! Check end-of-file
EXIT
ELSE
DES_RADIUS(LL) = 0.5*a ! Assign particle sizes to DES_RADIUS()
ENDIF
ENDDO
DO L = 1, MAX_PIP
! Skip 'empty' locations when populating the particle property arrays.
IF(IS_NONEXISTENT(L)) CYCLE
IF(IS_GHOST(L) .OR. IS_ENTERING_GHOST(L) .OR. IS_EXITING_GHOST(L)) CYCLE
PVOL(L) = (4.0D0/3.0D0)*PI*DES_RADIUS(L)**3
PMASS(L) = PVOL(L)*RO_SOL(L)
OMOI(L) = 2.5D0/(PMASS(L)*DES_RADIUS(L)**2) !ONE OVER MOI
ENDDO
close(79) ! Close file after reading
! Re-compute solids, gas volume fraction
!write(*,*) "Calling comp_mean_fields from usr0_des.f ..."
!CALL CALC_EPG_DES
RETURN
END SUBROUTINE USR0_DES