replica nfl jerseysreplica nfl jerseyssoccer jerseyreplica nfl jerseys forums.silverfrost.com :: View topic - warning 676 in recursive routines
forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

warning 676 in recursive routines
Goto page 1, 2  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
steveDoyle



Joined: 04 Sep 2009
Posts: 117
Location: Manchester

PostPosted: Sat Dec 28, 2024 6:29 pm    Post subject: warning 676 in recursive routines Reply with quote

Hi , i have a recursive routine (quicksort) that works correctly but give argument type warnings. Am i doing something wrong or is this a glitch in the compiler

thanks

steve


RECURSIVE SUBROUTINE QUICKSORTDP_index(RARRAY,index, LOW, IHIGH)

INTEGER LOW, IHIGH, IPIVOT
DOUBLE PRECISION RARRAY( * )
integer index(*)

IF (LOW .LT. IHIGH) THEN
CALL QSRT_PARTITIONDP_index(RARRAY,index, LOW, IHIGH, IPIVOT)
CALL QUICKSORTDP_index(RARRAY,index, LOW, IPIVOT - 1)
CALL QUICKSORTDP_index(RARRAY,index, IPIVOT + 1, IHIGH)
ENDIF

end

D:\apps_cpi\sprint\sprint.FOR(1592) : warning 676 - In a call to QUICKSORTDP_INDEX from another procedure, the first argument was of type REAL(KIND=2), it is now REAL(KIND=2)
D:\apps_cpi\sprint\sprint.FOR(1592) : warning 676 - In a call to QUICKSORTDP_INDEX from another procedure, the second argument was of type INTEGER(KIND=3), it is now INTEGER(KIND=3)
D:\apps_cpi\sprint\sprint.FOR(1592) : warning 676 - In a call to QUICKSORTDP_INDEX from another procedure, the third argument was of type INTEGER(KIND=3), it is now INTEGER(KIND=3)
D:\apps_cpi\sprint\sprint.FOR(1592) : warning 676 - In a call to QUICKSORTDP_INDEX from another procedure, the fourth argument was of type INTEGER(KIND=3), it is now INTEGER(KIND=3)
Back to top
View user's profile Send private message
Kenneth_Smith



Joined: 18 May 2012
Posts: 753
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Sun Dec 29, 2024 10:00 am    Post subject: Reply with quote

Steve,

I am guessing here, but if QUICKSORTDP_index and QSRT_PARTITIONDP_index are not contained within a module, since you have assumed size arrays (*), then the recursive QUICKSORTDP_index requires an interface block for QSRT_PARTITIONDP_index.

Ken
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 8087
Location: Salford, UK

PostPosted: Sun Dec 29, 2024 10:59 am    Post subject: Reply with quote

Steve

Please provide a short main program that illustrates the issue.
Back to top
View user's profile Send private message AIM Address
steveDoyle



Joined: 04 Sep 2009
Posts: 117
Location: Manchester

PostPosted: Sun Dec 29, 2024 5:17 pm    Post subject: Reply with quote

Hi Paul

thanks for the response. here is a working example

regards

steve

program test
implicit none
integer iarray(7)
integer n_item,ij

n_item = 7
iarray(1) = 7
iarray(2) = 3
iarray(3) = 2
iarray(4) = 1
iarray(5) =4
iarray(6) = 9
iarray(7) = 6
call QUICKSORTI(IARRAY, 1, n_item)
do 10 ij = 1, n_item
write(*,*) ij , ' ' ,iarray(ij)
10 continue
end



RECURSIVE SUBROUTINE QUICKSORTI(IARRAY, LOW, IHIGH)
! =====================
IMPLICIT NONE
INTEGER IARRAY( * ), LOW, IHIGH, IPIVOT
IF (LOW .LT. IHIGH) THEN
CALL QSRT_PARTITIONI(IARRAY, LOW, IHIGH, IPIVOT)
CALL QUICKSORTI(IARRAY, LOW, IPIVOT - 1)
CALL QUICKSORTI(IARRAY, IPIVOT + 1, IHIGH)
ENDIF
END

