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), | DIMENSION(:,:) | :: | body | ||
character(len=*), | intent(in), | DIMENSION(:) | :: | rowLabels | ||
character(len=*), | intent(in), | DIMENSION(:) | :: | columnLabels | ||
character(len=*), | intent(in) | :: | ReportName | |||
character(len=*), | intent(in) | :: | ReportForString | |||
character(len=*), | intent(in) | :: | TableName |
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 CreateSQLiteTabularDataRecords(body,rowLabels,columnLabels,ReportName,ReportForString,TableName)
! SUBROUTINE INFORMATION:
! AUTHOR Kyle Benne
! DATE WRITTEN January 2010
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine wites records to the TabularData table in the SQL database
! METHODOLOGY EMPLOYED:
! Standard SQL92 queries and commands via the Fortran SQLite3 API
! REFERENCES:
! na
! USE STATEMENTS:
USE ISO_C_FUNCTION_BINDING
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
CHARACTER(len=*),INTENT(IN),DIMENSION(:,:) :: body ! row,column
CHARACTER(len=*),INTENT(IN),DIMENSION(:) :: rowLabels
CHARACTER(len=*),INTENT(IN),DIMENSION(:) :: columnLabels
CHARACTER(len=*),INTENT(IN) :: ReportName
CHARACTER(len=*),INTENT(IN) :: ReportForString
CHARACTER(len=*),INTENT(IN) :: TableName
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: result
INTEGER :: iCol,sizeColumnLabels
INTEGER :: iRow,sizeRowLabels
INTEGER :: ReportNameIndex,TableNameIndex,ReportForStringIndex
INTEGER :: RowLabelIndex,ColumnLabelIndex
INTEGER :: UnitsIndex
CHARACTER(100) :: rowLabel,columnLabel,units,rowUnits
INTEGER :: rowLeftBracket,rowUnitStart,rowLabelEnd,rowRightBracket,rowUnitEnd
INTEGER :: colLeftBracket,colUnitStart,colLabelEnd,colRightBracket,colUnitEnd
IF (WriteTabularDataToSQLite) then
sizeColumnLabels = SIZE(columnLabels)
sizeRowLabels = SIZE(rowLabels)
DO iRow = 1, sizeRowLabels
rowLabel = rowLabels(iRow)
! Look in the rowLabel for units
rowLeftBracket = SCAN(rowLabel,'[')
rowUnitStart = rowLeftBracket + 1
rowLabelEnd = rowUnitStart - 2
rowRightBracket = SCAN(rowLabel,']',BACK = .TRUE.)
rowUnitEnd = rowRightBracket - 1
IF ((rowLeftBracket .NE. 0) .AND. (rowRightBracket .NE. 0)) THEN
rowUnits = rowLabel(rowUnitStart:rowUnitEnd)
rowLabel = TRIM(rowLabel(1:rowLabelEnd))
ELSE
rowUnits = ''
END IF
DO iCol = 1, sizeColumnLabels
columnLabel = columnLabels(iCol)
! Look in the colLabel for units
! This will override units from row
colLeftBracket = SCAN(columnLabel,'[')
colUnitStart = colLeftBracket + 1
colLabelEnd = colUnitStart - 2
colRightBracket = SCAN(columnLabel,']',BACK = .TRUE.)
colUnitEnd = colRightBracket - 1
IF ((colLeftBracket .NE. 0) .AND. (colRightBracket .NE. 0)) THEN
units = columnLabel(colUnitStart:colUnitEnd)
columnLabel = TRIM(columnLabel(1:colLabelEnd))
ELSE
units = rowUnits
END IF
ReportNameIndex = CreateSQLiteStringTableRecord(ReportName,ReportNameId)
ReportForStringIndex = CreateSQLiteStringTableRecord(ReportForString,ReportForStringId)
TableNameIndex = CreateSQLiteStringTableRecord(TableName,TableNameId)
RowLabelIndex = CreateSQLiteStringTableRecord(rowLabel,RowNameId)
ColumnLabelIndex = CreateSQLiteStringTableRecord(columnLabel,ColumnNameId)
UnitsIndex = CreateSQLiteStringTableRecord(units,UnitsId)
result = SQLiteBindInteger(TabularDataInsertStmt,1,ReportNameIndex)
result = SQLiteBindInteger(TabularDataInsertStmt,2,ReportForStringIndex)
result = SQLiteBindInteger(TabularDataInsertStmt,3,TableNameIndex)
result = SQLiteBindInteger(TabularDataInsertStmt,4,1)
result = SQLiteBindInteger(TabularDataInsertStmt,5,RowLabelIndex)
result = SQLiteBindInteger(TabularDataInsertStmt,6,ColumnLabelIndex)
result = SQLiteBindInteger(TabularDataInsertStmt,7,iRow)
result = SQLiteBindInteger(TabularDataInsertStmt,8,iCol)
result = SQLiteBindTextMacro(TabularDataInsertStmt,9,body(iRow,iCol))
result = SQLiteBindInteger(TabularDataInsertStmt,10,UnitsIndex)
result = SQLiteStepCommand(TabularDataInsertStmt)
result = SQLiteResetCommand(TabularDataInsertStmt)
result = SQLiteClearBindings(TabularDataInsertStmt)
END DO
END DO
END IF
END SUBROUTINE CreateSQLiteTabularDataRecords