- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This could easily be done with a subroutine, with no problems - -
I have three variable length arrays here,
I want to add the contents of arrays A and B to get array C.
The zeroth element tells the number of items in the array.
The problem is - I cant get the compiler to work re the calling routine.
I tried to keep this as simple as possible - there must be a special trick to make it compile properly ?
Maybe the compiler is not meant to do this? However, in the CALLED routine it compiles with no problem.
any clues ? See attached source file.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Your program is a long way from working. First off, you need IMPLICIT NONE in all program units to handle carelessly mismatched variable names. Then, since your function returns something that F77 could not (i.e. an array result) it needs its interface to be explicit in the caller. Also standard Fortran doesn't zero out arrays for you so you have to give them initial values yourself somehow. And the array assignment that captures the result of invocation of xadd is particularly problematic because function xadd doesn't know the true extents of its inputs because they are assumed size arrays (assumed shape arrays would have been a better fit for your usage) so either c has to be allocatable (but then your result ends up starting at index 1 instead of index 0) or you have to invoke xadd twice to get its specifications and value or you have to compute the size of the result separately, which is what I did.
module M implicit none contains function xadd(p,q) integer p(0:*),q(0:*),ip,np,nq,nx,ix integer xadd(0:max(p(0),q(0))) np=p(0) nq=q(0) nx=ubound(xadd,1) do ix=1,nx xadd(ix)=p(ix)+q(ix) enddo xadd(0)=nx end function end module M use M implicit none integer a(0:1000),b(0:1000),c(0:1000) integer i a(0) = 13 a(1:a(0)) = [(i,i=1,a(0))] a(a(0)+1:) = 0 b(0) = 17 b(1:b(0)) = [(i**2,i=1,b(0))] b(b(0)+1:) = 0 c(0:max(a(0),b(0)))=xadd(a,b) write(*,*) c(1:c(0)) end
Link Copied
- « Previous
-
- 1
- 2
- Next »
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@mecej4: thanks for the workaround and detecting the nonconformance. Indeed I should have changed the literal '10' in lines 29, 30, 35, 36, 41, and 42 to 'base' and put INTEGER(KIND(carry), PARAMETER :: base = 10 up there in the declarations. If I could submit bug reports I would for Quote #16.
@jimdempseyatthecove: I was so surprised by the drop in prices for Black Friday that I got a 50" 4K Samsung TV. Not all that great a TV because colors start to fade outside a narrow viewing angle and it only gets 4:2:0 chroma at 4K 60 Hz, but for programming 30 Hz is fine.
I forget the idiom for detecting carry on the Alpha 21164. Maybe it was something like:
subroutine cadd(a,b,carry,c) use ISO_FORTRAN_ENV implicit none integer(INT64), intent(in) :: a, b integer(INT64), intent(inout) :: carry integer(INT64), intent(out) :: c integer(INT64), parameter :: H = MASKL(1,INT64) c = a+b+carry carry = 0 if(IEOR(H,c) < IEOR(H,IOR(a,b))) carry = 1 end subroutine cadd
No, compiling with /FA /c /O3 doesn't do any magic with the above. It would be nice if Intel compiled a list of idioms for common operations like right shift (but I see that f2008 adds SHIFTR, so never mind) carry and borrow detection, and double-wide multiplication and division that the compiler recognizes and turns into a single machine instruction so that the programmer wouldn't have to play a guessing game or poke machine language into memory and invoke it to get maximum performance.
@billsincl: The instruction c = xadd(a,b) always copies 1001 elements even if only a dozen or so are meaningful. Since GMP is designed to be used from C and it doesn't seem to return structures, at least for the integer functions, you might have better success using f2003 C interoperability to interface with that package instead of trying to reinvent the wheel if you are trying to get productive quickly with bignum arithmetic.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
RO, I will investigate the issue you raised. I'm not yet convinced this is a bug.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ok, now I'm convinced. Escalated as issue DPD200365326. The generic interface is somehow triggering the problem. Another workaround is to use a RESULT clause, like this:
function plus(a,b)result (res) type(MyBigInt), intent(in) :: a, b type(MyBigInt) res integer(kind(res%Data)) carry integer i if(a%Sign /= b%Sign) then ! Insert logic to handle subtraction else res%Sign = a%Sign allocate(res%Data(max(a%NUsed,b%NUsed)+1)) carry = 0 do i = 1, min(a%Nused,b%NUsed) carry = carry+a%Data(i)+b%Data(i) res%Data(i) = modulo(carry,10) carry = carry/10 end do if(a%NUsed > b%NUsed) then do i = i, a%NUsed carry = carry+a%Data(i) res%Data(i) = modulo(carry,10) carry = carry/10 end do else if(b%NUsed > a%NUsed) then do i = i, b%NUsed carry = carry+b%Data(i) res%Data(i) = modulo(carry,10) carry = carry/10 end do end if if(carry == 0) then res%NUsed = i-1 else res%NUsed = i res%Data(i) = carry end if end if end function plus
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve, please consider the other issue raised by RO's program and bug: IFort does not issue warnings for references to the intrinsic function MODULE with arguments of different kind, even with /warn:all /stand.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Eh?
C:\Projects>ifort /stand U538733A.f90 Intel(R) Visual Fortran Intel(R) 64 Compiler XE for applications running on Inte l(R) 64, Version 15.0.1.148 Build 20141023 Copyright (C) 1985-2014 Intel Corporation. All rights reserved. U538733A.f90(29): warning #7374: F2003 standard requires all arguments be of the same type and same kind type parameter. [CARRY] res%Data(i) = modulo(carry,10) ------------------------------------^ U538733A.f90(35): warning #7374: F2003 standard requires all arguments be of the same type and same kind type parameter. [CARRY] res%Data(i) = modulo(carry,10) ---------------------------------------^ U538733A.f90(41): warning #7374: F2003 standard requires all arguments be of the same type and same kind type parameter. [CARRY] res%Data(i) = modulo(carry,10) ---------------------------------------^
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
dear RO:
I guess you mean where I said A=C?
I agree, it would copy the entire array there, I thought you meant somewhere else.
In the original routines, I had XCPY which is selective about how many elements it transfers over.
I was just simplifying for clarity's sake.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel wrote:You are correct. Sorry, I got the different versions of RO's file mixed up.
Eh?
- 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
Because you said "integer function" and then used integer again. The error message is perhaps not the best, but it is an error.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yeah, I was being redundant there -
But maybe the compiler boys could clarify the error message at least?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Well, it has to complain about something - it first noticed that it was a scalar, but I will ask the compiler gals (as it would be one of the gals in this case) if a better clue could be given.
The Fortran language doesn't allow you to be redundant in declarations, with limited exceptions. A given attribute may be specified only once.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for checking out this issue, Steve. Another workaround is to shuffle things around a little so that the compiler doesn't know that function plus is going to be given a generic name at the time it's compiled:
module M0 use ISO_FORTRAN_ENV implicit none private type, public :: MyBigInt integer NUsed integer Sign integer(INT8), allocatable :: Data(:) end type MyBigInt public plus contains function plus(a,b) type(MyBigInt), intent(in) :: a, b type(MyBigInt) plus integer(kind(plus%Data)) carry integer i if(a%Sign /= b%Sign) then ! Insert logic to handle subtraction else plus%Sign = a%Sign allocate(plus%Data(max(a%NUsed,b%NUsed)+1)) carry = 0 do i = 1, min(a%Nused,b%NUsed) carry = carry+a%Data(i)+b%Data(i) plus%Data(i) = modulo(carry,10) carry = carry/10 end do if(a%NUsed > b%NUsed) then do i = i, a%NUsed carry = carry+a%Data(i) plus%Data(i) = modulo(carry,10) carry = carry/10 end do else if(b%NUsed > a%NUsed) then do i = i, b%NUsed carry = carry+b%Data(i) plus%Data(i) = modulo(carry,10) carry = carry/10 end do end if if(carry == 0) then plus%NUsed = i-1 else plus%NUsed = i plus%Data(i) = carry end if end if end function plus end module M0 module M use M0 implicit none private plus interface operator(+) module procedure plus end interface operator(+) end module M program P use M use ISO_FORTRAN_ENV implicit none type(MyBigInt) a, b, c integer i integer(INT8) temp a%Sign = 1 ! Positive a%NUsed = 13 allocate(a%Data(a%NUsed)) temp = 3 do i = 1, a%NUsed a%Data(i) = temp temp = modulo(3*temp,10) end do write(*,*) 'a = ',merge('-','+',a%Sign == -1),a%Data(1:a%NUsed) b%Sign = 1 ! Positive b%NUsed = 17 allocate(b%Data(b%NUsed)) temp = 7 do i = 1, b%NUsed b%Data(i) = temp temp = modulo(7*temp,10) end do write(*,*) 'b = ',merge('-','+',b%Sign == -1),b%Data(1:b%NUsed) c = a+b write(*,*) 'c = ',merge('-','+',c%Sign == -1),c%Data(1:c%NUsed) end program P
The above works in ifort. But any generic name triggers the error, not just operator(+). If in Quote #16 you changed 'operator(+)' to a name such as 'generic' and then changed 'c = a+b' to 'c = generic(a,b)' the error persists.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I agree - it is simply a generic declaration naming plus as a specific that triggers the error. We'll fix it.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This reminds me of a story by Donald Knuth -
A guy walks into a tailor store, and gives the tailor a coat to measure.
In one week, he comes back and notices one sleeve is three inches too short.
The tailor says "Well, if you scrunch up your shoulder like this, and walk 45 degrees twisted like this, etc. etc."
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The problem RO noted in reply 16 will be fixed for the 16.0 release.

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page
- « Previous
-
- 1
- 2
- Next »