dbcsr_logger_create Subroutine

public subroutine dbcsr_logger_create(logger, mp_env, print_level, default_global_unit_nr, default_local_unit_nr, global_filename, local_filename, close_global_unit_on_dealloc, iter_info, close_local_unit_on_dealloc, suffix, template_logger)

initializes a logger

Note

the handling of filename, defaultunit_nr, close*_unit_on_dealloc tries to take the right decision with different inputs, and thus is a little complex.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_logger_type), POINTER :: logger

the logger to initialize

type(dbcsr_mp_obj), optional :: mp_env

the parallel environment (this is most likely the global parallel environment

integer, intent(in), optional :: print_level

the level starting with which something is written (defaults to dbcsr_note_level) the default unit_nr for output (if not given, and no file is given defaults to the standard output) the default unit number for local (i.e. task) output. If not given defaults to a out.taskid file created upon

integer, intent(in), optional :: default_global_unit_nr

the level starting with which something is written (defaults to dbcsr_note_level) the default unit_nr for output (if not given, and no file is given defaults to the standard output) the default unit number for local (i.e. task) output. If not given defaults to a out.taskid file created upon

integer, intent(in), optional :: default_local_unit_nr

the level starting with which something is written (defaults to dbcsr_note_level) the default unit_nr for output (if not given, and no file is given defaults to the standard output) the default unit number for local (i.e. task) output. If not given defaults to a out.taskid file created upon

character(len=*), intent(in), optional :: global_filename

a new file to open (can be given instead of the global_unit_nr) a new file to open (with suffix and mp_env%mp%mynode appended). Can be given instead of the default_local_unit_nr). the file is created only upon the first local logging request

character(len=*), intent(in), optional :: local_filename

a new file to open (can be given instead of the global_unit_nr) a new file to open (with suffix and mp_env%mp%mynode appended). Can be given instead of the default_local_unit_nr). the file is created only upon the first local logging request

logical, intent(in), optional :: close_global_unit_on_dealloc

if the unit should be closed when the logger is deallocated (defaults to true if a local_filename is given, to false otherwise)

type(dbcsr_iteration_info_type), optional, POINTER :: iter_info
logical, intent(in), optional :: close_local_unit_on_dealloc

if the unit should be closed when the logger is deallocated (defaults to true)

character(len=*), intent(in), optional :: suffix

the suffix that should be added to all the generated filenames

type(dbcsr_logger_type), optional, POINTER :: template_logger

a logger from where to take the unspecified things


