Best way to pass optional string argument?

I have a legacy application with a commonly used trace function that I modified to take an optional argument, which temporarily replaces a trace message in the structure. The trace message in the structure has a fixed size. Here’s a simplified version:

type :: my_structure
  character(128) :: trace_message
  logical        :: trace_enabled
end type

subroutine trace_execution(struct, message)
  type(my_structure), intent(in)           :: struct
  character(*)      , intent(in), optional :: message ! My addition

  character(:), allocatable :: tmp

  ! Original function was outer if statement
  if (struct%trace_enabled)
    if (present(message)) then ! My addition
      tmp = struct%trace_message
      struct%trace_messgae = message
      call my_trace_function(struct)
      struct%trace_message = tmp
    else
      call my_trace_function(struct)
    end if
  end if
end subroutine

I originally declared the optional argument character(128), optional like it is in the struct. Intel’s compiler didn’t like that because when I passed a literal (<128 characters in length) it said there’s a “character length mismatch” at the call site.

character(:), optional didn’t work either: “a colon may be used as a type parameter value only in the declaration of an entity or component that has the POINTER or ALLOCATABLE attribute”

character(:), allocatable, optional didn’t work either because the string literal wasn’t allocatable at the call site.

I want to avoid having a character(128) variable at the call site, the whole point of this addition was supposed to be convenience :grimacing:.

My Question(s): So, is the function as written above the most correct? Should tmp be declared the way it is? What about message? What’s the difference between character(:) and character(*)?

Please keep in mind

  • Assume I cannot change the structure itself (it interacts with third party software and needs to have a consistent layout)
  • This function is called all over the place, so I don’t want to modify the procedure such that existing calls are impacted

Much appreciated!

I think you probably want a character(*) declaration, but there is a problem if it is optional. An optional argument requires an explicit interface, and if the calling code assumes an implicit interface, then that will require modifying the calling code at all the locations it is referenced. Thus it will not be a localized change.

My code is in a module, so I think I should be covered, right?

Yes, if it is in a module, then it has an explicit interface.You should be able to change the dummy argument declaration, recompile, and everything should work. If you need the length of the dummy argumment, the len() function should work. The only other “gotcha” with the optional attribute is that any references to that argument should occur only after present() tells you that the argument is there.

@adamyakes ,

Do note Fortran does allow defined-length arguments in procedures, but the length-type parameter has to match, as you observed - note though the requirement is for the actual argument to be the same length or greater than the received argument in the procedure. Nonetheless, a preferable way you can manage this might be via a named-constant in your MODULE, see example below with SLEN:

module m
   integer, parameter :: SLEN = 10
contains
   subroutine sub( s )
      character(len=SLEN), intent(in) :: s
      print *, "In sub: s = ", s
   end subroutine 
end module
   use m
   character(len=SLEN) :: a
   a = repeat( "x", ncopies=SLEN )
   call sub( a )
end 
C:\temp>ifx /standard-semantics p.f90
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023.0.0 Build 20221201
Copyright (C) 1985-2022 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 In sub: s = xxxxxxxxxx

C:\temp>