Left justification of strings

We were cleaning out old kludges from some old codes and I could swear there is now a standard way to use edit descriptors to left-justify strings and can not find it. Did that not happen?

In addition to the standard tricks for amusement here are some of the ways people were accomplishing left justification of strings:

implicit none
character(len=80),parameter :: LH=repeat(' ',80)

   ! LEFT JUSTIFICATION
   ! pretty straight-forward
   write(*,"('A and Tnn gives left justification')")
   write(*,'(a,t11,a,t21,a)')'one','two','three'
   ! truncation can be a good thing
   write(*,"('repeat A10 with intentional truncation gives left justification (useful truncation!)')")
   write(*,'(*(a10))')'one'//LH,'two'//LH,'three'//LH
   ! cleaner than internal WRITE and adjustl() solutions usually used but a bit verbose
   write(*,"('A edit descriptor and pad()')")
   write(*,'(*(a))')pad('one',10),pad('two',10),pad('three',10)
   
   write(*,"('A with separate writes and TAB NO ADVANCE gives left justification')")
   write(*,'(*(a,t11))',advance='no')'one'
   write(*,'(*(a,t11))',advance='no')'two'
   write(*,'(*(a,t11))',advance='no')'three'
   write(*,*)
   ! relatively new so this has been a problem for a long time and seems like it still is
   write(*,"('repeat G0 (or A) with length set gives left justification')")
   write(*,'(*(g0))')[character(len=10) :: 'one','two','three']

contains

function pad(line,length) result(strout)
character(len=*),intent(in)                :: line
integer,intent(in)                         :: length
character(len=max(length,len(trim(line)))) :: strout ! do not truncate
   strout=line
end function pad

There is an intrinsic procedure named ADJUSTL that left-adjusts a character. (And ADJUSTR for right-adjust.)

I guess what @urbanjost is looking for is something like A-10 (in analogy with %-10s used in this page) that works directly for any strings (like “one”)?

Yes. Fortran right-justifies output when given an Aw edit descriptor where w is longer than the variable, so

write(*,'(A10,A10)' ) 'a','b'

would print

         a          b

which might see a little surprising considering Fortran pads character variables on the right with blanks on assignment if the LHS is shorter than the RHS. This has historically meant that to left-justify a string required using an A and T edit descriptor, function calls and internal writes to left-justify and center-justify strings easily. Writing output as HTML or other metadata formats has been one solution and quite a few Fortran compilers over the years had extensions to allow justification. I thought one was of those was adopted in f2008 but cannot find it. I have overloaded adjustl and adjustr and a custom adjustc that make it a little easier (adjustl and adjustr are extended to take a minimum length where ADJUSTL(‘one’,8) returns "one " for example. So I have several ways of controlling fixed-size string outputs and often use HTML with CSS style sheets as well, as well as writing RTF and Adobe PDF files so I do not need a solution if there is no “new” edit descriptor to left-justify strings, just wanted to get rid of some of these kludges if there was now a standard way to left-justify purely with a FORMAT. If not, fine; just thought there was a new standard way.

Perhaps it’s time to incorporate a full string trim into the standard.

It should operate to remove leading and trailing blanks from a string, e.g. to effect this code


program StringTrim
implicit none

print *, "Hello World!"
Print *

write(*,"(*('<',A,'>',:))") " One ", "  Two  ","   Three   ", " One  Two   Three   "

write(*,*)

write(*,"(*('<',A,'>',:))") Strim(" One "), Strim("  Two  "),Strim("   Three   "), Strim("  One  Two   Three   ")

Contains
    function Strim(StrIn) result(StrOut)
      character(len=*),intent(in) :: StrIn
      character(len=:),allocatable :: StrOut
      allocate(character(len=len(trim(adjustl(StrIn)))) :: StrOut)
      StrOut = trim(adjustl(StrIn))
   end function

end program


which produces the output:


Hello World!

< One >< Two >< Three >< One Two Three >


Or even the output

Hello World!

< One >< Two >< Three >< One Two Three >

I can’t see any difference between the two outputs. But I am confused by the first and last spaces remaining.

This system is truncating the output. Maybe this will work

Hello World!
   
< One ><  Two  ><   Three   >< One  Two   Three   >    ! no trimming
  
<One><Two><Three><One  Two   Three>                   ! using STRIM function