Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
The Intel sign-in experience has changed to support enhanced security controls. If you sign in, click here for more information.

Set file output to UNIX carriage control (LF) rather than Windows (CRLF)

ScottBoyce
Beginner
797 Views

I would like to make my output files with consistent record line endings.

The problem is I use the intrinsic function NEW_LINE(' ') within CHARACTER variables, but this always returns on Windows LF, rather than CRLF.

This results in a mixture of the two on my output files.

For example the following code:

PROGRAM CARRIAGE_CONTROL
  IMPLICIT NONE
  CHARACTER,    PARAMETER:: NL     = NEW_LINE(' ')
  CHARACTER,    PARAMETER:: CR     = ACHAR(13)  
  CHARACTER,    PARAMETER:: LF     = ACHAR(10)  
  CHARACTER(2), PARAMETER:: winNL  = CR//LF
  INTEGER:: IU
  
  OPEN(NEWUNIT=IU, FILE='LineEnding.txt', ACTION='WRITE', FORM='FORMATTED', ACCESS='SEQUENTIAL', STATUS='REPLACE', POSITION='REWIND')
  
   WRITE(IU,'(A)' ) 'Record 0' !CRLF record ending
   WRITE(IU,'(A)' ) 'Record 1' !CRLF record ending
   
   WRITE(IU,'(A)' ) 'Record 2'//NL//'Record 3'  !Middle record ending is LF, while end record is CRLF
   WRITE(IU,'(3A)') 'Record 4', NL, 'Record 5'
   
   WRITE(IU,'(2A)', ADVANCE='NO') 'Record 6', NL !LF   record ending
   WRITE(IU,'(A)' ) 'Record 7'                   !CRLF record ending
   
   WRITE(IU,'(A)' ) 'Record 8'//winNL//'Record 9'  !Middle record ending is CRLF, while end record is CRLF
   
   CLOSE(IU)
END PROGRAM

 

Produces the following output:

OutputFileImage

The issue is that Record 2, 4 and 6 do not have DOS style endings.

 

Ideally, it would be great to just set, through a compiler flag, or even a standard Fortran option that all files opened for WRITE use unix, instead of dos, style line record terminators. This would reduce the file size, and be consistent with the NEW_LINE intrinsic.

This would then change the code output such that:

OutputExample2.PNG

 

Thanks

 

 

0 Kudos
10 Replies
IanH
Black Belt
797 Views

Try with the file opened for formatted stream access, not formatted sequential.

ScottBoyce
Beginner
797 Views

IanH (Blackbelt) wrote:

Try with the file opened for formatted stream access, not formatted sequential.

 

That did not change the output, it still is a mixture of LF with CRLF.

IanH
Black Belt
797 Views

Scott B. wrote:

Quote:

IanH (Blackbelt) wrote:

 

Try with the file opened for formatted stream access, not formatted sequential.

 

 

 

That did not change the output, it still is a mixture of LF with CRLF.

File a bug report. That's what new_line is supposed to do.

Steve_Lionel
Black Belt Retired Employee
797 Views

I disagree - it is exactly what NEW_LINE is specified as doing in the standard.

Result Value.
Case (i): If A is default character and the character in position 10 of the ASCII collating sequence is representable in the default character set, then the result is ACHAR (10).
Case (ii): If A is ASCII character or ISO 10646 character, then the result is CHAR (10, KIND (A)).
Case (iii): Otherwise, the result is a processor-dependent character that represents a newline in output to files connected for formatted stream output if there is such a character.
Case (iv): Otherwise, the result is the blank character.

 

In Intel Fortran you can open a formatted file with RECORDTYPE="STREAM_LF" and it will do what you want. There is no standard way to do this.

IanH
Black Belt
797 Views

Steve Lionel (Ret.) (Blackbelt) wrote:

I disagree - it is exactly what NEW_LINE is specified as doing in the standard.

Result Value.
Case (i): If A is default character and the character in position 10 of the ASCII collating sequence is representable in the default character set, then the result is ACHAR (10).
Case (ii): If A is ASCII character or ISO 10646 character, then the result is CHAR (10, KIND (A)).
Case (iii): Otherwise, the result is a processor-dependent character that represents a newline in output to files connected for formatted stream output if there is such a character.
Case (iv): Otherwise, the result is the blank character.

 

In Intel Fortran you can open a formatted file with RECORDTYPE="STREAM_LF" and it will do what you want. There is no standard way to do this.

