Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | option |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE LinesOut(option)
! SUBROUTINE INFORMATION:
! AUTHOR Linda K. Lawrie
! DATE WRITTEN March 1999
! MODIFIED March 2006 -- add option for "IDF segments out"
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine produces a file of lines in the surfaces.
! METHODOLOGY EMPLOYED:
! Use the surface absolute coordinate information to produce
! lines.
! REFERENCES:
! na
! USE STATEMENTS:
USE DataPrecisionGlobals
USE DataHeatBalance
USE DataSurfaces
USE DataInterfaces, ONLY: ShowWarningError, ShowContinueError, ShowFatalError
USE General, ONLY: RoundSigDigits
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
character(len=*), intent(IN) :: option
! SUBROUTINE PARAMETER DEFINITIONS:
character(len=*), parameter :: fmt700="(5(f10.2,','),f10.2)"
character(len=*), parameter :: fmta="(A)"
character(len=*), parameter :: fmtcoord="(2X,2(f10.2,','),f10.2,A,A)"
character(len=*), parameter :: vertexstring='X,Y,Z ==> Vertex'
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
logical, save :: optiondone=.false.
character(len=MaxNameLength), SAVE :: lastoption=' '
integer unit ! Unit number on which to write file
integer surf ! Loop variable for surfaces
integer vert ! Loop counter
integer,external :: getnewunitnumber ! External function for a new unit number
character(len=1) :: optcommasemi
integer :: write_stat
if (totsurfaces > 0 .and. .not. allocated(surface)) then
! no error needed, probably in end processing, just return
return
endif
if (optiondone) then
CALL ShowWarningError('Report of Surfaces/Lines Option has already been completed with option='//trim(lastoption))
CALL ShowContinueError('..option="'//trim(Option)//'" will not be done this time.')
return
endif
lastoption=option
optiondone=.true.
unit=getnewunitnumber()
open(unit,file='eplusout.sln', Action='write', iostat=write_stat)
if (write_stat /= 0) then
CALL ShowFatalError('LinesOut: Could not open file "eplusout.sln" for output (write).')
endif
if (option /= 'IDF') then
do surf=1,totsurfaces
if (surface(surf)%class .eq. SurfaceClass_IntMass) CYCLE
if (surface(surf)%sides == 0) CYCLE
write(unit,fmta) trim(surface(surf)%ZoneName)//':'//trim(surface(surf)%Name)
do vert=1,Surface(Surf)%Sides
if (vert /= Surface(Surf)%Sides) then
write(unit,fmt700) surface(surf)%vertex(vert)%x,surface(surf)%vertex(vert)%y,surface(surf)%vertex(vert)%z, &
surface(surf)%vertex(vert+1)%x,surface(surf)%vertex(vert+1)%y,surface(surf)%vertex(vert+1)%z
else
write(unit,fmt700) surface(surf)%vertex(vert)%x,surface(surf)%vertex(vert)%y,surface(surf)%vertex(vert)%z, &
surface(surf)%vertex(1)%x,surface(surf)%vertex(1)%y,surface(surf)%vertex(1)%z
endif
enddo
enddo
else
write(unit,fmta) ' Building North Axis = 0'
write(unit,fmta) 'GlobalGeometryRules,UpperLeftCorner,CounterClockwise,WorldCoordinates;'
do surf=1,totsurfaces
if (surface(surf)%class .eq. SurfaceClass_IntMass) CYCLE
if (surface(surf)%sides == 0) CYCLE
! process heat transfer surfaces
write(unit,fmta) ' Surface='//trim(cSurfaceClass(surface(surf)%class))//', Name='//trim(surface(surf)%Name)// &
', Azimuth='//trim(roundsigdigits(surface(surf)%Azimuth,1))
write(unit,fmta) ' '//trim(roundsigdigits(surface(surf)%Sides))//', !- Number of (X,Y,Z) groups in this surface'
do vert=1,Surface(Surf)%Sides
optcommasemi=','
if (vert == Surface(Surf)%Sides) optcommasemi=';'
write(unit,fmtcoord) surface(surf)%vertex(vert)%x,surface(surf)%vertex(vert)%y,surface(surf)%vertex(vert)%z, &
optcommasemi,' !- '//trim(vertexstring)//' '//trim(roundsigdigits(vert))
enddo
enddo
endif
close(unit)
return
END SUBROUTINE LinesOut