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

Define a character function with variable length

Zorrilla__David
Beginner
2,722 Views

I'm trying to programming a function with variable length arguments and variable length retuned value. I try this:

FUNCTION REPLACE_CHAR(STR,CHIN,CHOUT)
    IMPLICIT NONE
    
    CHARACTER(LEN=*) :: STR
    CHARACTER(LEN=LEN(STR))::REPLACE_CHAR
    CHARACTER(LEN=1)::CHIN,CHOUT
    INTEGER(KIND=4)::I
    
    REPLACE_CHAR=STR
    DO I=1,LEN_TRIM(STR)
        IF (STR(I:I)==CHIN)THEN
            REPLACE_CHAR(I:I)=CHOUT
        ENDIF
    ENDDO
    RETURN
END FUNCTION   

But although I have no error in compilation of this functions, I have an error when I call this functions from another:

CHARACTER(LEN=LEN(STR))::REPLACE_CHAR,STR1
STR1=REPLACE_CHAR(STR,'\','/')

I also try this (with allocate):

FUNCTION REPLACE_CHAR(STR,CHIN,CHOUT)
    IMPLICIT NONE
    
    !CHARACTER(LEN=*) :: STR
    CHARACTER(LEN=LEN(STR))::REPLACE_CHAR
    CHARACTER(LEN=:),ALLOCATABLE :: STR, REPLACE_CHAR
    CHARACTER(LEN=1)::CHIN,CHOUT
    INTEGER(KIND=4)::I,LENGTH
    
    LENGTH=LEN(STR)
    ALLOCATE(CHARACTER(LEN=LENGTH) :: REPLACE_CHAR)
    
    REPLACE_CHAR=STR
    DO I=1,LEN_TRIM(STR)
        IF (STR(I:I)==CHIN)THEN
            REPLACE_CHAR(I:I)=CHOUT
        ENDIF
    ENDDO
    RETURN
END FUNCTION 

But I have the same error when I call this function.

How can I do this?

Thanks in advanced

0 Kudos
8 Replies
Arjen_Markus
Honored Contributor I
2,722 Views

You do not indicate what the error is, but judging from the way you are declaring and using the function, I suspect that you did not put it in a module.

When you do, there is no need for the explicit declaration of replace_char. This is taken care of by the use statement for the module. Moreover, the module provides exactly the right information for the compiler. So my advice is to put the function in a module and then use that.

The "allocatable" version is more flexible, because it may be that at some point you are going to replace a string by a longer string and will not know in advance how long the resulting string should be. But for now, the first version ought to do it.

0 Kudos
andrew_4619
Honored Contributor II
2,723 Views
module rs
    implicit none 
    contains
    FUNCTION REPLACE_CHAR(STR,CHIN,CHOUT)
        CHARACTER(LEN=:), ALLOCATABLE :: REPLACE_CHAR
        CHARACTER(Len=*)              :: STR 
        CHARACTER(LEN=1)              :: CHIN, CHOUT
        INTEGER(KIND=4)::I,LENGTH
   
        REPLACE_CHAR = STR    ! automatic allocation of REPLACE_CHAR
        DO I = 1 , LEN_TRIM(STR)
            IF (STR(I:I) == CHIN)THEN
                REPLACE_CHAR(I:I) = CHOUT
            ENDIF
        ENDDO
    END FUNCTION 
end module rs
    
program main
    use rs, only: REPLACE_CHAR
    implicit none
    character(:), allocatable :: str1
    character(80)             :: str
    str = 'c:\testing\testing\123'
    print *, str
    STR1 = REPLACE_CHAR(STR,'\','/') 
    print *, str1
    print *, REPLACE_CHAR('c:\testing\testing\1234','\','/') 
end program main

 

0 Kudos
Zorrilla__David
Beginner
2,723 Views

Thanks. I have just tried and works but there's a way to do this without a module definition. I have been reading this post (https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/280657) ;and it seems that you can do this without a module.....?

Thanks

0 Kudos
andrew_4619
Honored Contributor II
2,723 Views

Why the aversion to modules? They are the best thing in Fortran. You would need to supply and interface to the routine where it is used otherwise. A module does that automatically.

0 Kudos
Zorrilla__David
Beginner
2,723 Views

I have no problem with modules, but if I use a module I have to "remember" to call it (use...) and if I don't use a module I define these functions/subroutines in another file (library.f90, for example) and can call this routines from anywhere.

In fact, this subroutines work for me in early version of intel fortran by using   CHARACTER(LEN=*) in the definition of the routine, and I call them without using "USE" statement or defining variables with "ALLOCATE" statement.

Anyway thaks a lot for your help. I think you are a good team in fortran programming.

Thaks

0 Kudos
Arjen_Markus
Honored Contributor I
2,723 Views

But without modules you have to rely on your getting the argument list correct yourself. With modules the compiler can check them, so that errors in at least the number and the types of the arguments are caught at an early stage. I find that a very small price to pay - merely remembering to add a single line of code.

Beware of CHARACTER(len=*) functions: they were introduced in FORTRAN 77, but their semantics are definitely surprising.

0 Kudos
Zorrilla__David
Beginner
2,723 Views

Yes, you have convince me about using modules and allocatable statements (in fact I force my student to use these statements). I am now "reprogramming" my routines.

Another question about this topic, could I have some problems in linux compiler or maybe I have to change something in the routine (because I am programming in windows but I'd like to compiler this software in linux too).

Thanks

0 Kudos
Arjen_Markus
Honored Contributor I
2,723 Views

As long as you use standard Fortran the code should be quite portable. I wouldn't worry about that. The only thing you may run into if you are using cutting-edge features (e.g. the latest additions to the language in Fortran 2008), then some compilers may not actually support that. But other than that, it should be fine.

0 Kudos
Reply