Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Blank Characters

JohnNichols
Valued Contributor III
3,393 Views

If I have a character*72 Name

and Name is all blank characters coming in from a file from another program - how do I test for blankness --

Ta

John

0 Kudos
23 Replies
mecej4
Honored Contributor III
3,226 Views

The rules of Fortran provide truncation or blank padding, as needed, when a character variable is assigned a value from a character expression and the lengths do not match.

Try

program blank
character(len=72) :: bl1, bl2
bl1 = repeat(' ',72)
bl2 = '   '
print *, bl1 == bl2
end program

 

0 Kudos
GVautier
New Contributor II
3,226 Views

Hello

name.eq." "

 

 

0 Kudos
JohnNichols
Valued Contributor III
3,226 Views
!----------------------------------------------------------
!  St7APIDemo.f90
!----------------------------------------------------------
!  This example demonstrates the Visual Fortran link to
!  the Strand7/Straus7 API. The program loads St7API.DLL,
!  opens a requested file and then runs the linear static
!  solver.
!
!  To successfully run this program, the location of
!  the dynamic link library "ST7API.DLL" must be added to
!  the Windows PATH environment variable.
!
!  This program was successully compiled and run using:
!  - Intel Visual Fortran 10.0
!  - Compaq Visual Fortran 6.6.0
!----------------------------------------------------------

    PROGRAM St7ApiDemo

!  Use the API interface and constants modules
    USE St7APICall
    USE St7APIConst
    IMPLICIT NONE
   
!  Declaration of local variables
    INTEGER(4) :: iNode,nNode,nBeam,nPlate,nBrick,nMax,iErr,i
    integer(4) :: NewNode,nBricks, iBrick, BrickID,iConn(9),propNum, iPlate,nPlates
    integer(4) :: iConnPL(5)
    REAL(8) :: XYZ(3)
    LOGICAL :: Loaded    
    Logical :: Exists 
    CHARACTER(72) :: fName
    character(len=72) :: sAuthor,sTitle
    character(len=72) :: bl1, bl2 

!  Load the API
    write(*,1000)
1000 Format(/"------------------------------------------------------------------------------------------------------"/)    
    Write(*,100)
