Ignore:
Timestamp:
Jan 5, 2021 11:21:41 AM (3 years ago)
Author:
Giersch
Message:

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/pmc_general_mod.f90

    r4649 r4828  
    1515! <http://www.gnu.org/licenses/>.
    1616!
    17 ! Copyright 1997-2020 Leibniz Universitaet Hannover
     17! Copyright 1997-2021 Leibniz Universitaet Hannover
    1818!--------------------------------------------------------------------------------------------------!
    1919!
     
    2626! -----------------
    2727! $Id$
     28! Interface pmc_sort removed. Subroutine description added.
     29!
     30! 4649 2020-08-25 12:11:17Z raasch
    2831! File re-formatted to follow the PALM coding standard
    2932!
     
    143146    END INTERFACE pmc_g_setname
    144147
    145     INTERFACE pmc_sort
    146        MODULE PROCEDURE sort_2d_i
    147     END INTERFACE pmc_sort
    148 
    149     PUBLIC pmc_g_setname, pmc_sort
     148    PUBLIC pmc_g_setname
    150149
    151150 CONTAINS
    152151
    153 !--------------------------------------------------------------------------------------------------!
     152!---------------------------------------------------------------------------------------------------!
    154153! Description:
    155154! ------------
    156 !> @Todo: Missing subroutine description.
    157 !--------------------------------------------------------------------------------------------------!
     155!> Add array to list of arraydef structure. No the arra "name" is schedules for parent child transfer
     156!---------------------------------------------------------------------------------------------------!
    158157 SUBROUTINE pmc_g_setname( mychild, couple_index, aname )
    159158
     
    182181 END SUBROUTINE pmc_g_setname
    183182
    184 
    185 !--------------------------------------------------------------------------------------------------!
    186 ! Description:
    187 ! ------------
    188 !> @Todo: Missing subroutine description.
    189 !--------------------------------------------------------------------------------------------------!
    190  SUBROUTINE sort_2d_i( array, sort_ind )
    191 
    192     IMPLICIT NONE
    193 
    194     INTEGER(iwp), INTENT(IN)                    ::  sort_ind
    195     INTEGER(iwp), DIMENSION(:,:), INTENT(INOUT) ::  array
    196 
    197     INTEGER(iwp) ::  i  !<
    198     INTEGER(iwp) ::  j  !<
    199     INTEGER(iwp) ::  n  !<
    200 
    201     INTEGER(iwp), DIMENSION(SIZE(array,1)) ::  tmp  !<
    202 
    203     n = SIZE( array, 2 )
    204     DO  j = 1, n-1
    205        DO  i = j+1, n
    206           IF ( array(sort_ind,i) < array(sort_ind,j) )  THEN
    207              tmp = array(:,i)
    208              array(:,i) = array(:,j)
    209              array(:,j) = tmp
    210           ENDIF
    211        ENDDO
    212     ENDDO
    213 
    214  END  SUBROUTINE sort_2d_i
    215 
    216183#endif
    217184 END MODULE pmc_general
Note: See TracChangeset for help on using the changeset viewer.