- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
With the code below, I get "error #6406: Conflicting attributes or multiple declaration of name.". Is it true that allocatable characters cannot be protected, or is it just a bug in the implementation?
module mod1
character(:), allocatable, protected :: global_str
contains
subroutine set_global_string(str)
character(*), intent(IN) :: str
global_str = TRIM(str)
end subroutine
end module mod1
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I just found another issue with my "allocatable character" attempts. When I try to compile the code below, I get the error message "Generic procedure reference has two or more specific procedure with the same type/rank/keyword signature". And if I comment out the "module procedure CONCAT_ARRAY_CHAR" line, then the error message I get is "If a dummy argument is allocatable or a pointer, the associated actual argument shall have deferred length parameter if and only if the dummy argument has deferred length parameter". It looks like"character(*)" and "character(:), allocatable" are treated the same. Is that the expected behavior? Thanks.
module mod1
private
interface concat
module procedure CONCAT_ARRAY_STRING
module procedure CONCAT_ARRAY_CHAR
end interface; public concat
contains
!--------------------------------------------------------------------------------------------------
pure subroutine CONCAT_ARRAY_CHAR(array, string)
character(*), intent(IN) :: array(:)
character(*), intent(OUT) :: string
integer :: i
string = ''
do i = 1, SIZE(array)
string = TRIM(string)//ADJUSTL(array(i))
enddo
end subroutine
!--------------------------------------------------------------------------------------------------
pure subroutine CONCAT_ARRAY_STRING(array, string)
character(:), allocatable, intent(IN) :: array(:)
character(:), allocatable, intent(OUT) :: string
integer :: i
string = ''
do i = 1, SIZE(array)
string = string//array(i)
enddo
end subroutine
end module mod1
!--------------------------------------------------------------------------------------------------
program test
use mod1
character(5), allocatable :: chr(:)
character(25) :: cat_chr
character(:), allocatable :: str(:)
character(:), allocatable :: cat_str
continue
allocate (chr(5))
chr = '12345'
allocate (str(5), source = '12345')
call concat(chr, cat_chr)
print '("character: " A)', cat_chr
call concat(str, cat_str)
print '("string: " A)', cat_str
end program test
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In the case of the generic, CHARACTER(*) and CHARACTER(:) are not distinguishable for the purpose of generic resolution. These do not differ in Type, Kind or Rank and therefore the compiler is correct to complain.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In the case of the generic, CHARACTER(*) and CHARACTER(:) are not distinguishable for the purpose of generic resolution. These do not differ in Type, Kind or Rank and therefore the compiler is correct to complain.
I apologize if I'm bothering you too much with these questions, but I'm just trying to understand how the feature works.
In the generic resolution case, I guess the best option is to stick with the CHARACTER(*) form (i.e., to use CONCAT_ARRAY_CHAR only). The problem I see now, is that the length of the allocatable arguments (str and cat_str) must be preallocated.
Thanks for the help!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
CHARACTER(*), INTENT(IN), DIMENSION(:) :: array
CHARACTER(:), INTENT(OUT), ALLOCATABLE :: string
INTEGER i
!****
string = ''
DO i = 1, SIZE(array)
! No trim if you want the padding in the inputs to be in the output
string = string // TRIM(array(i))
END DO
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
CHARACTER(*), INTENT(IN), DIMENSION(:) :: array
CHARACTER(:), INTENT(OUT), ALLOCATABLE :: string
INTEGER i
!****
string = ''
DO i = 1, SIZE(array)
! No trim if you want the padding in the inputs to be in the output
string = string // TRIM(array(i))
END DO
If I have:
pure subroutine concat(array, string)
character(*), intent(IN) :: array(:)
character(*), intent(OUT) :: string
integer :: i
string = ''
do i = 1, SIZE(array)
string = TRIM(string)//ADJUSTL(array(i))
enddo
end subroutine
Then I can use concat with both regular and allocatable character arguments (with the drawback that the second argument must be preallocated to a certain length), but if I have:
pure subroutine concat(array, string)
character(*), intent(IN) :: array(:)
character(:), allocatable, intent(OUT) :: string
integer :: i
string = ''
do i = 1, SIZE(array)
string = TRIM(string)//ADJUSTL(array(i))
enddo
end subroutine
then I cannot call the subroutine with a fixed-length second argument, say:
character(100), allocatable :: array(:)
character(4096) :: string
...
call concat(array, string)
end
Also, because the resolution of CHARACTER(*) and CHARACTER(:) seems to be the same, I cannot overload the generic name.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Let me cheat and shift the goal posts a bit. Can I interest you in a function?
[cpp]MODULE ConcatMod
IMPLICIT NONE
PRIVATE
PUBLIC Concat
CONTAINS
!*****************************************************************************
!!
!*****************************************************************************
PURE FUNCTION Concat(array) RESULT(string)
! Arguments
CHARACTER(*), INTENT(IN) :: array(:)
! Return type
CHARACTER(LEN=concat_len(array)) string
! Locals
INTEGER i
!***************************************************************************
string = ''
DO i = 1, SIZE(array)
string = TRIM(string) // TRIM(array(i))
END DO
END FUNCTION Concat
!*****************************************************************************
!!
!*****************************************************************************
PURE FUNCTION concat_len(array) RESULT(ln)
! Arguments
CHARACTER(*), INTENT(IN) :: array(:)
! Return type
INTEGER ln
! Locals
INTEGER i
!***************************************************************************
ln = 0
DO i = 1, SIZE(array)
ln = ln + LEN_TRIM(array(i))
END DO
END FUNCTION concat_len
END MODULE ConcatMod
[/cpp]
(Edit to differentiate letter l from number 1)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Let me cheat and shift the goal posts a bit. Can I interest you in a function?
That option became the only one to me, after Steve Lionel mentioned the generic resolution conflict. Although my version is much simpler:
pure function concat(array) result(string)
character(*), intent(IN) :: array(:)
character(:), allocatable :: string
integer :: i
string = ''
do i = 1, SIZE(array)
string = TRIM(string)//TRIM(array(i))
enddo
end function
There is no need for the concat_len function anymore.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I've avoided allocatable function results due to some ICE's under 11.0. This has now got me thinking - when an allocatable function result is assigned to an allocatable variable, does the compiler do the equivalent of a "MOVE_ALLOC", or does it create a new allocation and then copy? Can you explicitly use an allocatable function result as an argument to MOVE_ALLOC?
My mental picture of an allocatable (which I now suspect is rather erroneous) was that they were like a C++ smart pointer. So hence I thought I could so something like the following:
[cpp]TYPE ReallyExpensiveToCopyType ... END TYPE TYPE(ReallyExpensiveToCopyType) :: my_obj my_obj = Construct(obj) IF (.NOT. ALLOCATED(my_obj)) THEN CALL things_are_not_going_well() ... ELSE CALL do_something_useful(my_obj) ... END IF FUNCTION Factory(...) RESULT(obj) TYPE(ReallyExpensiveToCopyType), ALLOCATABLE :: obj ... IF (arguments_validate(...)) THEN ALLOCATATE(obj) ... RETURN END IF END FUNCTION Factory [/cpp]
In the end I've used the same approach, but the object is passed as a subroutine argument.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page