100 Format(//"              Program to make Strand 7 Changes",//)    
    CALL LoadSt7API(Loaded)
    IF (Loaded) then
        Write(*,300)
300     Format("              ST7API.DLL loaded successfully.")
    ELSE
        TYPE *, "Cannot load ST7API.DLL."
        TYPE *, "Press <Enter>"
        READ(*,*)
        STOP
    ENDIF

!  Initialise the API
    iErr = St7Init()
    IF (iErr == ERR7_NoError) THEN
        Write(*,500)
500 Format("              API initialisation successful.")
    ELSE
        TYPE *, "Error initialising the API."
        TYPE *, "Press <Enter>"
        READ(*,*)
        STOP
        ENDIF


        WRITE(*,10)
10      FORMAT(1X,/,'              Name of the input file please : ',\)
        READ(*,20)fName
        
20   format(a12)
        Inquire(FILE = fName, Exist=Exists)
        if(Exists .eq. .FALSE.) then
            Stop "                File does not exist"
        endif
        
!  Open a user-selected ST7 file

    
    iErr = St7OpenFile(1,fName,"c:\\temp"C)
    
    
    IF (iErr /= ERR7_NoError) THEN
        write(*, 200) iErr
200     Format("               St7OpenFile returned error #",3x, I4)
        TYPE *, "              Requested file cannot be opened."
        TYPE *, "             Press <Enter>\"
        READ(*,*)
        STOP
    ELSE
        Write(*,400)
400     Format(/"              File successfully opened.")
    ENDIF
    

!  Obtain and display the entity totals
    CALL ChkErr(St7GetTotal(1,tyNODE,nNode))
    CALL ChkErr(St7GetTotal(1,tyBEAM,nBeam))
    CALL ChkErr(St7GetTotal(1,tyPLATE,nPlate))
    CALL ChkErr(St7GetTotal(1,tyBRICK,nBrick))

    write(*,1000)
    Write(*,600)
600 Format("              FILE ENTITY TOTALS:")
    Write(*,700)nNode
700 Format("              Total Nodes   ::  ", I8)
    Write(*,800)nBeam
800 Format("              Total Beams   ::  ", I8)
    Write(*,900)nPlate
900 Format("              Total Plates  ::  ",I8)
    Write(*,1100)nBrick
1100 Format("              Total Bricks  ::  ",I8)

!  Obtain and display some string titles
    CALL ChkErr(St7GetTitle(1,TITLEAuthor,sAuthor,72))
    CALL ChkErr(St7GetTitle(1,TITLEModel,sTitle,72))

    write(*,1000)
    Write(*,1500)
     bl1 = repeat(' ',72) 
     bl2 = '   ' 
1500 Format("              File Author Details")
     print *, sAuthor == bl1 
     if(sAuthor == bl1)then
     print *, sAuthor == bl1 

         stop " No Author"
     endif
    Write(*,1600)sAuthor
1600 Format("              File author :: ",(A))
    Write(*,1700)sTitle
1700 Format("              File title  :: ",(A))

      write(*,1000)
!  Display the coordinates of a few nodes
    IF (nNode.gt.0) THEN
        nMax = nNode
        
        Write(*,1800)
1800    format("              POSITION OF FIRST NODE")
        DO iNode = 1, 1
            iErr = St7GetNodeXYZ(1,iNode,XYZ)
            Write(*,1900)XYZ(1),XYZ(2),XYZ(3)
1900        Format("               X :: ",F10.3,/,"               Y :: ",F10.3,/,"               Z :: ",F10.3)
        end do
        
            Write(*,2000)
2000    format("              Position of First Copied Node")
        DO iNode = 1, nMax
            iErr = St7GetNodeXYZ(1,iNode,XYZ)
            NewNode = iNode + nMax
            
            XYZ(1) = XYZ(1) - 9.590
            XYZ(2) = XYZ(2) + 0.548
            XYZ(3) = XYZ(3) + 23.09
            iErr = St7SetNodeXYZ(1,NewNode,XYZ)
            if(iNode .eq. 1) then
                Write(*,2100)XYZ(1),XYZ(2),XYZ(3)
            endif
2100        Format("               X :: ",F10.3,/,"               Y :: ",F10.3,/,"               Z :: ",F10.3)
        end do
    ENDIF
    
    If(nBrick .gt. 0) then
        Write(*,2200)
2200    format("              Copy the Brick Element Details.")
        
        nBricks = nBrick
        
        do iBrick = 1, nBricks
            
            iErr = St7GetBrickID(1,iBrick,BrickID)
            iErr = St7GetElementConnection(1,tyBRICK,iBrick,iConn)
            iErr = St7GetElementProperty(1,tyBrick,iBrick,propNum)
            
            do i = 2,9
                iConn(i) = IConn(i) + nMax
            end do
            
            iErr = St7SetElementConnection(1, tyBrick, iBrick + NBricks, propNum, iConn)
            !write(*,*)iBrick,BrickID
        end do
          Write(*,2400)
2400    format("              Add the Brick Element Details.")
        
        nBricks = nBrick
        
        do iBrick = 1, nBricks
            
            iErr = St7GetBrickID(1,iBrick,BrickID)
            iErr = St7GetElementConnection(1,tyBRICK,iBrick,iConn)
            iErr = St7GetElementProperty(1,tyBrick,iBrick,propNum)
            
            do i = 2,9
                iConn(i) = IConn(i) + nMax
                if(iConn(i) .eq. 46781) then
                    if(i .eq. 2 .or. i .eq. 3 .or. i .eq. 4 .or. i .eq. 5) then
                        Call NewBox(iConn(2), iConn(3), iConn(4),iConn(5),nMax)
                        stop
                    else
                        
                    endif
                endif
            end do
        end do
        
        
    endif
    
    
    
    if(nPlate .gt. 0) then
        Write(*,2300)
2300    Format("              Copy the Plate Element Details")
    
        nPlates = nPlate
        
        do iPlate =1,nPlates
            iErr = St7GetPlateID(1,iPlate,BrickID)
            iErr = St7GetElementProperty(1,tyPlate,iPlate,propNum)
            iErr = St7GetElementConnection(1,tyPlate,iPlate,iConnPL)
            
            do i = 2,5
                iConnPL(i) = IConnPL(i) + nMax
            end do
            iErr = St7SetElementConnection(1, tyPlate, iPlate + nPlates, propNum, iConnPL)
            write(*,*)iPlate,BrickID,propNum
        end do
    endif

! Run the Linear Static Solver
    !iErr = St7RunSolver(1,stLinearStaticSolver,smNormalRun,1)
    !IF (iErr == ERR7_NoError) THEN
      !  TYPE *, "Linear Static Solver successfully run."
   ! E!LSE
      !  TYPE *, "Solver returned error #",iErr
   ! ENDIF
   ! TYPE *, "Press <Enter>"
   ! READ(*,*)

!  Close the ST7 file
    iErr = St7SaveFile(1)
    iErr = St7CloseFile(1)

!  Unload the API
    CALL FreeSt7API

    write(*,3000)
3000 Format( "                   End of Program.")

        END PROGRAM St7ApiDemo
        
        Subroutine NewBox(i1,i2,i3,i4,NodeMax)
        
        implicit none
        
        Integer(4) :: i1,i2,i3,i4,NodeMax
        
        Write(*,*)i1,i2,i3,i4,NodeMax
        
        return
        end subroutine
        

Does not work - although your examples does -- here is the code it has a lock dongle so I cannot send all .

!  This routine uses St7GetAPIErrorString to return the
!  error message associated with any errors found.
!  All St7API.DLL function calls return an integer to
!  signify whether the function was successful.
!  If the return is zero, the function was successful.

    SUBROUTINE ChkErr(iErr)
    USE St7APICall
    USE St7APIConst
    INTEGER(4), INTENT(IN) :: iErr
    INTEGER(4) :: iTemp
    CHARACTER(128) :: ErrorString

    IF (iErr /= ERR7_NoError) THEN
        ErrorString = ""
        iTemp = St7GetAPIErrorString(iErr, ErrorString, kMaxStrLen)
        TYPE *, TRIM(ErrorString)
    ENDIF

    END SUBROUTINE ChkErr

 

0 Kudos
mecej4
Honored Contributor III
3,226 Views

Without having the modules USEd in your source, we cannot run the compiler on your program. A specific question: if the vendor library is written in C, does it expect null-terminated strings, or does it know how to handle Fortran strings and the semi-hidden Fortran string length arguments? Without that awareness, the API C routines may go looking for those non-existing null characters. On the Fortran side, an embedded null character has no special significance, and a string with all blanks will not match a string with all blanks except for a null somewhere in the middle. Embedded white-space characters (tab, form-feed, space, CR, LF,..) will pose similar problems.

Note also that CVF and Intel Fortran have default conventions on how to pass those hidden arguments. See https://software.intel.com/en-us/node/679043

Try this to see the effect of nulls:

program blank
character(len=72) :: bl1, bl2
bl1 = repeat(' ',72)
bl2 = '   '
print *, bl1 == bl2
bl1(36:36) = char(0)
print *, bl1 == bl2
end program

 

0 Kudos
GVautier
New Contributor II
3,226 Views

Hello

I agree with mecje4

St7GetAPIErrorString(iErr, ErrorString, kMaxStrLen)

The kMaxStrlen argument lets suppose that the function returns a C string (null terminated). You can try to use ErrorString[1:1]==char(0) or strlen(ErrorString)==0 to test if the returned C string is empty.

 

When you ask for help, it's better to give the context of your question in the first post. Answers will be more pertinent.

 

 

0 Kudos
JohnNichols
Valued Contributor III
3,226 Views

Dear mecej4 and Giles:

Thank you for the answers.  The program is called STRAND7 and is written in Australia as a FEM Analysis package. As far back as I can remember it was written in Fortran or so the legend goes.  I have continued to assume that it is written in Fortran but it appears I am wrong.  I cannot send the APIDLL's as a Strand DLL supported program will not run without the dongle, I have had this problem before the Strand people are paranoid about unlicensed use of their stuff.  I had typed comments into the last post, but they appear to have got lost in the translation.

I should have thought of the null terminated string, never crossed my mind. I need to test the string for individual characters - thanks for the help. 

PS: If any of you live in London, there is now a simple device monitoring one of the London bridges, it should be running in Linux on a NUC, but it is running on Windows on a HP Pavilion.  You should always write code late on a Sunday night onto a computer in London to be deployed the following morning, that is to be locked away for three months, and has to function completely stand alone. Gotta love it. 

John

 

0 Kudos
GVautier
New Contributor II
3,226 Views

An empty C string has its first character set to 0. So testing only the first character will detect an empty string:

if (string(1:1)==char(0)) then    ! empty string

 

0 Kudos
mecej4
Honored Contributor III
3,226 Views

Don't need a dongle just to read the API manual, which we can find  at http://www.strand7.com/downloads/Strand7%20R246%20API%20Manual%20TOC.pdf .

In that manual, it clearly says, on page 11,

API Strings and Visual Fortran
The Strand7 API uses null-terminated strings. These are always declared as
CHARACTER(LEN=*) in the interface section (St7APICall.f90), and are passed by
reference. Strings will be declared in your program as CHARACTER(LEN=255) (for
example). An API call returning the string will null-terminate the string with CHAR=0 at
some point. All character values beyond this point will be undefined.

 

0 Kudos
JohnNichols
Valued Contributor III
3,226 Views

Quite true. I should not have missed that -- thank you.

0 Kudos
FortranFan
Honored Contributor II
3,226 Views

John Nichols wrote:

..  how do I test for blankness ..

@John Nichols,

I suggest string length of zero be your test for "blankness".  And this: if you're dealing with CHARACTER variables in Fortran that are interfacing with C type of APIs, meaning null-termination in C can be involved, then you should use strnlen function from C runtime library to get the string length.  Otherwise, use the LEN_TRIM intrinsic function in Fortran:

module m

   use, intrinsic :: iso_c_binding, only : c_char, c_null_char

   implicit none

   private

   public :: Some_C_API

contains

   subroutine Some_C_API( s ) bind(C, name="Some_C_API")

      character(kind=c_char,len=1), intent(inout) :: s(*)

      s(1) = c_null_char

      return

   end subroutine Some_C_API

end module m
program p

   use, intrinsic :: iso_c_binding, only : c_char, c_size_t
   use m, only : Some_C_API

   implicit none

   interface

      function strnlen( s, maxlens ) result( lens ) bind(C, name="strnlen")

         import :: c_char, c_size_t

         implicit none

         !.. Argument list
         character(kind=c_char,len=1), intent(in) :: s(*)
         integer(c_size_t), intent(in)            :: maxlens
         !.. Function result
         integer(c_size_t) :: lens

      end function strnlen

   end interface

   integer(kind=c_size_t), parameter :: MAXLEN = 255
   character(len=MAXLEN) :: bl1
   character(len=MAXLEN) :: bl2
   character(kind=c_char,len=MAXLEN) :: bl3

   bl1 = repeat( " ", MAXLEN )
   bl2 = "  "
   call Some_C_API( bl3 )

   print *, "len_trim(bl1) = ", len_trim(bl1)
   print *, "len_trim(bl2) = ", len_trim(bl2)
   print *, "strnlen(bl3)  = ", strnlen(bl3, MAXLEN)

   stop

end program p

Upon execution with Intel Fortran,

 len_trim(bl1) =  0
 len_trim(bl2) =  0
 strnlen(bl3)  =  0

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,226 Views

John,

Also note in FortranFan's example, if you add at line 38

print *, "len_trim(bl3) = ", len_trim(bl3) ! length of empty "C" string with NULL

That the result with show 1

IOW, if you intend to use the string in the Fortran portion, you might want to inspect the len_trim'th character for NULL and take that into consideration. As to what action you want to take, it is up to you. Also, do not overwrite the C original string null with ' ' as this may corrupt the C visible string. You can overwrite the null in any copy you make in the Fortran space.

Jim Dempsey

 

0 Kudos
JohnNichols
Valued Contributor III
3,226 Views

Jim and FF:

Thank you for the code.  The original code is a very basic example in Fortran for interfacing with the Strand7 API. Strand7 is an FEM modeller.

I had tried to use this once before but the dongle issues got in the road.  However a young scientist and I have been modelling an interesting structure using two different FEM codes to make sure the answers match as closely as possible our real data. It is a challenge as the structure is interconnected in weird ways that make simple models impossible and block models challenging.  I needed to copy elements of the model involving plates and blocks, but the STRAND7 GUI left some elements behind in the copy -- a real pain. I thought I would try the API and it turned out to be quite good and for the simple copies we want easy to code.

The code include the example to print out the titles etc, but I kept getting two lines printed even though the string appeared empty in VS Studio debug mode. Hence my question about blanks as the debug showed a string about 20 characters long with nothing in it, I had heard many years ago that Strand was written in Fortran - I was quite slow in not picking up the notes in the API manual as I had looked at this manual to see the C String. 

My code to check for zero length looks for the Char(0) called ASC in the code as a variable name.  This is quick and dirty code to solve a simple problem, so I used a simple method, really should clean it up. 

Thanks for all the help -- I am not sure how I would survive without this forum. 

Code I used - very dirty and very simple 

  do i = 1, 72
                if(sAuthor(i:i) == ASC) then
                    Flag(1) = Flag(1) + 1
                endif
                if(sTitle(i:i) == ASC) then
                    Flag(2) = Flag(2) + 1
                endif
                if(sProject(i:i) == ASC) then
                    Flag(3) = Flag(3) + 1
                endif
                if(sCreate(i:i) == ASC) then
                    Flag(4) = Flag(4) + 1
                endif
            end do


            write(*,1000)
            Write(*,1500)
1500        Format("              File Author Details", i5)


            if(Flag(1) .eq. 72) then
                sAuthor = "Project Author not provided for file."
                Write(*,2800)(72-Flag(1)),sAuthor
2800            Format("              File Author   :: ","[",I2,"] ",(A))
            else
                Write(*,1600)(72-Flag(1)),sAuthor
1600            Format("              File author   :: ","[",I2,"] ",(A))
            endif
            if(Flag(2) .eq. 72) then
                sTitle = "Project Title not provided for file."
                Write(*,1700)(72-Flag(1)),sTitle
            else
                Write(*,1700)(72-Flag(2)),sTitle
1700            Format("              File title    :: ","[",I2,"] ",(A))
            endif
            if(Flag(3) .eq. 72) then
                sProject = "Project Title not provided for file."
                Write(*,2700)(72-Flag(3)),sProject
2700            Format("              File project  :: ","[",I2,"] ",(A))
            else
                Write(*,2500)(72-Flag(3)),sProject
2500            Format("              File project  :: ","[",I2,"] ",(A))
            endif
            Write(*,2600)(72-Flag(4)),sCreate
2600        Format("              File created  :: ","[",I2,"] ",(A))

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,226 Views

Why do you expect 72 NULLs for an empty field? An empty field is presumably a field with a NULL in position (1) .OR. the pointer/reference being NULL. The C program might not zero-fill the transfer buffer prior to inserting the text.

Jim Dempsey

0 Kudos
JohnNichols
Valued Contributor III
3,226 Views

jimdempseyatthecove wrote:

Why do you expect 72 NULLs for an empty field? An empty field is presumably a field with a NULL in position (1) .OR. the pointer/reference being NULL. The C program might not zero-fill the transfer buffer prior to inserting the text.

Jim Dempsey

True -- I could have just checked the first place, I did in the beginning, but I got carried away.

No one said you could not have fun --

Merry Christmas

John 

0 Kudos
GVautier
New Contributor II
3,226 Views

Vautier, Gilles wrote:

An empty C string has its first character set to 0. So testing only the first character will detect an empty string:

if (string(1:1)==char(0)) then    ! empty string

 

Exactly what I said earlier.

0 Kudos
JohnNichols
Valued Contributor III
3,226 Views

Just out of interest could a Fortran String include a chr(0) as a legal entity - but not be the end?

0 Kudos
andrew_4619
Honored Contributor II
3,226 Views

John Nichols wrote:

Just out of interest could a Fortran String include a chr(0) as a legal entity - but not be the end?

Yes

0 Kudos
GVautier
New Contributor II
3,226 Views

Sure

A character(n) Fortran string is an array of n bytes whose values range from 0 to 255.

0 Kudos
mecej4
Honored Contributor III
3,226 Views

A little bit of delving into history should explain why the ASCII null character has no special significance in Fortran. Fortran was in use for several years before the ASCII character set was devised. Take, for example, the CDC "display" character set, https://en.wikipedia.org/wiki/CDC_display_code . The very first 6-bit code, octal 00, stands for ':'. The very last 6-bit code, octal 77, stands for ';', and octal 55 stands for 'blank' or 'space'. No tabs, carriage-returns line-feeds or form-feeds to be found in that character set. All characters can be displayed and printed, and only 'blank' is 'white-space'. 

0 Kudos
andrew_4619
Honored Contributor II
2,600 Views

Ancient history! I coded my first Fortran (FORTRAN) on a CDC Cyber using a teletype terminal and looking back it is amazing that the experience didn't give me an aversion to computers for life. Despite all our whinges the performance and features in the current products is truly fantastic!

0 Kudos
Reply