SUBROUTINE QSRT_PARTITIONI(IARRAY, LOW, IHIGH, IPIVOT)
! ==========================
IMPLICIT NONE
INTEGER IARRAY( * ), LOW, IHIGH, IPIVOT, PIVOT_VALUE, I, J,temp
PIVOT_VALUE = IARRAY(IHIGH) ! Use the last element as pivot
I = LOW - 1
DO 10 J = LOW, IHIGH - 1
IF (IARRAY(J) .LE. PIVOT_VALUE) THEN
I = I + 1
TEMP = iarray(I)
iarray(I) = iarray(J)
iarray(J) = TEMP
ENDIF
10 CONTINUE
TEMP = iarray(I + 1)
iarray(I + 1) = iarray(iHIGH)
iarray(iHIGH) = TEMP
IPIVOT = I + 1
END
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 8087
Location: Salford, UK

PostPosted: Mon Dec 30, 2024 8:59 am    Post subject: Reply with quote

This is a false warning that has been removed for the next release of FTN95.
Back to top
View user's profile Send private message AIM Address
steveDoyle



Joined: 04 Sep 2009
Posts: 117
Location: Manchester

PostPosted: Mon Dec 30, 2024 9:16 am    Post subject: Reply with quote

Hi Paul

thanks for the quick response.

regards

steve
Back to top
View user's profile Send private message
Kenneth_Smith



Joined: 18 May 2012
Posts: 753
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Mon Dec 30, 2024 11:44 am    Post subject: Reply with quote

So my guess, was way out - again.

Adding (kind=3) to all integer declarations removes the warning.

Code:
program test
implicit none
integer(kind=3) iarray(7)
integer(kind=3) n_item,ij

n_item = 7
iarray(1) = 7
iarray(2) = 3
iarray(3) = 2
iarray(4) = 1
iarray(5) =4
iarray(6) = 9
iarray(7) = 6
call QUICKSORTI(IARRAY, 1, n_item)
do 10 ij = 1, n_item
write(*,*) ij , ' ' ,iarray(ij)
10 continue
end



RECURSIVE SUBROUTINE QUICKSORTI(IARRAY, LOW, IHIGH)
! =====================
IMPLICIT NONE
INTEGER(kind=3) IARRAY( * ), LOW, IHIGH, IPIVOT
IF (LOW .LT. IHIGH) THEN
CALL QSRT_PARTITIONI(IARRAY, LOW, IHIGH, IPIVOT)
CALL QUICKSORTI(IARRAY, LOW, IPIVOT - 1)
CALL QUICKSORTI(IARRAY, IPIVOT + 1, IHIGH)
ENDIF
END

SUBROUTINE QSRT_PARTITIONI(IARRAY, LOW, IHIGH, IPIVOT)
! ==========================
IMPLICIT NONE
INTEGER(kind=3) IARRAY( * ), LOW, IHIGH, IPIVOT, PIVOT_VALUE, I, J,temp
PIVOT_VALUE = IARRAY(IHIGH) ! Use the last element as pivot
I = LOW - 1
DO 10 J = LOW, IHIGH - 1
IF (IARRAY(J) .LE. PIVOT_VALUE) THEN
I = I + 1
TEMP = iarray(I)
iarray(I) = iarray(J)
iarray(J) = TEMP
ENDIF
10 CONTINUE
TEMP = iarray(I + 1)
iarray(I + 1) = iarray(iHIGH)
iarray(iHIGH) = TEMP
IPIVOT = I + 1
END
Back to top
View user's profile Send private message Visit poster's website
steveDoyle



Joined: 04 Sep 2009
Posts: 117
Location: Manchester

PostPosted: Mon Dec 30, 2024 3:24 pm    Post subject: Reply with quote

H i ken

thanks for the feedback

I still depend on some ancient fortran 77 code analysers (aka Luddite or too mean to invest in the latest products...) so i void using F95 syntax. If i need anything elaborate i tend to use C++

It is also easier for the junior engineers i work with to understand what is going on as their coding skills have drastically declined over the 40 old years I've been trying to get computers to do what is required

regards

steve
Back to top
View user's profile Send private message
arctica



Joined: 10 Sep 2006
Posts: 118
Location: United Kingdom

PostPosted: Mon Dec 30, 2024 4:39 pm    Post subject: Reply with quote

Hi Steve, ken,

The revised code runs as expected. I do think that keeping the f95 syntax clear and with plenty of comment lines makes for easier code for learners to follow.

My update to the code would have the terminations in place, e.g. end program test, end subroutine A etc. Also do loops are much cleaner in Fortran 95 now, where we can do the following:

