slo Subroutine

private subroutine slo(n, Indrow, Jpntr, Indcol, Ipntr, Ndeg, List, Maxclq, Iwa1, Iwa2, Iwa3, Iwa4)

given the sparsity pattern of an m by n matrix a, this subroutine determines the smallest-last ordering of the columns of a.

the smallest-last ordering is defined for the loopless graph g with vertices a(j), j = 1,2,...,n where a(j) is the j-th column of a and with edge (a(i),a(j)) if and only if columns i and j have a non-zero in the same row position.

the smallest-last ordering is determined recursively by letting list(k), k = n,...,1 be a column with least degree in the subgraph spanned by the un-ordered columns.

note that the value of m is not needed by slo and is therefore not present in the subroutine statement.

Arguments

Type IntentOptional Attributes Name
integer :: n

a positive integer input variable set to the number of columns of a.

integer, dimension(*) :: Indrow

an integer input array which contains the row indices for the non-zeroes in the matrix a.

integer, dimension(n+1) :: Jpntr

an integer input array of length n + 1 which specifies the locations of the row indices in indrow. the row indices for column j are indrow(k), k = jpntr(j),...,jpntr(j+1)-1. note that jpntr(n+1)-1 is then the number of non-zero elements of the matrix a.

integer, dimension(*) :: Indcol

an integer input array which contains the column indices for the non-zeroes in the matrix a.

integer, dimension(*) :: Ipntr

an integer input array of length m + 1 which specifies the locations of the column indices in indcol. the column indices for row i are indcol(k), k = ipntr(i),...,ipntr(i+1)-1. note that ipntr(m+1)-1 is then the number of non-zero elements of the matrix a.

integer, dimension(n) :: Ndeg

an integer input array of length n which specifies the degree sequence. the degree of the j-th column of a is ndeg(j).

integer, dimension(n) :: List

an integer output array of length n which specifies the smallest-last ordering of the columns of a. the j-th column in this order is list(j).

integer :: Maxclq

an integer output variable set to the size of the largest clique found during the ordering.

integer, dimension(0:n-1) :: Iwa1

integer work array of length n

integer, dimension(n) :: Iwa2

integer work array of length n

integer, dimension(n) :: Iwa3

integer work array of length n

integer, dimension(n) :: Iwa4

integer work array of length n


Called by

proc~~slo~~CalledByGraph proc~slo dsm_module::slo proc~dsm dsm_module::dsm proc~dsm->proc~slo proc~dsm_wrapper numerical_differentiation_module::sparsity_pattern%dsm_wrapper proc~dsm_wrapper->proc~dsm proc~compute_sparsity_random numerical_differentiation_module::compute_sparsity_random proc~compute_sparsity_random->proc~dsm_wrapper proc~compute_sparsity_random_2 numerical_differentiation_module::compute_sparsity_random_2 proc~compute_sparsity_random_2->proc~dsm_wrapper proc~set_sparsity_pattern numerical_differentiation_module::numdiff_type%set_sparsity_pattern proc~set_sparsity_pattern->proc~dsm_wrapper