I was a bit brief because I was about to get off my horseless chariot, so elaborating - I was r-eferring to the mix of line endings in the same file, not changing the line ending convention.  The character returned by the new_line intrinsic, when written to a formatted stream file via an A edit descriptor is supposed to create a new record, and on Windows such records are delimited by cr-lf, so if you are not seeing cr-lf under those circumstances that is a compiler (runtime) bug. See f2018 13.7.4p5.

ScottBoyce
Beginner
797 Views

I agree with you Steve that NEW_LINE only returns a single character (which is odd considering DOS uses two characters).

 

I read about opening the file with RECORDTYPE="STREAM_LF", but does that only work for ACCESS='STREAM'?

Also that makes the code no longer portable outside of Intel Fortran, which is why I was hoping for a compiler option instead.

Another issue is this is a large numerical simulation software and changing all the OPEN statements is not really an option.

 

I would put in a request for a compiler option that makes all WRITE statements use LF over CRLF. Or have it so it makes it that all write statements produce the same ending that NEW_LINE does.


Another compiler option that would be great is to allow for NEW_LINE to return two characters for dos endings (I probably would not use this, but still useful).

This is probably esoteric, but its been a real stop gap for me because this software contains a lot legacy code so the output is a mixture of LF with CRLF causing post-processors to get confused as to the file type (dos/unix) being processed.

Steve_Lionel
Black Belt Retired Employee
797 Views