do ij = 1, n_item
write(*,*) ij , ' ' ,iarray(ij)
end do

Good to highlight the recursive functionality.

Code tested on ftn95 version 9.05.0.0

Lester
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2601
Location: Sydney

PostPosted: Tue Dec 31, 2024 11:05 am    Post subject: Reply with quote

The high pivot selection fails badly if there is an ordered set of values.
I have enhanced the code to demonstrate this with real*8 values

Code:
  program testd
    implicit none
    real*8, allocatable :: varray(:)
    integer :: n_item,ij, ne, np, no,k
    logical :: echo_partition = .false.

    n_item = 88888000 

    write (*,11) delta_sec()
    Write (*, 10) 'Sort test for size = ',n_item
    allocate ( varray(n_item) )

   Write (*, 10, advance='NO') 'Initialising'
    n_item = size (varray)
    call random_number (varray )
    write (*,11) delta_sec()

  do k = 1,2    ! k=2 tests ordered set

   Write (*, 10, advance='NO') 'Sorting'
    np = 0
    no = 0

    call QUICKSORTD (vARRAY, 1, n_item)
    write (*,11) delta_sec()

    write (*,*) n_item,' items sorted'
    write (*,*) np,' partitions'
    write (*,*) no,' all shift'

   Write (*, 10, advance='NO') 'Checking'
    ne = 0
    do ij = 1, n_item-1
      if ( varray(ij) <= varray(ij+1) ) cycle
      write (*,*) ij , ' ' ,varray(ij),varray(ij+1)
      ne = ne+1
    end do
    write (*,11) delta_sec()
    write (*,*) ne,' order errors'

  end do
     
 10 format (/a,i0)
 11 format (2x,f0.4)

  contains
 
    RECURSIVE SUBROUTINE QUICKSORTD (DARRAY, LOW, IHIGH)
      IMPLICIT NONE
      real*8 :: DARRAY(*)
      INTEGER LOW, IHIGH, IPIVOT

      IF (LOW < IHIGH) THEN
        CALL QSRT_PARTITIOND (DARRAY, LOW, IHIGH, IPIVOT)
        CALL QUICKSORTD      (DARRAY, LOW,        IPIVOT - 1)
        CALL QUICKSORTD      (DARRAY, IPIVOT + 1, IHIGH)
      END IF

    END SUBROUTINE QUICKSORTD

    SUBROUTINE QSRT_PARTITIOND (DARRAY, LOW, HIGH, IPIVOT)
      IMPLICIT NONE
      real*8 :: DARRAY(*),  PIVOT_VALUE, dtemp
      INTEGER LOW, HIGH, IPIVOT, I, J, ns, nk
      logical :: use_mid_value = .true.

  !  mid value is much better for sorting an ordered set
      if ( use_mid_value ) then
        if ( high - low  > 1 ) then
          ipivot = (low+high) / 2
          dtemp  = darray(IPIVOT)
          darray(IPIVOT) = darray(HIGH)
          darray(HIGH)   = dtemp
        end if
      end if

      PIVOT_VALUE = DARRAY(HIGH) ! Use the last element as pivot

      I = LOW - 1
      ns = 0
      nk = 0
      DO J = LOW, HIGH - 1
        IF (DARRAY(J) > PIVOT_VALUE) CYCLE
        I = I + 1
        if ( i /= j ) then
          dtemp = darray(J)
          darray(J) = darray(I)
          darray(I) = dtemp
          ns = ns+1
        else
          nk = nk+1
        end if
      END DO

      IPIVOT = I + 1
      if ( IPIVOT /= HIGH ) then
        dtemp = darray(IPIVOT)
        darray(IPIVOT) = darray(HIGH)
        darray(HIGH)   = dtemp
        if ( echo_partition ) write (*,*) 'partition', LOW, HIGH, ns, nk
        np = np+1
      else
        if ( echo_partition ) write (*,*) 'no pivot switch', nk, high-low
        no = no+1
      end if

    END SUBROUTINE QSRT_PARTITIOND

    real function delta_sec ()
      integer*8 :: tick, rate, last_tick = 0
      real      :: sec
      call system_clock ( tick, rate )
      sec = real ( tick-last_tick ) / real ( rate )
      last_tick = tick
      delta_sec = sec
    end function delta_sec

  end program testd


see "use_mid_value = .true." but reduce n_item !
Back to top
View user's profile Send private message
arctica



