Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Concatenate numeric arrays

391 views
Skip to first unread message

qol...@gmail.com

unread,
Nov 10, 2018, 9:50:54 AM11/10/18
to
Is there an existing standard function to do this?

real(8) V1(3), v2(4)
real(8), allocatable :: vv(:)

v1 = [1., 2., 3.]
v2 = [7., 8., 9., 5.]
vv = v1 // v2 ! illegal...

Modern Fortran is well endowed with array manipulation functions and stuff, but I cannot find anything to do this.

--

qolin at domain dot com
domain is qomputing

Thomas Koenig

unread,
Nov 10, 2018, 10:17:37 AM11/10/18
to
qol...@gmail.com <qol...@gmail.com> schrieb:
> Is there an existing standard function to do this?
>
> real(8) V1(3), v2(4)
> real(8), allocatable :: vv(:)
>
> v1 = [1., 2., 3.]
> v2 = [7., 8., 9., 5.]
> vv = v1 // v2 ! illegal...


This is what I would do:

program main
integer, parameter :: dp = selected_real_kind(15)
real(kind=dp) :: v1(3), v2(4)
real(kind=dp), allocatable :: vv(:)
v1 = [1._dp, 2._dp, 3._dp]
v2 = [7._dp, 8._dp, 9._dp, 5._dp]
vv = [v1, v2]
print *,vv
end program main

qol...@gmail.com

unread,
Nov 10, 2018, 10:43:27 AM11/10/18
to
On Saturday, 10 November 2018 15:17:37 UTC, Thomas Koenig wrote:
> qolin schrieb:
Thanks Thomas, yes I remember now I tried that and it didn't work, because in application code there is an additional wrinkle that I forgot to put in the original post: the arrays V1, V2 (etc) are allocatable, and any of them may be unallocated.

Of course I realize now that the concatenation operator for characters would also fail if given unallocated strings, so my original example is not representative. Anyway, FWIW here is the function I wrote, I would be interested to see it can be improved:

function concatenate_real8_vectors(v1,v2,v3,v4,v5) result (res)

real(8), dimension(:), optional :: v1, v2, v3, v4, v5
real(8), allocatable :: res(:)

integer sr, ii, sv

sr = 0
do ii = 1, 2
call xx(v1)
call xx(v2)
call xx(v3)
call xx(v4)
call xx(v5)
if(ii == 2) exit
allocate(res(sr))
sr = 0
enddo

contains
subroutine xx(v)
real(8), optional, intent(in) :: v(:)
if(present(v)) then
sv = size(v)
if(ii == 2) res(sr+1:sr+sv) = v
sr = sr + sv
endif
end subroutine

end function

spectrum

unread,
Nov 10, 2018, 3:35:14 PM11/10/18
to
Just for fun, I've tried the following code to define "//" for
two allocatable arrays and return a concatenated allocatable array:

module utils
implicit none