Source Code

   SUBROUTINE dbcsr_logger_create(logger, mp_env, print_level, &
                                  default_global_unit_nr, default_local_unit_nr, global_filename, &
                                  local_filename, close_global_unit_on_dealloc, iter_info, &
                                  close_local_unit_on_dealloc, suffix, template_logger)
      !! initializes a logger
      !! @note
      !! the handling of *_filename, default_*_unit_nr, close_*_unit_on_dealloc
      !! tries to take the right decision with different inputs, and thus is a
      !! little complex.

      TYPE(dbcsr_logger_type), POINTER                   :: logger
         !! the logger to initialize
      TYPE(dbcsr_mp_obj), OPTIONAL                       :: mp_env
         !! the parallel environment (this is most likely the global parallel environment
      INTEGER, INTENT(in), OPTIONAL                      :: print_level, default_global_unit_nr, &
                                                            default_local_unit_nr
         !! the level starting with which something is written (defaults to dbcsr_note_level)
         !! the default unit_nr for output (if not given, and no file is given defaults to the standard output)
         !! the default unit number for local (i.e. task) output. If not given defaults to a out.taskid file created upon
      CHARACTER(len=*), INTENT(in), OPTIONAL             :: global_filename, local_filename
         !! a new file to open (can be given instead of the global_unit_nr)
         !! a new file to open (with suffix and mp_env%mp%mynode appended). Can be given instead of the default_local_unit_nr). the
         !! file is created only upon the first local logging request
      LOGICAL, INTENT(in), OPTIONAL                      :: close_global_unit_on_dealloc
         !! if the unit should be closed when the logger is deallocated (defaults to true if a local_filename is given, to false
         !! otherwise)
      TYPE(dbcsr_iteration_info_type), OPTIONAL, POINTER :: iter_info
      LOGICAL, INTENT(in), OPTIONAL                      :: close_local_unit_on_dealloc
         !! if the unit should be closed when the logger is deallocated (defaults to true)
      CHARACTER(len=*), INTENT(in), OPTIONAL             :: suffix
         !! the suffix that should be added to all the generated filenames
      TYPE(dbcsr_logger_type), OPTIONAL, POINTER         :: template_logger
         !! a logger from where to take the unspecified things

      CHARACTER(len=*), PARAMETER :: routineN = 'dbcsr_logger_create', &
                                     routineP = moduleN//':'//routineN

      INTEGER                                            :: stat

      ALLOCATE (logger, stat=stat)
      IF (stat /= 0) &
         DBCSR_ABORT(routineP//" could not ALLOCATE a logger")

      NULLIFY (logger%iter_info)
      logger%ref_count = 1
      last_logger_id_nr = last_logger_id_nr + 1
      logger%id_nr = last_logger_id_nr

      IF (PRESENT(template_logger)) THEN
         IF (template_logger%ref_count < 1) &
            DBCSR_ABORT(routineP//" template_logger%ref_count<1")
         logger%print_level = template_logger%print_level
         logger%default_global_unit_nr = template_logger%default_global_unit_nr
         logger%close_local_unit_on_dealloc = template_logger%close_local_unit_on_dealloc
         IF (logger%close_local_unit_on_dealloc) THEN
            logger%default_local_unit_nr = -1
         ELSE
            logger%default_local_unit_nr = template_logger%default_local_unit_nr
         END IF
         logger%close_global_unit_on_dealloc = template_logger%close_global_unit_on_dealloc
         IF (logger%close_global_unit_on_dealloc) THEN
            logger%default_global_unit_nr = -1
         ELSE
            logger%default_global_unit_nr = template_logger%default_global_unit_nr
         END IF
         logger%local_filename = template_logger%local_filename
         logger%global_filename = template_logger%global_filename
         logger%mp_env = template_logger%mp_env
         logger%suffix = template_logger%suffix
         logger%iter_info => template_logger%iter_info
      ELSE
         ! create a file if nothing is specified, one can also get the unit from the default logger
         ! which should have something reasonable as the argument is required in that case
         logger%default_global_unit_nr = -1
         logger%close_global_unit_on_dealloc = .TRUE.
         logger%local_filename = "localLog"
         logger%global_filename = "mainLog"
         logger%print_level = dbcsr_note_level
         ! generate a file for default local logger
         ! except the ionode that should write to the default global logger
         logger%default_local_unit_nr = -1
         logger%close_local_unit_on_dealloc = .TRUE.
         logger%suffix = ""
      END IF
      IF (PRESENT(mp_env)) logger%mp_env = mp_env
      IF (.NOT. ASSOCIATED(logger%mp_env%mp)) &
         DBCSR_ABORT(routineP//" mp env not associated")

      IF (logger%mp_env%mp%refcount < 1) &
         DBCSR_ABORT(routineP//" mp_env%ref_count<1")
      logger%mp_env%mp%refcount = logger%mp_env%mp%refcount + 1

      IF (PRESENT(print_level)) logger%print_level = print_level

      IF (PRESENT(default_global_unit_nr)) &
         logger%default_global_unit_nr = default_global_unit_nr
      IF (PRESENT(global_filename)) THEN
         logger%global_filename = global_filename
         logger%close_global_unit_on_dealloc = .TRUE.
         logger%default_global_unit_nr = -1
      END IF
      IF (PRESENT(close_global_unit_on_dealloc)) THEN
         logger%close_global_unit_on_dealloc = close_global_unit_on_dealloc
         IF (PRESENT(default_global_unit_nr) .AND. PRESENT(global_filename) .AND. &
             (.NOT. close_global_unit_on_dealloc)) THEN
            logger%default_global_unit_nr = default_global_unit_nr
         END IF
      END IF

      IF (PRESENT(default_local_unit_nr)) &
         logger%default_local_unit_nr = default_local_unit_nr
      IF (PRESENT(local_filename)) THEN
         logger%local_filename = local_filename
         logger%close_local_unit_on_dealloc = .TRUE.
         logger%default_local_unit_nr = -1
      END IF
      IF (PRESENT(suffix)) logger%suffix = suffix

      IF (PRESENT(close_local_unit_on_dealloc)) THEN
         logger%close_local_unit_on_dealloc = close_local_unit_on_dealloc
         IF (PRESENT(default_local_unit_nr) .AND. PRESENT(local_filename) .AND. &
             (.NOT. close_local_unit_on_dealloc)) THEN
            logger%default_local_unit_nr = default_local_unit_nr
         END IF
      END IF

      IF (logger%default_local_unit_nr == -1) THEN
         IF (logger%mp_env%mp%mynode == logger%mp_env%mp%source) THEN
            logger%default_local_unit_nr = logger%default_global_unit_nr
            logger%close_local_unit_on_dealloc = .FALSE.
         END IF
      END IF
      IF (PRESENT(iter_info)) logger%iter_info => iter_info
      IF (ASSOCIATED(logger%iter_info)) THEN
         CALL dbcsr_iteration_info_retain(logger%iter_info)
      ELSE
         CALL dbcsr_iteration_info_create(logger%iter_info, "")
      END IF
   END SUBROUTINE dbcsr_logger_create