Source Code

    subroutine slo(n,Indrow,Jpntr,Indcol,Ipntr,Ndeg,List,Maxclq,Iwa1, &
                   Iwa2,Iwa3,Iwa4)

    implicit none

    integer                  :: n         !! a positive integer input variable set to the number
                                          !! of columns of `a`.
    integer                  :: Maxclq    !! an integer output variable set to the size
                                          !! of the largest clique found during the ordering.
    integer,dimension(*)     :: Indrow    !! an integer input array which contains the row
                                          !! indices for the non-zeroes in the matrix `a`.
    integer,dimension(n+1)   :: Jpntr     !! an integer input array of length `n + 1` which
                                          !! specifies the locations of the row indices in `indrow`.
                                          !! the row indices for column `j` are
                                          !! `indrow(k), k = jpntr(j),...,jpntr(j+1)-1`.
                                          !! **note** that `jpntr(n+1)-1` is then the number of non-zero
                                          !! elements of the matrix `a`.
    integer,dimension(*)     :: Indcol    !! an integer input array which contains the
                                          !! column indices for the non-zeroes in the matrix `a`.
    integer,dimension(*)     :: Ipntr     !! an integer input array of length `m + 1` which
                                          !! specifies the locations of the column indices in `indcol`.
                                          !! the column indices for row `i` are
                                          !! `indcol(k), k = ipntr(i),...,ipntr(i+1)-1`.
                                          !! **note** that `ipntr(m+1)-1` is then the number of non-zero
                                          !! elements of the matrix `a`.
    integer,dimension(n)     :: Ndeg      !! an integer input array of length `n` which specifies
                                          !! the degree sequence. the degree of the `j`-th column
                                          !! of `a` is `ndeg(j)`.
    integer,dimension(n)     :: List      !! an integer output array of length `n` which specifies
                                          !! the smallest-last ordering of the columns of `a`. the `j`-th
                                          !! column in this order is `list(j)`.
    integer,dimension(0:n-1) :: Iwa1      !! integer work array of length `n`
    integer,dimension(n)     :: Iwa2      !! integer work array of length `n`
    integer,dimension(n)     :: Iwa3      !! integer work array of length `n`
    integer,dimension(n)     :: Iwa4      !! integer work array of length `n`

    integer :: ic , ip , ir , jcol , jp , mindeg , numdeg , numord

    ! INITIALIZATION BLOCK.

    mindeg = n
    do jp = 1 , n
        Iwa1(jp-1) = 0
        Iwa4(jp) = n
        List(jp) = Ndeg(jp)
        mindeg = min(mindeg,Ndeg(jp))
    enddo

    ! CREATE A DOUBLY-LINKED LIST TO ACCESS THE DEGREES OF THE
    ! COLUMNS. THE POINTERS FOR THE LINKED LIST ARE AS FOLLOWS.
    !
    ! EACH UN-ORDERED COLUMN IC IS IN A LIST (THE DEGREE LIST)
    ! OF COLUMNS WITH THE SAME DEGREE.
    !
    ! IWA1(NUMDEG) IS THE FIRST COLUMN IN THE NUMDEG LIST
    ! UNLESS IWA1(NUMDEG) = 0. IN THIS CASE THERE ARE
    ! NO COLUMNS IN THE NUMDEG LIST.
    !
    ! IWA2(IC) IS THE COLUMN BEFORE IC IN THE DEGREE LIST
    ! UNLESS IWA2(IC) = 0. IN THIS CASE IC IS THE FIRST
    ! COLUMN IN THIS DEGREE LIST.
    !
    ! IWA3(IC) IS THE COLUMN AFTER IC IN THE DEGREE LIST
    ! UNLESS IWA3(IC) = 0. IN THIS CASE IC IS THE LAST
    ! COLUMN IN THIS DEGREE LIST.
    !
    ! IF IC IS AN UN-ORDERED COLUMN, THEN LIST(IC) IS THE
    ! DEGREE OF IC IN THE GRAPH INDUCED BY THE UN-ORDERED
    ! COLUMNS. IF JCOL IS AN ORDERED COLUMN, THEN LIST(JCOL)
    ! IS THE SMALLEST-LAST ORDER OF COLUMN JCOL.

    do jp = 1 , n
        numdeg = Ndeg(jp)
        Iwa2(jp) = 0
        Iwa3(jp) = Iwa1(numdeg)
        if ( Iwa1(numdeg)>0 ) Iwa2(Iwa1(numdeg)) = jp
        Iwa1(numdeg) = jp
    enddo
    Maxclq = 0
    numord = n

    !  BEGINNING OF ITERATION LOOP.
    !
    !
    ! MARK THE SIZE OF THE LARGEST CLIQUE
    ! FOUND DURING THE ORDERING.

100 if ( mindeg+1==numord .and. Maxclq==0 ) Maxclq = numord

    ! CHOOSE A COLUMN JCOL OF MINIMAL DEGREE MINDEG.

200 jcol = Iwa1(mindeg)
    if ( jcol>0 ) then
        List(jcol) = numord
        numord = numord - 1

        ! TERMINATION TEST.

        if ( numord==0 ) then

            ! INVERT THE ARRAY LIST.

            do jcol = 1 , n
                Iwa2(List(jcol)) = jcol
            enddo
            do jp = 1 , n
                List(jp) = Iwa2(jp)
            enddo

        else

            ! DELETE COLUMN JCOL FROM THE MINDEG LIST.

            Iwa1(mindeg) = Iwa3(jcol)
            if ( Iwa3(jcol)>0 ) Iwa2(Iwa3(jcol)) = 0

            ! FIND ALL COLUMNS ADJACENT TO COLUMN JCOL.

            Iwa4(jcol) = 0

            ! DETERMINE ALL POSITIONS (IR,JCOL) WHICH CORRESPOND
            ! TO NON-ZEROES IN THE MATRIX.

            do jp = Jpntr(jcol) , Jpntr(jcol+1) - 1
                ir = Indrow(jp)

                ! FOR EACH ROW IR, DETERMINE ALL POSITIONS (IR,IC)
                ! WHICH CORRESPOND TO NON-ZEROES IN THE MATRIX.

                do ip = Ipntr(ir) , Ipntr(ir+1) - 1
                    ic = Indcol(ip)

                    ! ARRAY IWA4 MARKS COLUMNS WHICH ARE ADJACENT TO
                    ! COLUMN JCOL.

                    if ( Iwa4(ic)>numord ) then
                        Iwa4(ic) = numord

                        ! UPDATE THE POINTERS TO THE CURRENT DEGREE LISTS.

                        numdeg = List(ic)
                        List(ic) = List(ic) - 1
                        mindeg = min(mindeg,List(ic))

                        ! DELETE COLUMN IC FROM THE NUMDEG LIST.

                        if ( Iwa2(ic)==0 ) then
                            Iwa1(numdeg) = Iwa3(ic)
                        else
                            Iwa3(Iwa2(ic)) = Iwa3(ic)
                        endif
                        if ( Iwa3(ic)>0 ) Iwa2(Iwa3(ic)) = Iwa2(ic)

                        ! ADD COLUMN IC TO THE NUMDEG-1 LIST.

                        Iwa2(ic) = 0
                        Iwa3(ic) = Iwa1(numdeg-1)
                        if ( Iwa1(numdeg-1)>0 ) Iwa2(Iwa1(numdeg-1)) = ic
                        Iwa1(numdeg-1) = ic
                    endif
                enddo
            enddo

            ! END OF ITERATION LOOP.

            goto 100
        endif
    else
        mindeg = mindeg + 1
        goto 200
    endif

    end subroutine slo