@@ -153,23 +153,23 @@ program test_sorting
153153! test the sorting routines on the test arrays
154154 ltest = .true.
155155
156- call test_int_ord_sorts( ldummy ); ltest = (ltest .and. ldummy)
156+ call test_int_ord_sorts( ldummy ); ltest = (ltest .and. ldummy)
157157
158- call test_char_ord_sorts(ldummy ); ltest = (ltest .and. ldummy)
158+ call test_char_ord_sorts(ldummy ); ltest = (ltest .and. ldummy)
159159
160- call test_string_ord_sorts( ldummy ); ltest = (ltest .and. ldummy)
160+ call test_string_ord_sorts( ldummy ); ltest = (ltest .and. ldummy)
161161
162- call test_int_sorts( ldummy ); ltest = (ltest .and. ldummy)
162+ call test_int_sorts( ldummy ); ltest = (ltest .and. ldummy)
163163
164- call test_char_sorts( ldummy ); ltest = (ltest .and. ldummy)
164+ call test_char_sorts( ldummy ); ltest = (ltest .and. ldummy)
165165
166- call test_string_sorts( ldummy ); ltest = (ltest .and. ldummy)
166+ call test_string_sorts( ldummy ); ltest = (ltest .and. ldummy)
167167
168- call test_int_sort_indexes( )
168+ call test_int_sort_indexes( ldummy ); ltest = (ltest .and. ldummy )
169169
170- call test_char_sort_indexes( )
170+ call test_char_sort_indexes( ldummy ); ltest = (ltest .and. ldummy )
171171
172- call test_string_sort_indexes( )
172+ call test_string_sort_indexes( ldummy ); ltest = (ltest .and. ldummy )
173173
174174
175175 call check(ltest)
@@ -207,7 +207,7 @@ end subroutine test_int_ord_sorts
207207
208208 subroutine test_int_ord_sort ( a , a_name , ltest )
209209 integer (int32), intent (in ) :: a(:)
210- character (* ), intent (in ) :: a_name
210+ character (* ), intent (in ) :: a_name
211211 logical , intent (out ) :: ltest
212212
213213 integer (int64) :: t0, t1, tdiff
@@ -397,7 +397,7 @@ subroutine test_string_ord_sort( a, a_name, ltest )
397397 write (* ,' (a, 2(1x,a))' ) ' string_dummy(i-1:i) = ' , &
398398 string_dummy(i-1 :i)
399399 end if
400-
400+
401401 string_dummy = a
402402 call ord_sort( string_dummy, reverse = .true. )
403403
@@ -546,7 +546,7 @@ subroutine test_char_sort( a, a_name, ltest )
546546 write (* ,* ) ' i = ' , i
547547 write (* ,' (a17, 2(1x,a4))' ) ' char_dummy(i-1:i) = ' , char_dummy(i-1 :i)
548548 end if
549-
549+
550550 end subroutine test_char_sort
551551
552552 subroutine test_string_sorts ( ltest )
@@ -614,29 +614,46 @@ subroutine test_string_sort( a, a_name, ltest )
614614
615615 end subroutine test_string_sort
616616
617- subroutine test_int_sort_indexes ( )
617+ subroutine test_int_sort_indexes ( ltest )
618+ logical , intent (out ) :: ltest
619+
620+ logical :: ldummy
618621
619- call test_int_sort_index( blocks, " Blocks" )
620- call test_int_sort_index( decrease, " Decreasing" )
621- call test_int_sort_index( identical, " Identical" )
622- call test_int_sort_index( increase, " Increasing" )
623- call test_int_sort_index( rand1, " Random dense" )
624- call test_int_sort_index( rand2, " Random order" )
625- call test_int_sort_index( rand0, " Random sparse" )
626- call test_int_sort_index( rand3, " Random 3" )
627- call test_int_sort_index( rand10, " Random 10" )
622+ ltest = .true.
623+
624+ call test_int_sort_index( blocks, " Blocks" , ldummy )
625+ ltest = (ltest .and. ldummy)
626+ call test_int_sort_index( decrease, " Decreasing" , ldummy )
627+ ltest = (ltest .and. ldummy)
628+ call test_int_sort_index( identical, " Identical" , ldummy )
629+ ltest = (ltest .and. ldummy)
630+ call test_int_sort_index( increase, " Increasing" , ldummy )
631+ ltest = (ltest .and. ldummy)
632+ call test_int_sort_index( rand1, " Random dense" , ldummy )
633+ ltest = (ltest .and. ldummy)
634+ call test_int_sort_index( rand2, " Random order" , ldummy )
635+ ltest = (ltest .and. ldummy)
636+ call test_int_sort_index( rand0, " Random sparse" , ldummy )
637+ ltest = (ltest .and. ldummy)
638+ call test_int_sort_index( rand3, " Random 3" , ldummy )
639+ ltest = (ltest .and. ldummy)
640+ call test_int_sort_index( rand10, " Random 10" , ldummy )
641+ ltest = (ltest .and. ldummy)
628642
629643 end subroutine test_int_sort_indexes
630644
631- subroutine test_int_sort_index ( a , a_name )
645+ subroutine test_int_sort_index ( a , a_name , ltest )
632646 integer (int32), intent (inout ) :: a(:)
633647 character (* ), intent (in ) :: a_name
648+ logical , intent (out ) :: ltest
634649
635650 integer (int64) :: t0, t1, tdiff
636651 real (dp) :: rate
637652 integer (int64) :: i
638653 logical :: valid
639654
655+ ltest = .true.
656+
640657 tdiff = 0
641658 do i = 1 , repeat
642659 dummy = a
@@ -649,6 +666,7 @@ subroutine test_int_sort_index( a, a_name )
649666
650667 dummy = a(index)
651668 call verify_sort( dummy, valid, i )
669+ ltest = (ltest .and. valid)
652670 if ( .not. valid ) then
653671 write ( * , * ) " SORT_INDEX did not sort " // a_name // " ."
654672 write (* ,* ) ' i = ' , i
@@ -662,6 +680,7 @@ subroutine test_int_sort_index( a, a_name )
662680 call sort_index( dummy, index, work, iwork, reverse= .true. )
663681 dummy = a(index)
664682 call verify_reverse_sort( dummy, valid, i )
683+ ltest = (ltest .and. valid)
665684 if ( .not. valid ) then
666685 write ( * , * ) " SORT_INDEX did not reverse sort " // &
667686 a_name // " ."
@@ -671,23 +690,34 @@ subroutine test_int_sort_index( a, a_name )
671690
672691 end subroutine test_int_sort_index
673692
674- subroutine test_char_sort_indexes ( )
693+ subroutine test_char_sort_indexes ( ltest )
694+ logical , intent (out ) :: ltest
675695
676- call test_char_sort_index( char_decrease, " Char. Decrease" )
677- call test_char_sort_index( char_increase, " Char. Increase" )
678- call test_char_sort_index( char_rand, " Char. Random" )
696+ logical :: ldummy
697+
698+ ltest = .true.
699+
700+ call test_char_sort_index( char_decrease, " Char. Decrease" , ldummy )
701+ ltest = (ltest .and. ldummy)
702+ call test_char_sort_index( char_increase, " Char. Increase" , ldummy )
703+ ltest = (ltest .and. ldummy)
704+ call test_char_sort_index( char_rand, " Char. Random" , ldummy )
705+ ltest = (ltest .and. ldummy)
679706
680707 end subroutine test_char_sort_indexes
681708
682- subroutine test_char_sort_index ( a , a_name )
709+ subroutine test_char_sort_index ( a , a_name , ltest )
683710 character (len= 4 ), intent (in ) :: a(0 :)
684711 character (* ), intent (in ) :: a_name
712+ logical , intent (out ) :: ltest
685713
686714 integer (int64) :: t0, t1, tdiff
687715 real (dp) :: rate
688716 integer (int64) :: i
689717 logical :: valid
690718
719+ ltest = .true.
720+
691721 tdiff = 0
692722 do i = 1 , repeat
693723 char_dummy = a
@@ -699,6 +729,7 @@ subroutine test_char_sort_index( a, a_name )
699729 tdiff = tdiff/ repeat
700730
701731 call verify_char_sort( char_dummy, valid, i )
732+ ltest = (ltest .and. valid)
702733 if ( .not. valid ) then
703734 write ( * , * ) " SORT_INDEX did not sort " // a_name // " ."
704735 write (* ,* ) ' i = ' , i
@@ -710,23 +741,34 @@ subroutine test_char_sort_index( a, a_name )
710741
711742 end subroutine test_char_sort_index
712743
713- subroutine test_string_sort_indexes ( )
744+ subroutine test_string_sort_indexes ( ltest )
745+ logical , intent (out ) :: ltest
746+
747+ logical :: ldummy
714748
715- call test_string_sort_index( string_decrease, " String Decrease" )
716- call test_string_sort_index( string_increase, " String Increase" )
717- call test_string_sort_index( string_rand, " String Random" )
749+ ltest = .true.
750+
751+ call test_string_sort_index( string_decrease, " String Decrease" , ldummy )
752+ ltest = (ltest .and. ldummy)
753+ call test_string_sort_index( string_increase, " String Increase" , ldummy )
754+ ltest = (ltest .and. ldummy)
755+ call test_string_sort_index( string_rand, " String Random" , ldummy )
756+ ltest = (ltest .and. ldummy)
718757
719758 end subroutine test_string_sort_indexes
720759
721- subroutine test_string_sort_index ( a , a_name )
760+ subroutine test_string_sort_index ( a , a_name , ltest )
722761 type (string_type), intent (in ) :: a(0 :)
723762 character (* ), intent (in ) :: a_name
763+ logical , intent (out ) :: ltest
724764
725765 integer (int64) :: t0, t1, tdiff
726766 real (dp) :: rate
727767 integer (int64) :: i
728768 logical :: valid
729769
770+ ltest = .true.
771+
730772 tdiff = 0
731773 do i = 1 , repeat
732774 string_dummy = a
@@ -738,6 +780,7 @@ subroutine test_string_sort_index( a, a_name )
738780 tdiff = tdiff/ repeat
739781
740782 call verify_string_sort( string_dummy, valid, i )
783+ ltest = (ltest .and. valid)
741784 if ( .not. valid ) then
742785 write ( * , * ) " SORT_INDEX did not sort " // a_name // " ."
743786 write (* ,* ) ' i = ' , i
0 commit comments