ido Subroutine

private subroutine ido(m, 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 an incidence-degree ordering of the columns of a.

the incidence-degree 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 incidence-degree ordering is determined recursively by letting list(k), k = 1,...,n be a column with maximal incidence to the subgraph spanned by the ordered columns. among all the columns of maximal incidence, ido chooses a column of maximal degree.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: m

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

integer, intent(in) :: n

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

integer, intent(in), dimension(*) :: Indrow

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

integer, intent(in), 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, intent(in), dimension(*) :: Indcol

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

integer, intent(in), dimension(m+1) :: 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, intent(in), 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, intent(out), dimension(n) :: List

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

integer, intent(out) :: 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.


Calls

proc~~ido~~CallsGraph proc~ido dsm_module::ido proc~numsrt dsm_module::numsrt proc~ido->proc~numsrt

Called by

proc~~ido~~CalledByGraph proc~ido dsm_module::ido proc~dsm dsm_module::dsm proc~dsm->proc~ido 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 ido(m,n,Indrow,Jpntr,Indcol,Ipntr,Ndeg,List,Maxclq, &
                   Iwa1,Iwa2,Iwa3,Iwa4)

    implicit none

    integer,intent(in)       :: m         !! a positive integer input variable set to the number
                                          !! of rows of `a`.
    integer,intent(in)       :: n         !! a positive integer input variable set to the number
                                          !! of columns of `a`.
    integer,intent(out)      :: Maxclq    !! an integer output variable set to the size
                                          !! of the largest clique found during the ordering.
    integer,dimension(*),intent(in) :: Indrow    !! an integer input array which contains the row
                                                 !! indices for the non-zeroes in the matrix `a`.
    integer,dimension(n+1),intent(in) :: 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(*),intent(in)     :: Indcol   !! an integer input array which contains the
                                                    !! column indices for the non-zeroes in the matrix `a`.
    integer,dimension(m+1),intent(in)   :: 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),intent(in)     :: 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),intent(out)    :: List     !! an integer output array of length `n` which specifies
                                                    !! the incidence-degree 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 , maxinc , maxlst , ncomp , &
               numinc , numlst , numord , numwgt

    ! sort the degree sequence.

    call numsrt(n,n-1,Ndeg,-1,Iwa4,Iwa2,Iwa3)

    ! initialization block.
    !
    ! create a doubly-linked list to access the incidences of the
    ! columns. the pointers for the linked list are as follows.
    !
    ! each un-ordered column ic is in a list (the incidence list)
    ! of columns with the same incidence.
    !
    ! iwa1(numinc) is the first column in the numinc list
    ! unless iwa1(numinc) = 0. in this case there are
    ! no columns in the numinc list.
    !
    ! iwa2(ic) is the column before ic in the incidence list
    ! unless iwa2(ic) = 0. in this case ic is the first
    ! column in this incidence list.
    !
    ! iwa3(ic) is the column after ic in the incidence list
    ! unless iwa3(ic) = 0. in this case ic is the last
    ! column in this incidence list.
    !
    ! if ic is an un-ordered column, then list(ic) is the
    ! incidence of ic to the graph induced by the ordered
    ! columns. if jcol is an ordered column, then list(jcol)
    ! is the incidence-degree order of column jcol.

    maxinc = 0
    do jp = n , 1 , -1
        ic = Iwa4(jp)
        Iwa1(n-jp) = 0
        Iwa2(ic) = 0
        Iwa3(ic) = Iwa1(0)
        if ( Iwa1(0)>0 ) Iwa2(Iwa1(0)) = ic
        Iwa1(0) = ic
        Iwa4(jp) = 0
        List(jp) = 0
    enddo

    ! DETERMINE THE MAXIMAL SEARCH LENGTH FOR THE LIST
    ! OF COLUMNS OF MAXIMAL INCIDENCE.

    maxlst = 0
    do ir = 1 , m
        maxlst = maxlst + (Ipntr(ir+1)-Ipntr(ir))**2
    enddo
    maxlst = maxlst/n
    Maxclq = 0
    numord = 1

    ! BEGINNING OF ITERATION LOOP.

    ! UPDATE THE SIZE OF THE LARGEST CLIQUE
    ! FOUND DURING THE ORDERING.

100 if ( maxinc==0 ) ncomp = 0
    ncomp = ncomp + 1
    if ( maxinc+1==ncomp ) Maxclq = max(Maxclq,ncomp)

    ! CHOOSE A COLUMN JCOL OF MAXIMAL DEGREE AMONG THE
    ! COLUMNS OF MAXIMAL INCIDENCE MAXINC.

200 jp = Iwa1(maxinc)
    if ( jp>0 ) then
        numwgt = -1
        do numlst = 1 , maxlst
            if ( Ndeg(jp)>numwgt ) then
                numwgt = Ndeg(jp)
                jcol = jp
            endif
            jp = Iwa3(jp)
            if ( jp<=0 ) exit
        enddo
        List(jcol) = numord
        numord = numord + 1

        ! TERMINATION TEST.

        if ( numord>n ) 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 MAXINC LIST.

            if ( Iwa2(jcol)==0 ) then
                Iwa1(maxinc) = Iwa3(jcol)
            else
                Iwa3(Iwa2(jcol)) = Iwa3(jcol)
            endif
            if ( Iwa3(jcol)>0 ) Iwa2(Iwa3(jcol)) = Iwa2(jcol)

            ! FIND ALL COLUMNS ADJACENT TO COLUMN JCOL.

            Iwa4(jcol) = n

            ! 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 INCIDENCE LISTS.

                        numinc = List(ic)
                        List(ic) = List(ic) + 1
                        maxinc = max(maxinc,List(ic))

                        ! DELETE COLUMN IC FROM THE NUMINC LIST.

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

                        ! ADD COLUMN IC TO THE NUMINC+1 LIST.

                        Iwa2(ic) = 0
                        Iwa3(ic) = Iwa1(numinc+1)
                        if ( Iwa1(numinc+1)>0 ) Iwa2(Iwa1(numinc+1)) = ic
                        Iwa1(numinc+1) = ic
                    endif
                enddo
            enddo

            ! END OF ITERATION LOOP.

            goto 100
        endif
    else
        maxinc = maxinc - 1
        goto 200
    endif

    end subroutine ido