LCOV - code coverage report
Current view: top level - io - generic_txtio.f90 (source / functions) Hit Total Coverage
Test: FLEUR test coverage Lines: 0 52 0.0 %
Date: 2024-05-02 04:21:52 Functions: 0 10 0.0 %

          Line data    Source code
       1             : MODULE m_generic_txtio
       2             : 
       3             :    !------------------------------------------------------------------------------
       4             :    !
       5             :    ! MODULE:  m_generic_txtio
       6             :    !
       7             :    !> @author
       8             :    !> Henning Janßen
       9             :    !
      10             :    ! DESCRIPTION:
      11             :    !>  Contains relatively general subroutines for writing txt files with keywords
      12             :    !>  written for hubbard 1 solver
      13             :    !
      14             :    !------------------------------------------------------------------------------
      15             :    USE m_juDFT
      16             : 
      17             :    IMPLICIT NONE
      18             : 
      19             :    PUBLIC :: writeValue,comment,header,startSection,endSection
      20             : 
      21             :    PRIVATE
      22             : 
      23             :    INTERFACE writeValue
      24             :       PROCEDURE writeInt, writeReal, writeRealArray, writeKeyword, writeCharacter, write_tmat
      25             :    END INTERFACE
      26             : 
      27             :    INTERFACE comment
      28             :       PROCEDURE add_comment
      29             :    END INTERFACE
      30             : 
      31             :    INTERFACE header
      32             :       PROCEDURE add_header
      33             :    END INTERFACE
      34             : 
      35             : 
      36             :    !Format specifiers:
      37             :    INTEGER, PARAMETER            :: indent_before_key = 3
      38             :    INTEGER, PARAMETER            :: pos_numbers       = 18
      39             :    INTEGER, PARAMETER            :: float_width       = 10
      40             :    INTEGER, PARAMETER            :: decimal_places    = 5
      41             :    INTEGER, PARAMETER            :: int_width         = 6
      42             : 
      43             : CONTAINS
      44           0 :    SUBROUTINE add_comment(iounit,comment_str,indent)
      45             : 
      46             :       INTEGER,           INTENT(IN)  :: iounit
      47             :       CHARACTER(len=*),  INTENT(IN)  :: comment_str
      48             :       INTEGER, OPTIONAL, INTENT(IN)  :: indent
      49             : 
      50             :       INTEGER ind
      51             :       CHARACTER(len=300) fmt
      52           0 :       ind = 0
      53           0 :       IF(PRESENT(indent)) ind = indent
      54           0 :       WRITE(fmt,'("(A1,TR",I1,",(A))")') ind
      55             : 
      56           0 :       WRITE(iounit,fmt) "#",TRIM(ADJUSTL(comment_str))
      57             : 
      58           0 :    END SUBROUTINE add_comment
      59             : 
      60           0 :    SUBROUTINE add_header(iounit,header_str,indent)
      61             : 
      62             :       INTEGER,           INTENT(IN)  :: iounit
      63             :       CHARACTER(len=*),  INTENT(IN)  :: header_str
      64             :       INTEGER, OPTIONAL, INTENT(IN)  :: indent
      65             : 
      66             :       INTEGER ind
      67           0 :       ind = 0
      68           0 :       IF(PRESENT(indent)) ind = indent
      69             : 
      70           0 :       WRITE(iounit,"(A)") "#**********************************************************"
      71           0 :       CALL add_comment(iounit,header_str,ind)
      72           0 :       WRITE(iounit,"(A)") "#**********************************************************"
      73             : 
      74           0 :    END SUBROUTINE add_header
      75             : 
      76           0 :    SUBROUTINE writeReal(iounit,key,value)
      77             : 
      78             :       IMPLICIT NONE
      79             : 
      80             :       INTEGER,             INTENT(IN)  :: iounit
      81             :       CHARACTER(len=*),    INTENT(IN)  :: key
      82             :       REAL,                INTENT(IN)  :: value
      83             : 
      84             :       INTEGER indent_after_key
      85             :       CHARACTER(len=300) fmt
      86             : 
      87           0 :       indent_after_key = pos_numbers-LEN(key)-indent_before_key
      88             : 
      89           0 :       IF(indent_after_key.LT.1) CALL juDFT_error("indent_after_key<0",calledby="writeReal")
      90             :       !Define Format specifier
      91             :       WRITE(fmt,'("(TR",I2.2,",A",I2.2,",TR",I2.2,",f",I2.2,".",I2.2,")")') &
      92           0 :             indent_before_key,LEN(key),indent_after_key,float_width,decimal_places
      93             : 
      94           0 :       WRITE(iounit,fmt) TRIM(ADJUSTL(key)), value
      95             : 
      96           0 :    END SUBROUTINE writeReal
      97             : 
      98           0 :    SUBROUTINE writeRealArray(iounit,key,value)
      99             : 
     100             :       IMPLICIT NONE
     101             : 
     102             :       INTEGER,             INTENT(IN)  :: iounit
     103             :       CHARACTER(len=*),    INTENT(IN)  :: key
     104             :       REAL,                INTENT(IN)  :: value(:)
     105             : 
     106             :       INTEGER indent_after_key
     107             :       CHARACTER(len=300) fmt
     108           0 :       indent_after_key = pos_numbers-LEN(key)-indent_before_key
     109             : 
     110           0 :       IF(indent_after_key.LT.1) CALL juDFT_error("indent_after_key<0",calledby="writeRealArray")
     111             :       !Define Format specifier
     112             :       WRITE(fmt,'("(TR",I2.2,",A",I2.2,",TR",I2.2,",",I2.2,"f",I2.2,".",I2.2,")")') &
     113           0 :             indent_before_key,LEN(key),indent_after_key,SIZE(value,1),float_width,decimal_places
     114             : 
     115           0 :       WRITE(iounit,fmt) TRIM(ADJUSTL(key)), value
     116             : 
     117           0 :    END SUBROUTINE writeRealArray
     118             : 
     119           0 :    SUBROUTINE writeInt(iounit,key,value)
     120             : 
     121             :       IMPLICIT NONE
     122             : 
     123             :       INTEGER,             INTENT(IN)  :: iounit
     124             :       CHARACTER(len=*),    INTENT(IN)  :: key
     125             :       INTEGEr,             INTENT(IN)  :: value
     126             : 
     127             :       INTEGER indent_after_key
     128             :       CHARACTER(len=300) fmt
     129             : 
     130           0 :       indent_after_key = pos_numbers-LEN(key)-indent_before_key
     131             : 
     132           0 :       IF(indent_after_key.LT.1) CALL juDFT_error("indent_after_key<0",calledby="writeInt")
     133             :       !Define Format specifier
     134             :       WRITE(fmt,'("(TR",I2.2,",A",I2.2,",TR",I2.2,",I",I2.2,")")') &
     135           0 :             indent_before_key,LEN(key),indent_after_key,int_width
     136             : 
     137           0 :       WRITE(iounit,fmt) TRIM(ADJUSTL(key)), value
     138             : 
     139           0 :    END SUBROUTINE writeInt
     140             : 
     141           0 :    SUBROUTINE writeKeyword(iounit,key)
     142             : 
     143             :       IMPLICIT NONE
     144             : 
     145             :       INTEGER,          INTENT(IN)  :: iounit
     146             :       CHARACTER(len=*), INTENT(IN)  :: key
     147             : 
     148             :       CHARACTER(len=300) fmt
     149             : 
     150           0 :       WRITE(fmt,'("(TR",I2.2,",A",I2.2,")")') indent_before_key,LEN(key)
     151             : 
     152           0 :       WRITE(iounit,fmt) key
     153             : 
     154           0 :    END SUBROUTINE writeKeyword
     155             : 
     156           0 :    SUBROUTINE writeCharacter(iounit,key,value)
     157             : 
     158             :       IMPLICIT NONE
     159             : 
     160             :       INTEGER,          INTENT(IN)  :: iounit
     161             :       CHARACTER(len=*), INTENT(IN)  :: key
     162             :       CHARACTER(len=*), INTENT(IN)  :: value
     163             : 
     164             :       CHARACTER(len=300) fmt
     165             :       INTEGER indent_after_key
     166             : 
     167           0 :       indent_after_key = pos_numbers-LEN(key)-indent_before_key + 5
     168             : 
     169             :       WRITE(fmt,'("(TR",I2.2,",A",I2.2,",TR",I2.2,",A",I2.2,")")') &
     170           0 :             indent_before_key,LEN(value),indent_after_key,LEN(value)
     171             : 
     172           0 :       WRITE(iounit,fmt) TRIM(ADJUSTL(key)),TRIM(ADJUSTL(value))
     173           0 :    END SUBROUTINE writeCharacter
     174             : 
     175           0 :    SUBROUTINE write_tmat(iounit,mat)
     176             : 
     177             :       USE m_types
     178             :       IMPLICIT NONE
     179             : 
     180             :       INTEGER,          INTENT(IN)  :: iounit
     181             :       TYPE(t_mat),      INTENT(IN)  :: mat
     182             : 
     183             :       INTEGER i
     184             :       CHARACTER(len=300) fmt
     185             :       !Define Format specifier
     186             :       WRITE(fmt,'("(TR",I2.2,",",I2.2,"f",I2.2,".",I2.2,")")') &
     187           0 :             indent_before_key,mat%matsize2,float_width,decimal_places
     188             : 
     189           0 :       DO i = 1, mat%matsize1
     190           0 :          WRITE(iounit,fmt) mat%data_r(i,:)
     191             :       ENDDO
     192             : 
     193             : 
     194           0 :    END SUBROUTINE write_tmat
     195             : 
     196           0 :    SUBROUTINE startSection(iounit,sectionname)
     197             : 
     198             :       IMPLICIT NONE
     199             : 
     200             :       INTEGER,             INTENT(IN)  :: iounit
     201             :       CHARACTER(len=*),    INTENT(IN)  :: sectionname
     202             : 
     203             :       CHARACTER(len=300) fmt
     204             : 
     205           0 :       WRITE(fmt,'("(A",I2.2,",TR1,A1)")') LEN(sectionname)
     206           0 :       WRITE(iounit,fmt) sectionname , "{"
     207             : 
     208           0 :    END SUBROUTINE startSection
     209             : 
     210           0 :    SUBROUTINE endSection(iounit)
     211             : 
     212             :       IMPLICIT NONE
     213             : 
     214             :       INTEGER,             INTENT(IN)  :: iounit
     215             : 
     216           0 :       WRITE(iounit,"(A1)") "}"
     217             : 
     218           0 :    END SUBROUTINE endSection
     219             : 
     220             : 
     221             : END MODULE m_generic_txtio

Generated by: LCOV version 1.14