Skip to content

Commit

Permalink
FDS Source: Add SLCF IOR to smv file for Smokeview Issue 1962.
Browse files Browse the repository at this point in the history
  • Loading branch information
drjfloyd committed Aug 4, 2024
1 parent 4480381 commit 0339992
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 7 deletions.
8 changes: 4 additions & 4 deletions Source/dump.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1160,11 +1160,11 @@ SUBROUTINE INITIALIZE_MESH_DUMPS(NM)
CC_VAL = 0
ENDIF
IF (SL%ID/='null') THEN
WRITE(SLICELABEL,'(A,A,A,A,A,A,I6,1X,I6,1X)') ' # ',TRIM(SL%SLICETYPE),' %',TRIM(SL%ID),TRIM(SLICEPARMS),&
' ! ',SL%SLCF_INDEX, CC_VAL
WRITE(SLICELABEL,'(A,A,A,A,A,A,I6,1X,I6,1X,I6,1X)') ' # ',TRIM(SL%SLICETYPE),' %',TRIM(SL%ID),TRIM(SLICEPARMS),&
' ! ',SL%SLCF_INDEX, CC_VAL, SL%IOR
ELSE
WRITE(SLICELABEL,'(A,A,A,A,I6,1X,I6,1X)') ' # ',TRIM(SL%SLICETYPE),TRIM(SLICEPARMS),&
' ! ',SL%SLCF_INDEX, CC_VAL
WRITE(SLICELABEL,'(A,A,A,A,I6,1X,I6,1X,I6,1X)') ' # ',TRIM(SL%SLICETYPE),TRIM(SLICEPARMS),&
' ! ',SL%SLCF_INDEX, CC_VAL, SL%IOR
ENDIF
IF (SL%SLICETYPE=='STRUCTURED') THEN
IF (SL%CELL_CENTERED) THEN
Expand Down
10 changes: 8 additions & 2 deletions Source/read.f90
Original file line number Diff line number Diff line change
Expand Up @@ -15006,7 +15006,7 @@ SUBROUTINE READ_SLCF

REAL(EB) :: MAXIMUM_VALUE,MINIMUM_VALUE
REAL(EB) :: AGL_SLICE
INTEGER :: N,NN,NM,MESH_NUMBER,N_SLCF_O,NITER,ITER,VELO_INDEX,GEOM_INDEX
INTEGER :: N,NN,NM,MESH_NUMBER,N_SLCF_O,NITER,ITER,VELO_INDEX,GEOM_INDEX,IOR
LOGICAL :: VECTOR,CELL_CENTERED,DEBUG
CHARACTER(LABEL_LENGTH) :: QUANTITY,SPEC_ID,PART_ID,QUANTITY2,PROP_ID,REAC_ID,SLICETYPE
REAL(EB), PARAMETER :: TOL=1.E-10_EB
Expand Down Expand Up @@ -15128,6 +15128,11 @@ SUBROUTINE READ_SLCF
END SELECT
ENDIF

IOR = 0
IF (ABS(XB(1)-XB(2))<TWO_EPSILON_EB) IOR = 1
IF (ABS(XB(3)-XB(4))<TWO_EPSILON_EB) IOR = 2
IF (ABS(XB(5)-XB(6))<TWO_EPSILON_EB) IOR = 3

CALL CHECK_XB(XB)

XB(1) = MAX(XB(1),XS)
Expand All @@ -15139,7 +15144,7 @@ SUBROUTINE READ_SLCF

! Reject a slice if it is beyond the bounds of the current mesh

IF (XB(1)>XF .OR. XB(2)<XS .OR. XB(3)>YF .OR. XB(4)<YS .OR. XB(5)>ZF .OR. XB(6)<ZS) THEN
IF (XB(1)>=XF .OR. XB(2)<=XS .OR. XB(3)>=YF .OR. XB(4)<=YS .OR. XB(5)>=ZF .OR. XB(6)<=ZS) THEN
N_SLCF = N_SLCF - 1
IF (VECTOR .AND. TWO_D) N_SLCF = N_SLCF - 2
IF (VECTOR .AND. .NOT. TWO_D) N_SLCF = N_SLCF - 3
Expand All @@ -15157,6 +15162,7 @@ SUBROUTINE READ_SLCF
SL=>SLICE(N)
SL%SLCF_INDEX=NN
SL%ID = ID
SL%IOR = IOR
SL%SLICETYPE = TRIM(SLICETYPE)
SL%GEOM_INDEX = GEOM_INDEX
IF (CELL_CENTERED) THEN
Expand Down
2 changes: 1 addition & 1 deletion Source/type.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1512,7 +1512,7 @@ MODULE TYPES

TYPE SLICE_TYPE
INTEGER :: I1,I2,J1,J2,K1,K2,GEOM_INDEX=-1,INDEX,INDEX2=0,Z_INDEX=-999,Y_INDEX=-999,MATL_INDEX=-999,&
PART_INDEX=0,VELO_INDEX=0,PROP_INDEX=0,REAC_INDEX=0,SLCF_INDEX
PART_INDEX=0,VELO_INDEX=0,PROP_INDEX=0,REAC_INDEX=0,SLCF_INDEX,IOR
REAL(FB), DIMENSION(2) :: MINMAX
REAL(FB) :: RLE_MIN, RLE_MAX
REAL(EB):: AGL_SLICE
Expand Down

0 comments on commit 0339992

Please sign in to comment.