The RECORDTYPE='STREAM_xx' extension existed long before ACCESS='STREAM' and works with sequential formatted access. The standard says (though I had to hunt for it - 13.7.4p5 in F2018 and also hinted at in the description of NEW_LINE I quoted above) that you get LF.  I was a bit astonished to find that ifort accepts ACCESS='STREAM', RECORDTYPE='STREAM_CRLF' and stream files will be written with CRLF record delimiters. (This makes me a bit uncomfortable, but once you add RECORDTYPE you're outside the standard and all bets are off.)

There is no way NEW_LINE could be plausibly extended to return multiple characters.

jimdempseyatthecove
Black Belt
797 Views

Have you tried using a Control Edit Descriptor or $ or \ to suppress line terminator, then use your desired line terminator at the end of your output list? The IVF document indicates $ suppresses line terminator for interactive I/O, $ (or \) may work for stream or formatted text output.

Jim Dempsey

ScottBoyce
Beginner
797 Views

I've actually never worked with the $ or \ in fortran. I have used in the past ADVANCE='NO'

Do you have any format examples for $ and \ (or reference that I could look them up with).

Due to the size of the program, its not really plausible to suppress the line terminator.
I just have written a lot of support and error reporting routines that build up a string that contains NEW_LINE characters, then write it to a file.

 

For example this is a warning routine that I have written:

-- Note that :
NL = NEW_LINE()

BLN = NL//NL

Z = 0

and WARN_IU is a global variable

 

  SUBROUTINE WARNING_STATEMENT(LINE,INFILE,OUTPUT,MSG, INLINE, CMD_PRINT, SET_UNIT, KPER)
    INTEGER,      INTENT(IN), OPTIONAL:: INFILE
    CHARACTER(*), INTENT(IN), OPTIONAL:: LINE
    CHARACTER(*), INTENT(IN), OPTIONAL:: MSG
    INTEGER,      INTENT(IN), OPTIONAL:: OUTPUT       !UNIT TO WRITE WARNING TOO, MAY ALSO SET WARN_IU
    LOGICAL,      INTENT(IN), OPTIONAL:: INLINE       !IF TRUE, WARNING IS  WRITTEN TO ONE LINE
    LOGICAL,      INTENT(IN), OPTIONAL:: CMD_PRINT    !IF TRUE, WARNING IS  WRITTEN TO CMD PROMPT
    LOGICAL,      INTENT(IN), OPTIONAL:: SET_UNIT     !IF TRUE, THEN ONLY SETS OUTPUT TO WARN_IU AND RETURNS
    INTEGER,      INTENT(IN), OPTIONAL:: KPER         !RESETS WARNING HEADER TO NEW STRESS PERIOD, NEXT CALLED WARNING WILL WRITE HEADER
    !
    INTEGER, SAVE:: SP_NUM = Z
    LOGICAL, SAVE:: WRITE_HEADER = FALSE
    !
    CHARACTER(:),ALLOCATABLE :: WARN, FNAME
    INTEGER:: IOUT
    LOGICAL:: CMD_PRN, ONE_LINE, CHECK
    !
    IOUT = Z
    IF(PRESENT(OUTPUT)) IOUT = OUTPUT
    !
    IF(PRESENT(SET_UNIT)) THEN
          IF(SET_UNIT) THEN
                           WARN_IU = IOUT
                           IF(WARN_IU.NE.Z) WRITE(WARN_IU,'(A)') BLN//'                           ONE-WATER WARNING FILE'//BLN//'         THE FOLLOWING COMMENTS WERE PASSED TO THE WARNING ROUTINE'//BLN//REPEAT('#',80)//BLN
                           RETURN
          END IF
    END IF
    !
    IF(PRESENT(KPER)) THEN
         IF(WARN_IU.NE.Z .AND. WARN_IU.NE.IOUT) THEN
             SP_NUM = KPER
             WRITE_HEADER = TRUE
         END IF
         RETURN
    END IF
    !
    IF(WRITE_HEADER) THEN
       WRITE_HEADER = FALSE
       WRITE(WARN_IU,'(A)') BLN//REPEAT('>',104)//NL//REPEAT('<',104)//BLN//REPEAT(BLNK,33)//'WARNINGS FOR STRESS PERIOD '//NUM2STR(SP_NUM)//BLN//REPEAT('<',104)//NL//REPEAT('>',104)//BLN//BLN//REPEAT('#',104)//NL
    END IF
    !
    CMD_PRN = FALSE
    IF(PRESENT(CMD_PRINT)) CMD_PRN = CMD_PRINT
    !
    ONE_LINE = FALSE
    IF(PRESENT(INLINE)) ONE_LINE = INLINE
    !
    IF(ONE_LINE) THEN
        WARN=NL//'WARNING: '
        IF(PRESENT(MSG )) THEN; IF(MSG .NE.BLNK) WARN = WARN//TRIM(MSG)//BLNK
        END IF
        IF(PRESENT(LINE)) THEN; IF(LINE.NE.BLNK) WARN = WARN//'FROM PROCESSING LINE "'//TRIM(ADJUSTL(LINE))//'" '
        END IF
        IF(PRESENT(INFILE)) THEN
           IF(INFILE.NE.Z) THEN 
              CALL GET_FILE_NAME(INFILE,FNAME,HAS_ERROR=CHECK) 
              IF(.NOT. CHECK) WARN = WARN//'FROM FILE "'//TRIM(FNAME)//'" '
              DEALLOCATE(FNAME)
           END IF
        END IF
    ELSE
        WARN=BLN//'                           ONE-WATER WARNING'//BLN//'         THE FOLLOWING COMMENTS WERE PASSED TO THE WARNING ROUTINE'//NL
        !
        IF(PRESENT(INFILE)) THEN
           IF(INFILE.NE.Z) THEN
              CALL GET_FILE_NAME(INFILE,FNAME,HAS_ERROR=CHECK) 
              IF(.NOT. CHECK) WARN = WARN//NL//'THE WARNING IS BELIEVED TO HAVE ORIGINATED FROM THE FOLLOWING FILE:'//NL//'"'//TRIM(FNAME)//'"'//NL
              DEALLOCATE(FNAME)
           END IF
        END IF
        IF(PRESENT(LINE)) THEN; IF(LINE.NE.BLNK) WARN = WARN//NL//'THE GUESSED LINE THAT THE WARNING OCCURED ON IS:'//NL//'"'//TRIM(LINE)//'"'//NL
        END IF
        IF(PRESENT(MSG )) THEN; IF(MSG .NE.BLNK) WARN = WARN//NL//'THE DESRIPTION OF THE WARNING IS:'//BLN//TRIM(MSG)//NL
        END IF
        !
        WARN = BLN//REPEAT('#',104)//WARN//NL//REPEAT('#',104)//BLN
    END IF
    !
    IF(WARN_IU.NE.Z .AND. WARN_IU.NE.IOUT) THEN
        IF(ONE_LINE) THEN
            WRITE(WARN_IU,'(A///,A//)') WARN,REPEAT('#',104)
        ELSE
            WRITE(WARN_IU,'(A)') WARN(223:LEN(WARN)-1)
        END IF
    END IF
    !
    IF(IOUT.NE.Z) WRITE(IOUT,'(A/)') WARN
    IF(CMD_PRN  ) WRITE(*,   '(A/)') WARN
  END SUBROUTINE

 

Steve_Lionel
Black Belt Retired Employee
797 Views

$ and \ are extensions. If you're going to use an extension, use RECORDTYPE. 

Reply