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) | :: | reportName | |||
character(len=*), | intent(in) | :: | objectName | |||
integer, | intent(in) | :: | averageOrSum |
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 WriteReportHeaders(reportName,objectName,averageOrSum)
! SUBROUTINE INFORMATION:
! AUTHOR Jason Glazer
! DATE WRITTEN August 2003
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Write the first few lines of each report with headers to the output
! file for tabular reports.
USE DataStringGlobals, ONLY : VerString
USE DataHeatBalance, ONLY : BuildingName
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
CHARACTER(len=*),INTENT(IN) :: reportName
CHARACTER(len=*),INTENT(IN) :: objectName
INTEGER, INTENT(IN) :: averageOrSum
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: fmta="(A)"
CHARACTER(len=*), PARAMETER :: TimeStampFmt1="(A,I4,A,I2.2,A,I2.2)"
CHARACTER(len=*), PARAMETER :: TimeStampFmt2="(A,I4.2,A,I2.2,A,I2.2,A)"
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
CHARACTER(len=MaxNameLength * 2) :: modifiedReportName
INTEGER :: iStyle
INTEGER :: curFH
CHARACTER(len=1) :: curDel
IF (averageOrSum .EQ. isSum) THEN ! if it is a summed variable CR5959
modifiedReportName = TRIM(reportName) // ' per second'
ELSE
modifiedReportName = reportName
ENDIF
DO iStyle = 1, numStyles
curFH = TabularOutputFile(iStyle)
curDel = del(iStyle)
SELECT CASE (TableStyle(iStyle))
CASE (tableStyleComma,tableStyleTab)
WRITE(curFH,fmta) '--------------------------------------------------' // &
'--------------------------------------------------'
WRITE(curFH,fmta) 'REPORT:' // curDel //TRIM(modifiedReportName)
WRITE(curFH,fmta) 'FOR:' // curDel //TRIM(objectName)
CASE (tableStyleFixed)
WRITE(curFH,fmta) '--------------------------------------------------' // &
'--------------------------------------------------'
WRITE(curFH,fmta) 'REPORT: '// curDel //TRIM(modifiedReportName)
WRITE(curFH,fmta) 'FOR: '// curDel //TRIM(objectName)
CASE (tableStyleHTML)
WRITE(curFH,fmta) '<hr>'
WRITE(curFH,fmta) '<p><a href="#toc" style="float: right">Table of Contents</a></p>'
WRITE(curFH,fmta) '<a name=' // TRIM(MakeAnchorName(reportName,objectName)) // '></a>'
WRITE(curFH,fmta) '<p>Report:<b>' // curDel //TRIM(modifiedReportName) //'</b></p>'
WRITE(curFH,fmta) '<p>For:<b>' // curDel //TRIM(objectName) //'</b></p>'
WRITE(curFH,TimeStampFmt1) "<p>Timestamp: <b>", td(1),'-', td(2),'-',td(3)
WRITE(curFH,TimeStampFmt2) ' ',td(5),':', td(6),':',td(7),'</b></p>'
CASE (tableStyleXML)
IF (LEN_TRIM(prevReportName) .NE. 0) THEN
WRITE(curFH,fmta) '</' // TRIM(prevReportName) //'>' !close the last element if it was used.
END IF
WRITE(curFH,fmta) '<' // TRIM(ConvertToElementTag(modifiedReportName)) //'>'
WRITE(curFH,fmta) ' <for>' //TRIM(objectName) //'</for>'
prevReportName = ConvertToElementTag(modifiedReportName) !save the name for next time
END SELECT
END DO
!clear the active subtable name for the XML reporting
activeSubTableName = ''
!save the report name if the subtable name is not available during XML processing
activeReportName = modifiedReportName
!save the "for" which is the object name in the report for HTML comment that contains the report, for, and subtable
activeForName = objectName
END SUBROUTINE WriteReportHeaders