OpenCMISS-Iron Internal API Documentation
sorting.f90
Go to the documentation of this file.
1 
43 
45 MODULE sorting
46 
47  USE base_routines
48  USE constants
49  USE kinds
51 
52 #include "macros.h"
53 
54  IMPLICIT NONE
55 
56  PRIVATE
57 
58  !Module parameters
59 
60  !Module types
61 
62  !Interfaces
63 
64  INTERFACE bubble_isort
65  MODULE PROCEDURE bubble_isort_intg
66  MODULE PROCEDURE bubble_isort_sp
67  MODULE PROCEDURE bubble_isort_dp
68  END INTERFACE !BUBBLE_ISORT
69 
70  INTERFACE bubble_sort
71  MODULE PROCEDURE bubble_sort_intg
72  MODULE PROCEDURE bubble_sort_sp
73  MODULE PROCEDURE bubble_sort_dp
74  END INTERFACE !BUBBLE_SORT
75 
76  INTERFACE heap_sort
77  MODULE PROCEDURE heap_sort_intg
78  MODULE PROCEDURE heap_sort_sp
79  MODULE PROCEDURE heap_sort_dp
80  END INTERFACE !HEAP_SORT
81 
82  INTERFACE shell_sort
83  MODULE PROCEDURE shell_sort_intg
84  MODULE PROCEDURE shell_sort_sp
85  MODULE PROCEDURE shell_sort_dp
86  END INTERFACE !SHELL_SORT
87 
88  PUBLIC bubble_isort
90 
91 CONTAINS
92 
93  !
94  !================================================================================================================================
95  !
96 
97  !#### Generic-subroutine: BUBBLE_ISORT
98  !### Description:
99  !### Sorts a list into assending order using the bubble sort method, returning sorting index
100  !### Child-subroutines: BUBBLE_ISORT_INTG,BUBBLE_ISORT_SP,BUBBLE_ISORT_DP
101 
102  !
103  !================================================================================================================================
104  !
105 
106  SUBROUTINE bubble_isort_intg(A,IND,ERR,ERROR,*)
107 
108  !#### Subroutine: BUBBLE_ISORT_INTG
109  !### Description:
110  !### BUBBLE_ISORT_INTG performs a bubble sort on an integer list, returning sorting index
111  !### Parent-function: BUBBLE_ISORT
112 
113  !Argument variables
114  INTEGER(INTG), INTENT(INOUT) :: A(:)
115  INTEGER(INTG), INTENT(OUT) :: IND(:)
116  INTEGER(INTG), INTENT(OUT) :: ERR
117  TYPE(varying_string), INTENT(OUT) :: ERROR
118  !Local variables
119  INTEGER(INTG) :: FLAG,i,j,k,VALUE,IVALUE
120 
121  enters("BUBBLE_ISORT_INTG",err,error,*999)
122 
123  IF(SIZE(ind,1)==SIZE(a,1)) THEN
124  ind(1)=1
125  IF(SIZE(a,1)>1) THEN
126  flag=SIZE(a,1)
127  DO i=1,SIZE(a,1)
128  k=flag-1
129  flag=0
130  DO j=1,k
131  IF(i==1) ind(j+1)=j+1
132  IF(a(j)>a(j+1)) THEN
133  VALUE=a(j)
134  a(j)=a(j+1)
135  a(j+1)=VALUE
136  ivalue=ind(j)
137  ind(j)=ind(j+1)
138  ind(j+1)=ivalue
139  flag=j
140  ENDIF
141  ENDDO
142  IF(flag==0) EXIT
143  ENDDO
144  ENDIF
145  ELSE
146  CALL flagerror("Size of input vectors does not match",err,error,*999)
147  ENDIF
148 
149  exits("BUBBLE_ISORT_INTG")
150  RETURN
151 999 errorsexits("BUBBLE_ISORT_INTG",err,error)
152  RETURN 1
153  END SUBROUTINE bubble_isort_intg
154 
155  !
156  !================================================================================================================================
157  !
158 
159  SUBROUTINE bubble_isort_sp(A,IND,ERR,ERROR,*)
160 
161  !#### Subroutine: BUBBLE_ISORT_SP
162  !### Description:
163  !### BUBBLE_ISORT_SP performs a bubble sort on a single precision list, returning sorting index
164  !### Parent-function: BUBBLE_ISORT
165 
166  !Argument variables
167  REAL(SP), INTENT(INOUT) :: A(:)
168  INTEGER(INTG), INTENT(OUT) :: IND(:)
169  INTEGER(INTG), INTENT(OUT) :: ERR
170  TYPE(varying_string), INTENT(OUT) :: ERROR
171  !Local variables
172  INTEGER(INTG) :: FLAG,i,j,k,IVALUE
173  REAL(SP) :: VALUE
174 
175  enters("BUBBLE_ISORT_SP",err,error,*999)
176 
177  IF(SIZE(ind,1)==SIZE(a,1)) THEN
178  ind(1)=1
179  IF(SIZE(a,1)>1) THEN
180  flag=SIZE(a,1)
181  DO i=1,SIZE(a,1)
182  k=flag-1
183  flag=0
184  DO j=1,k
185  IF(i==1) ind(j+1)=j+1
186  IF(a(j)>a(j+1)) THEN
187  VALUE=a(j)
188  a(j)=a(j+1)
189  a(j+1)=VALUE
190  ivalue=ind(j)
191  ind(j)=ind(j+1)
192  ind(j+1)=ivalue
193  flag=j
194  ENDIF
195  ENDDO
196  IF(flag==0) EXIT
197  ENDDO
198  ENDIF
199  ELSE
200  CALL flagerror("Size of input vectors does not match",err,error,*999)
201  ENDIF
202 
203  exits("BUBBLE_ISORT_SP")
204  RETURN
205 999 errorsexits("BUBBLE_ISORT_SP",err,error)
206  RETURN 1
207  END SUBROUTINE bubble_isort_sp
208 
209  !
210  !================================================================================================================================
211  !
212 
213  SUBROUTINE bubble_isort_dp(A,IND,ERR,ERROR,*)
214 
215  !#### Subroutine: BUBBLE_ISORT_DP
216  !### Description:
217  !### BUBBLE_ISORT_DP performs a bubble sort on a double precision list, returning sorting index
218  !### Parent-function: BUBBLE_ISORT
219 
220  !Argument variables
221  REAL(DP), INTENT(INOUT) :: A(:)
222  INTEGER(INTG), INTENT(OUT) :: IND(:)
223  INTEGER(INTG), INTENT(OUT) :: ERR
224  TYPE(varying_string), INTENT(OUT) :: ERROR
225  !Local variables
226  INTEGER(INTG) :: FLAG,i,j,k,IVALUE
227  REAL(DP) :: VALUE
228 
229  enters("BUBBLE_ISORT_DP",err,error,*999)
230 
231  IF(SIZE(ind,1)==SIZE(a,1)) THEN
232  ind(1)=1
233  IF(SIZE(a,1)>1) THEN
234  flag=SIZE(a,1)
235  DO i=1,SIZE(a,1)
236  k=flag-1
237  flag=0
238  DO j=1,k
239  IF(i==1) ind(j+1)=j+1
240  IF(a(j)>a(j+1)) THEN
241  VALUE=a(j)
242  a(j)=a(j+1)
243  a(j+1)=VALUE
244  ivalue=ind(j)
245  ind(j)=ind(j+1)
246  ind(j+1)=ivalue
247  flag=j
248  ENDIF
249  ENDDO
250  IF(flag==0) EXIT
251  ENDDO
252  ENDIF
253  ELSE
254  CALL flagerror("Size of input vectors does not match",err,error,*999)
255  ENDIF
256 
257  exits("BUBBLE_ISORT_DP")
258  RETURN
259 999 errorsexits("BUBBLE_ISORT_DP",err,error)
260  RETURN 1
261  END SUBROUTINE bubble_isort_dp
262 
263  !
264  !================================================================================================================================
265  !
266 
267  !#### Generic-subroutine: BUBBLE_SORT
268  !### Description:
269  !### Sorts a list into assending order using the bubble sort method.
270  !### Child-subroutines: BUBBLE_SORT_INTG,BUBBLE_SORT_SP,BUBBLE_SORT_DP
271 
272  !
273  !================================================================================================================================
274  !
275 
276  SUBROUTINE bubble_sort_intg(A,ERR,ERROR,*)
277 
278  !#### Subroutine: BUBBLE_SORT_INTG
279  !### Description:
280  !### BUBBLE_SORT_INTG performs a bubble sort on an integer list
281  !### Parent-function: BUBBLE_SORT
282 
283  !Argument variables
284  INTEGER(INTG), INTENT(INOUT) :: A(:)
285  INTEGER(INTG), INTENT(OUT) :: ERR
286  TYPE(varying_string), INTENT(OUT) :: ERROR
287  !Local variables
288  INTEGER(INTG) :: FLAG,i,j,k,VALUE
289 
290  enters("BUBBLE_SORT_INTG",err,error,*999)
291 
292  IF(SIZE(a,1)>1) THEN
293  flag=SIZE(a,1)
294  DO i=1,SIZE(a,1)
295  k=flag-1
296  flag=0
297  DO j=1,k
298  IF(a(j)>a(j+1)) THEN
299  VALUE=a(j)
300  a(j)=a(j+1)
301  a(j+1)=VALUE
302  flag=j
303  ENDIF
304  ENDDO
305  IF(flag==0) EXIT
306  ENDDO
307  ENDIF
308 
309  exits("BUBBLE_SORT_INTG")
310  RETURN
311 999 errorsexits("BUBBLE_SORT_INTG",err,error)
312  RETURN 1
313  END SUBROUTINE bubble_sort_intg
314 
315  !
316  !================================================================================================================================
317  !
318 
319  SUBROUTINE bubble_sort_sp(A,ERR,ERROR,*)
320 
321  !#### Subroutine: BUBBLE_SORT_SP
322  !### Description:
323  !### BUBBLE_SORT_SP performs a bubble sort on a single precision list
324  !### Parent-function: BUBBLE_SORT
325 
326  !Argument variables
327  REAL(SP), INTENT(INOUT) :: A(:)
328  INTEGER(INTG), INTENT(OUT) :: ERR
329  TYPE(varying_string), INTENT(OUT) :: ERROR
330  !Local variables
331  INTEGER(INTG) :: FLAG,i,j,k
332  REAL(SP) :: VALUE
333 
334  enters("BUBBLE_SORT_SP",err,error,*999)
335 
336  IF(SIZE(a,1)>1) THEN
337  flag=SIZE(a,1)
338  DO i=1,SIZE(a,1)
339  k=flag-1
340  flag=0
341  DO j=1,k
342  IF(a(j)>a(j+1)) THEN
343  VALUE=a(j)
344  a(j)=a(j+1)
345  a(j+1)=VALUE
346  flag=j
347  ENDIF
348  ENDDO
349  IF(flag==0) EXIT
350  ENDDO
351  ENDIF
352 
353  exits("BUBBLE_SORT_SP")
354  RETURN
355 999 errorsexits("BUBBLE_SORT_SP",err,error)
356  RETURN 1
357  END SUBROUTINE bubble_sort_sp
358 
359  !
360  !================================================================================================================================
361  !
362 
363  SUBROUTINE bubble_sort_dp(A,ERR,ERROR,*)
364 
365  !#### Subroutine: BUBBLE_SORT_DP
366  !### Description:
367  !### BUBBLE_SORT_DP performs a bubble sort on a double precision list
368  !### Parent-function: BUBBLE_SORT
369 
370  !Argument variables
371  REAL(DP), INTENT(INOUT) :: A(:)
372  INTEGER(INTG), INTENT(OUT) :: ERR
373  TYPE(varying_string), INTENT(OUT) :: ERROR
374  !Local variables
375  INTEGER(INTG) :: FLAG,i,j,k
376  REAL(DP) :: VALUE
377 
378  enters("BUBBLE_SORT_DP",err,error,*999)
379 
380  IF(SIZE(a,1)>1) THEN
381  flag=SIZE(a,1)
382  DO i=1,SIZE(a,1)
383  k=flag-1
384  flag=0
385  DO j=1,k
386  IF(a(j)>a(j+1)) THEN
387  VALUE=a(j)
388  a(j)=a(j+1)
389  a(j+1)=VALUE
390  flag=j
391  ENDIF
392  ENDDO
393  IF(flag==0) EXIT
394  ENDDO
395  ENDIF
396 
397  exits("BUBBLE_SORT_DP")
398  RETURN
399 999 errorsexits("BUBBLE_SORT_DP",err,error)
400  RETURN 1
401  END SUBROUTINE bubble_sort_dp
402 
403  !
404  !================================================================================================================================
405  !
406 
407  !#### Generic-subroutine: HEAP_SORT
408  !### Description:
409  !### Sorts a list into assending order using the heap sort method.
410  !### Child-subroutines: HEAP_SORT_INTG,HEAP_SORT_SP,HEAP_SORT_DP
411 
412  !
413  !================================================================================================================================
414  !
415 
416  SUBROUTINE heap_sort_intg(A,ERR,ERROR,*)
417 
418  !#### Subroutine: HEAP_SORT_INTG
419  !### Description:
420  !### HEAP_SORT_INTG performs a heap sort on an integer list
421  !### Parent-function: HEAP_SORT
422 
423  !Argument variables
424  INTEGER(INTG), INTENT(INOUT) :: A(:)
425  INTEGER(INTG), INTENT(OUT) :: ERR
426  TYPE(varying_string), INTENT(OUT) :: ERROR
427  !Local variables
428  INTEGER(INTG) :: I,IVALUE,J,L,VALUE
429 
430  enters("HEAP_SORT_INTG",err,error,*999)
431 
432  IF(SIZE(a,1)>1) THEN
433  l=SIZE(a,1)/2+1
434  ivalue=SIZE(a,1)
435  DO
436  IF(l>1) THEN
437  l=l-1
438  VALUE=a(l)
439  ELSE
440  VALUE=a(ivalue)
441  a(ivalue)=a(1)
442  ivalue=ivalue-1
443  IF(ivalue==1) THEN
444  a(1)=VALUE
445  EXIT
446  ENDIF
447  ENDIF
448  i=l
449  j=l+l
450  DO WHILE(j<=ivalue)
451  IF(j<ivalue) THEN
452  IF(a(j)<a(j+1)) j=j+1
453  ENDIF
454  IF(VALUE<a(j)) THEN
455  a(i)=a(j)
456  i=j
457  j=j+j
458  ELSE
459  j=ivalue+1
460  ENDIF
461  ENDDO
462  a(i)=VALUE
463  ENDDO
464  ENDIF
465 
466  exits("HEAP_SORT_INTG")
467  RETURN
468 999 errorsexits("HEAP_SORT_INTG",err,error)
469  RETURN 1
470  END SUBROUTINE heap_sort_intg
471 
472  !
473  !================================================================================================================================
474  !
475 
476  SUBROUTINE heap_sort_sp(A,ERR,ERROR,*)
477 
478  !#### Subroutine: HEAP_SORT_SP
479  !### Description:
480  !### HEAP_SORT_SP performs a heap sort on a single precision list
481  !### Parent-function: HEAP_SORT
482 
483  !Argument variables
484  REAL(SP), INTENT(INOUT) :: A(:)
485  INTEGER(INTG), INTENT(OUT) :: ERR
486  TYPE(varying_string), INTENT(OUT) :: ERROR
487  !Local variables
488  INTEGER(INTG) :: I,IVALUE,J,L
489  REAL(SP) :: VALUE
490 
491  enters("HEAP_SORT_SP",err,error,*999)
492 
493  IF(SIZE(a,1)>1) THEN
494  l=SIZE(a,1)/2+1
495  ivalue=SIZE(a,1)
496  DO
497  IF(l>1) THEN
498  l=l-1
499  VALUE=a(l)
500  ELSE
501  VALUE=a(ivalue)
502  a(ivalue)=a(1)
503  ivalue=ivalue-1
504  IF(ivalue==1) THEN
505  a(1)=VALUE
506  EXIT
507  ENDIF
508  ENDIF
509  i=l
510  j=l+l
511  DO WHILE(j<=ivalue)
512  IF(j<ivalue) THEN
513  IF(a(j)<a(j+1)) j=j+1
514  ENDIF
515  IF(VALUE<a(j)) THEN
516  a(i)=a(j)
517  i=j
518  j=j+j
519  ELSE
520  j=ivalue+1
521  ENDIF
522  ENDDO
523  a(i)=VALUE
524  ENDDO
525  ENDIF
526 
527  exits("HEAP_SORT_SP")
528  RETURN
529 999 errorsexits("HEAP_SORT_SP",err,error)
530  RETURN 1
531  END SUBROUTINE heap_sort_sp
532 
533  !
534  !================================================================================================================================
535  !
536 
537  SUBROUTINE heap_sort_dp(A,ERR,ERROR,*)
538 
539  !#### Subroutine: HEAP_SORT_DP
540  !### Description:
541  !### HEAP_SORT_DP performs a heap sort on a double precision list
542  !### Parent-function: HEAP_SORT
543 
544  !Argument variables
545  REAL(DP), INTENT(INOUT) :: A(:)
546  INTEGER(INTG), INTENT(OUT) :: ERR
547  TYPE(varying_string), INTENT(OUT) :: ERROR
548  !Local variables
549  INTEGER(INTG) :: I,IVALUE,J,L
550  REAL(DP) :: VALUE
551 
552  enters("HEAP_SORT_DP",err,error,*999)
553 
554  IF(SIZE(a,1)>1) THEN
555  l=SIZE(a,1)/2+1
556  ivalue=SIZE(a,1)
557  DO
558  IF(l>1) THEN
559  l=l-1
560  VALUE=a(l)
561  ELSE
562  VALUE=a(ivalue)
563  a(ivalue)=a(1)
564  ivalue=ivalue-1
565  IF(ivalue==1) THEN
566  a(1)=VALUE
567  EXIT
568  ENDIF
569  ENDIF
570  i=l
571  j=l+l
572  DO WHILE(j<=ivalue)
573  IF(j<ivalue) THEN
574  IF(a(j)<a(j+1)) j=j+1
575  ENDIF
576  IF(VALUE<a(j)) THEN
577  a(i)=a(j)
578  i=j
579  j=j+j
580  ELSE
581  j=ivalue+1
582  ENDIF
583  ENDDO
584  a(i)=VALUE
585  ENDDO
586  ENDIF
587 
588  exits("HEAP_SORT_DP")
589  RETURN
590 999 errorsexits("HEAP_SORT_DP",err,error)
591  RETURN 1
592  END SUBROUTINE heap_sort_dp
593 
594  !
595  !================================================================================================================================
596  !
597 
598  !#### Generic-subroutine: SHELL_SORT
599  !### Description:
600  !### Sorts a list into either assending or descending order using the shell sort method.
601  !### Child-subroutines: SHELL_SORT_INTG,SHELL_SORT_SP,SHELL_SORT_DP
602 
603  !
604  !================================================================================================================================
605  !
606 
607  SUBROUTINE shell_sort_intg(A,ERR,ERROR,*)
608 
609  !#### Subroutine: SHELL_SORT_INTG
610  !### Description:
611  !### SHELL_SORT_INTG performs a shell sort on an integer list
612  !### Parent-function: SHELL_SORT
613 
614  !Argument variables
615  INTEGER(INTG), INTENT(INOUT) :: A(:)
616  INTEGER(INTG), INTENT(OUT) :: ERR
617  TYPE(varying_string), INTENT(OUT) :: ERROR
618  !Local variables
619  INTEGER(INTG) :: I,INC,J,VALUE
620 
621  enters("SHELL_SORT_INTG",err,error,*999)
622 
623  inc=4
624  DO WHILE(inc<=SIZE(a,1))
625  inc=3*inc+1
626  ENDDO
627  DO WHILE(inc>1)
628  inc=inc/3
629  DO i=inc+1,SIZE(a,1)
630  VALUE=a(i)
631  j=i
632  DO WHILE(a(j-inc)>VALUE)
633  a(j)=a(j-inc)
634  j=j-inc
635  IF(j<=inc) EXIT
636  ENDDO
637  a(j)=VALUE
638  ENDDO !i
639  ENDDO
640 
641  exits("SHELL_SORT_INTG")
642  RETURN
643 999 errorsexits("SHELL_SORT_INTG",err,error)
644  RETURN 1
645  END SUBROUTINE shell_sort_intg
646 
647  !
648  !================================================================================================================================
649  !
650 
651  SUBROUTINE shell_sort_sp(A,ERR,ERROR,*)
652 
653  !#### Subroutine: SHELL_SORT_SP
654  !### Description:
655  !### SHELL_SORT_SP performs a shell sort on a single precision list
656  !### Parent-function: SHELL_SORT
657 
658  !Argument variables
659  REAL(SP), INTENT(INOUT) :: A(:)
660  INTEGER(INTG), INTENT(OUT) :: ERR
661  TYPE(varying_string), INTENT(OUT) :: ERROR
662  !Local variables
663  INTEGER(INTG) :: I,INC,J
664  REAL(SP) :: VALUE
665 
666  enters("SHELL_SORT_SP",err,error,*999)
667 
668  inc=4
669  DO WHILE(inc<=SIZE(a,1))
670  inc=3*inc+1
671  ENDDO
672  DO WHILE(inc>1)
673  inc=inc/3
674  DO i=inc+1,SIZE(a,1)
675  VALUE=a(i)
676  j=i
677  DO WHILE(a(j-inc)>VALUE)
678  a(j)=a(j-inc)
679  j=j-inc
680  IF(j<=inc) EXIT
681  ENDDO
682  a(j)=VALUE
683  ENDDO !i
684  ENDDO
685 
686  exits("SHELL_SORT_SP")
687  RETURN
688 999 errorsexits("SHELL_SORT_SP",err,error)
689  RETURN 1
690  END SUBROUTINE shell_sort_sp
691 
692  !
693  !================================================================================================================================
694  !
695 
696  SUBROUTINE shell_sort_dp(A,ERR,ERROR,*)
697 
698  !#### Subroutine: SHELL_SORT_DP
699  !### Description:
700  !### SHELL_SORT_DP performs a shell sort on a double precision list
701  !### Parent-function: SHELL_SORT
702 
703  !Argument variables
704  REAL(DP), INTENT(INOUT) :: A(:)
705  INTEGER(INTG), INTENT(OUT) :: ERR
706  TYPE(varying_string), INTENT(OUT) :: ERROR
707  !Local variables
708  INTEGER(INTG) :: I,INC,J
709  REAL(DP) :: VALUE
710 
711  enters("SHELL_SORT_DP",err,error,*999)
712 
713  inc=4
714  DO WHILE(inc<=SIZE(a,1))
715  inc=3*inc+1
716  ENDDO
717  DO WHILE(inc>1)
718  inc=inc/3
719  DO i=inc+1,SIZE(a,1)
720  VALUE=a(i)
721  j=i
722  DO WHILE(a(j-inc)>VALUE)
723  a(j)=a(j-inc)
724  j=j-inc
725  IF(j<=inc) EXIT
726  ENDDO
727  a(j)=VALUE
728  ENDDO !i
729  ENDDO
730 
731  exits("SHELL_SORT_DP")
732  RETURN
733 999 errorsexits("SHELL_SORT_DP",err,error)
734  RETURN 1
735  END SUBROUTINE shell_sort_dp
736 
737  !
738  !================================================================================================================================
739  !
740 
741 END MODULE sorting
subroutine, public enters(NAME, ERR, ERROR,)
Records the entry into the named procedure and initialises the error code.
subroutine heap_sort_intg(A, ERR, ERROR,)
Definition: sorting.f90:417
subroutine shell_sort_sp(A, ERR, ERROR,)
Definition: sorting.f90:652
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
This module contains all program wide constants.
Definition: constants.f90:45
subroutine bubble_sort_intg(A, ERR, ERROR,)
Definition: sorting.f90:277
subroutine shell_sort_intg(A, ERR, ERROR,)
Definition: sorting.f90:608
subroutine bubble_isort_dp(A, IND, ERR, ERROR,)
Definition: sorting.f90:214
subroutine, public exits(NAME)
Records the exit out of the named procedure.
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
subroutine heap_sort_sp(A, ERR, ERROR,)
Definition: sorting.f90:477
subroutine bubble_sort_dp(A, ERR, ERROR,)
Definition: sorting.f90:364
subroutine bubble_isort_sp(A, IND, ERR, ERROR,)
Definition: sorting.f90:160
subroutine bubble_sort_sp(A, ERR, ERROR,)
Definition: sorting.f90:320
This module contains all procedures for sorting. NOTE: THE ROUTINES IN THIS MODULE HAVE NOT BEEN TEST...
Definition: sorting.f90:45
subroutine heap_sort_dp(A, ERR, ERROR,)
Definition: sorting.f90:538
subroutine bubble_isort_intg(A, IND, ERR, ERROR,)
Definition: sorting.f90:107
Flags an error condition.
subroutine shell_sort_dp(A, ERR, ERROR,)
Definition: sorting.f90:697
This module contains all kind definitions.
Definition: kinds.f90:45