interface operator (//)
module procedure cat
endinterface
contains

function cat( a, b ) result( res )
real, allocatable, intent(in) :: a(:), b(:)
real, allocatable :: res(:)
allocate( res( 0 ) )
if ( allocated( a ) ) res = [ res, a ]
if ( allocated( b ) ) res = [ res, b ]
endfunction
end

subroutine test()
use utils
implicit none
real, allocatable :: v1(:), v2(:), v3(:), v(:)
v1 = [1.0]
v2 = [2.0, 3.0]
v3 = [4.0, 5.0, 6.0]

v = v1 // v2 // v3 ! works (*1)
! v = (v1 // v2) // v3 ! error (*2)
print *, v
end

program main
call test()
end

With gfortran-8.2, this code seems to work with Line (*1) above,
but fails when Line (*2) is uncommented. The error message is

v = (v1 // v2) // v3 ! error (*2)
1
Error: Operands of string concatenation operator at (1) are REAL(4)/REAL(4)

So I'm wondering if I'm doing something wrong...?

Also, if I compile with "gfortran -g test.f90" and use valgrind, then it gives no
memory leak. Here, is it OK to assume that no memory leak occurs with
an allocatable function result? (in other words, is it automatically deallocated?)

edmondo.g...@gmail.com

unread,
Nov 12, 2018, 5:47:49 AM11/12/18
to
Similar result with ifort, but better error message.
As far as I understood it, it is saying that the expression ( v1 // v2 ) is no more an allocatable and so it cannot be passed to an allocatable argmument:

testSpe.f90(28): error #7976: An allocatable dummy argument may only be argument associated with an allocatable actual argument.
v = (v1 // v2) // v3 ! error (*2)
------------^
compilation aborted for testSpe.f90 (code 1)

ifort version 17.04

spectrum

unread,
Nov 13, 2018, 11:47:26 AM11/13/18
to
On Monday, November 12, 2018 at 7:47:49 PM UTC+9, edmondo.g...@gmail.com wrote:

> Similar result with ifort, but better error message.
> As far as I understood it, it is saying that the expression ( v1 // v2 ) is no more an allocatable and so it cannot be passed to an allocatable argument:
>
> testSpe.f90(28): error #7976: An allocatable dummy argument may only be argument associated with an allocatable actual argument.
> v = (v1 // v2) // v3 ! error (*2)
> ------------^
> compilation aborted for testSpe.f90 (code 1)
>
> ifort version 17.04

Thanks very much for trying with ifort-17 (which I don't have access). The error message
does seem to suggest that the (v1 // v2) is not a (named) object with
the ALLOCATABLE attribute, so my "cat" routine is probably not invoked
for the second "//".

But this means that, with the above approach, one cannot write an
expression like v1 // (v2 // v3) to control the order of association
(unless one introduces intermediate variables like vtmp = v2 // v3; v = v1 // vtmp).

# Interestingly, PGI2017.4 (<-- sorry not the latest one...) with -Mallocatable=03
compiles (v1 // v2) // v3 successfully and gives the same result as v1 // v2 // v3.

---
Another attempt is to wrap an allocatable array into a type. Then, additional
parentheses seem to work. But clearly, this is more verbose than directly
defining such operators for allocatable arrays.

module utils
implicit none
interface operator (//)
module procedure cat_myarr
endinterface

type myarr_t
integer, allocatable :: x(:)
endtype
contains
function cat_myarr( a, b ) result( res )
type(myarr_t), intent(in) :: a, b
type(myarr_t) :: res
allocate( res % x( 0 ) )
if ( allocated( a % x ) ) res % x = [ res % x, a % x ]
if ( allocated( b % x ) ) res % x = [ res % x, b % x ]
endfunction
end

subroutine test()
use utils
implicit none
type(myarr_t) :: v1, v2, v3, ans1, ans2, ans3
v1 % x = [1]
! v2 % x = [2, 3]
v3 % x = [4, 5, 6]

ans1 = v1 // v2 // v3
ans2 = ( v1 // v2 ) // v3
ans3 = v1 // (( v2 // v3 ))

print *, "ans1 = ", ans1 % x
print *, "ans2 = ", ans2 % x
print *, "ans3 = ", ans3 % x
end

program main
call test()
end

Result (gfortran-8.2 and PGI2017.4):
ans1 = 1 4 5 6
ans2 = 1 4 5 6
ans3 = 1 4 5 6

Ron Shepard

unread,
Nov 13, 2018, 9:04:06 PM11/13/18
to
On 11/13/18 10:47 AM, spectrum wrote:
> But this means that, with the above approach, one cannot write an
> expression like v1 // (v2 // v3) to control the order of association
> (unless one introduces intermediate variables like vtmp = v2 // v3; v = v1 // vtmp).

My feeling is that you are trying to swim upstream with this approach.
Your problems are caused by the requirement that the input dummy arrays
are allocatable. If the dummy arguments were declared as regular assumed
shape arrays, then there would be no problem with your // operator.

In most situations in the rest of the language, allocatable arrays must
be allocated before you use them in expressions. If you stick to that
model, then your life is much simpler.

$.02 -Ron Shepard

FortranFan

unread,
Nov 14, 2018, 9:13:16 AM11/14/18
to
On Saturday, November 10, 2018 at 10:43:27 AM UTC-5, qol...@gmail.com wrote:

> .. in application code there is an additional wrinkle that I forgot to put in the original post: the arrays V1, V2 (etc) are allocatable, and any of them may be unallocated.
>
> Of course I realize now that the concatenation operator for characters would also fail if given unallocated strings, so my original example is not representative. Anyway, FWIW here is the function I wrote, ..


There is a school of thought which insists subroutines in Fortran, rather than function subprograms, are better suited for such needs, especially the one with "an additional wrinkle .. the arrays V1, V2 (etc) are allocatable, and any of them may be unallocated"

paul.rich...@gmail.com

unread,
Nov 14, 2018, 9:32:05 AM11/14/18
to

> With gfortran-8.2, this code seems to work with Line (*1) above,
> but fails when Line (*2) is uncommented. The error message is
>
> v = (v1 // v2) // v3 ! error (*2)
> 1
> Error: Operands of string concatenation operator at (1) are REAL(4)/REAL(4)
>
> So I'm wondering if I'm doing something wrong...?

Well, yes you are, as posted later in this thread, since the allocatable attribute is not carried through the parentheses and so there is an interface mismatch.

If // is replaced by .concat. for example, the error message is exactly the same. The interface search, therefore, is probably not falling through to try character concatenation. So I would conclude, without having looked yet at ~/gcc/fortran/interface.c, that the mismatch on the allocatable attribute is found but that the error message is the standard one for TKR checking. I will have a look to see what can be done to emit an improved error message.

Cheers

Paul

qol...@gmail.com

unread,
Nov 14, 2018, 11:12:40 AM11/14/18
to
Yes I am usually of that persuasion myself. If I was doing this starting now, I would probably implement it as a subroutine. However recently I have become infatuated with Fortran's array expression syntax, and the various built-in functions that support it... hence my original function.

FortranFan

unread,
Nov 14, 2018, 11:45:49 AM11/14/18
to
On Wednesday, November 14, 2018 at 11:12:40 AM UTC-5, qol...@gmail.com wrote:

> ..
>
> Yes I am usually of that persuasion myself. .. However recently I have become infatuated with Fortran's array expression syntax, and the various built-in functions that support it... hence my original function.
> ..


Ok but you're bringing in "an additional wrinkle" with unallocated objects which is *not supported* by anything intrinsic in the language.

Consider the canonical example of the array expression facility in the language introduced since Fortran 90:

C = A + B

But well it requires objects A and B to be allocated (assuming they have the corresponding attribute) in order to employ the intrinsic binary operator of '+' and the assignment.

What you have in mind does not "conform" to the language.

qol...@gmail.com

unread,
Nov 14, 2018, 12:38:56 PM11/14/18
to
Indeed I agree, it cannot be done reasonably using a simple assignment like you show, hence it needs a procedure. T thought that was obvious from my post on 10 November.
In our latest exchange, I thought we were discussing the merits of a subroutine versus a function.
0 new messages