Joined: 10 Sep 2006
Posts: 118
Location: United Kingdom

PostPosted: Tue Dec 31, 2024 2:09 pm    Post subject: Reply with quote

Thanks for sharing the revised code John.

Lester
Back to top
View user's profile Send private message
steveDoyle



Joined: 04 Sep 2009
Posts: 117
Location: Manchester

PostPosted: Tue Dec 31, 2024 3:37 pm    Post subject: Reply with quote

The quicksort theory states the worst case is for an ordered set

ref: https://www.geeksforgeeks.org/quick-sort-algorithm/

Time Complexity:

Best Case: (Ω(n log n)), Occurs when the pivot element divides the array into two equal halves.
Average Case (θ(n log n)), On average, the pivot divides the array into two parts, but not necessarily equal.
Worst Case: (O(n�)), Occurs when the smallest or largest element is always chosen as the pivot (e.g., sorted arrays).

i'll look at updating my code to use the mid value as the pivot

thanks

steve
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2601
Location: Sydney

PostPosted: Wed Jan 01, 2025 1:58 am    Post subject: Re: Reply with quote

steveDoyle wrote:
The quicksort theory states the worst case is for an ordered set


I am not sure of the source of that claim, however you can easily show the difference between "high" pivot and "mid_point" pivot with the program I provided.

"high" pivot fails badly for an ordered set of values, while
"mid_point" pivot removes the worst case is for an ordered set problem.

So to demonstrate this,
choose a smaller value for n_items, say 100000 (you will see why)
set use_mid_value = .false.
run with these options
then set use_mid_value = .true.

The statistics are interesting, which may take some time to understand.

The other main changes that can be done to the quick_sort are :
a) Include a bubble sort for when high-low < say 6. This can sometimes improve, but now only slightly with the latest FTN95 /64 compiler
b) convert to an indexed sort, so that the original "DARRAY"data is not altered. There was a time when swapping the index values was faster than swapping the darray values, but that has also gone away.
c) replace recursion with a partition list in a DO loop.

The sort I use has replaced recursion with a list of partition pairs, which replaced the recursive stack with a list of low/high.

The remaining problem with quick sort is how to split the list darray(low:high) into darray(low:pivot-1), darray(pivot) and darray(pivot+1:high) efficiently, while not loosing the previous order of values.
I have seen some use of the intrinsic PACK, which is neat, but not the most efficient for data movement, as it requires a double scan or temporary arrays to be merged.

I posted the program, as I thought the statistics it recovers are interesting, (and could be improved for the ordered case)
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2601
Location: Sydney

PostPosted: Wed Jan 01, 2025 9:47 am    Post subject: Reply with quote

I have created a variant of the indexed quick sort, which may be of interest.

This is:
An indexed sort that does not change the original data order.
This is still a recursive sort.
In the partitioning, I have experimented with the high-low lists where I overwrite the index(low:) with the values < pivot_value, but have a temporary array to store the high value pointers.
I have 2 versions of the partitioning; a temporary stack array for the array < 800 kBytes and an alternative heap array for larger tests. (Gfortran has a smaller stack problem, but FTN95 does not)
I have included a bubble sort for small partitions ( entries < 5 ), although it does not have as great affect that it did. (run times can vary a bit, independent of bubble size?)
I have allowed for different pivot selection.
I have included statistics to give some indication of the relative scan approaches and include identifying when a partition does not change the order of entries.
I have not paid attention to repeated values, which can be further sorted by their order in the list.

It may provide a platform to test some other alternatives or further investigate pivot selections.

I have always found quick_sort to be very robust, especially when choosing a central pivot value.

https://www.dropbox.com/scl/fi/eb0gvx4w0t2773ujwci74/steve_sort_id.f90?rlkey=uyutn439deehcvgee2iloqme4&st=s4d2gd6u&dl=0

Let me know if you find any improvements in this code.

John
Back to top
View user's profile Send private message
Kenneth_Smith



Joined: 18 May 2012
Posts: 753
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Wed Jan 01, 2025 10:55 am    Post subject: Reply with quote

John,

You might want to look at this implementation, which is the fastest I have seen for large data sets. It sorts the input array and also returns index values.

https://github.com/gher-uliege/OAK/blob/master/quicksort.f90
Back to top
View user's profile Send private message Visit poster's website
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Goto page 1, 2  Next
Page 1 of 2

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group