getList Subroutine

public subroutine getList(iList, nIntAtt, intAttNames, intAttCnts, intAtts, rList, nRealAtt, realAttNames, realAttCnts, realAtts, cList, nCharAtt, charAttNames, charAttCnts, charAtts, vNames)

getList – retrieve defined attributes from a list

Arguments

Type IntentOptional Attributes Name
type(iNode), optional, pointer :: iList

int list

integer, optional :: nIntAtt

num of int att

character(len=MLEN), optional, pointer :: intAttNames(:)
integer, optional, pointer :: intAttCnts(:)

data count in int att

integer, optional, pointer :: intAtts(:,:)

int attribute

type(rNode), optional, pointer :: rList

char list

integer, optional :: nRealAtt

num of real att

character(len=MLEN), optional, pointer :: realAttNames(:)
integer, optional, pointer :: realAttCnts(:)

data count in real att

real, optional, pointer :: realAtts(:,:)

real attribute

type(cNode), optional, pointer :: cList

real list

integer, optional :: nCharAtt

num of char att

character(len=MLEN), optional, pointer :: charAttNames(:)
integer, optional, pointer :: charAttCnts(:)

data count in char att

character(len=MLEN), optional, pointer :: charAtts(:)

char att

character(len=MLEN), optional, pointer :: vNames(:)

Calls

proc~~getlist~~CallsGraph proc~getlist getList proc~getmaxlencnt getMaxLenCnt proc~getlist->proc~getmaxlencnt

Called by

proc~~getlist~~CalledByGraph proc~getlist getList proc~esmf_cfioeosfilecreate ESMF_CFIOEosFileCreate proc~esmf_cfioeosfilecreate->proc~getlist proc~esmf_cfiosdffilecreate ESMF_CFIOSdfFileCreate proc~esmf_cfiosdffilecreate->proc~getlist proc~esmf_cfiofilecreate ESMF_CFIOFileCreate proc~esmf_cfiofilecreate->proc~esmf_cfiosdffilecreate proc~mapl_cfiocreatewrite MAPL_CFIOCreatewrite proc~mapl_cfiocreatewrite->proc~esmf_cfiofilecreate program~test~10 test program~test~10->proc~esmf_cfiofilecreate program~test~11 test program~test~11->proc~esmf_cfiofilecreate program~test~12 test program~test~12->proc~esmf_cfiofilecreate program~test~13 test program~test~13->proc~esmf_cfiofilecreate program~test~14 test program~test~14->proc~esmf_cfiofilecreate program~test~3 test program~test~3->proc~esmf_cfiofilecreate program~test~5 test program~test~5->proc~esmf_cfiofilecreate program~test~7 test program~test~7->proc~esmf_cfiofilecreate program~test~8 test program~test~8->proc~esmf_cfiofilecreate program~test~9 test program~test~9->proc~esmf_cfiofilecreate

Source Code

   subroutine getList(iList, nIntAtt, intAttNames, intAttCnts, intAtts,     &
                      rList, nRealAtt, realAttNames, realAttCnts, realAtts, &
                      cList, nCharAtt, charAttNames, charAttCnts, charAtts, vNames)
!
! !INPUT PARAMETERS:
!
           type(iNode), pointer, OPTIONAL :: iList   !! int list
           type(cNode), pointer, OPTIONAL :: cList   !! real list
           type(rNode), pointer, OPTIONAL :: rList   !! char list
!
! !OUTPUT PARAMETERS:
!
           integer, OPTIONAL :: nIntAtt              !! num of int att
           integer, OPTIONAL :: nRealAtt             !! num of real att
           integer, OPTIONAL :: nCharAtt             !! num of char att
           character(len=MLEN), pointer, OPTIONAL :: intAttNames(:)
           character(len=MLEN), pointer, OPTIONAL :: realAttNames(:)
           character(len=MLEN), pointer, OPTIONAL :: charAttNames(:)
           integer, OPTIONAL, pointer :: intAttCnts(:) !!data count in int att
           integer, OPTIONAL, pointer :: realAttCnts(:)!!data count in real att
           integer, OPTIONAL, pointer :: charAttCnts(:)!!data count in char att
           integer, OPTIONAL, pointer :: intAtts(:,:)  !!int attribute
           real, OPTIONAL, pointer :: realAtts(:,:)    !!real attribute
           character(len=MLEN), pointer, OPTIONAL :: charAtts(:) !! char att
           character(len=MLEN), pointer, OPTIONAL :: vNames(:)
!
!------------------------------------------------------------------------------
           type(iNode), pointer :: p    ! pointer for integer list
           type(rNode), pointer :: rp   ! pointer for real list
           type(cNode), pointer :: cp   ! pointer for char list
           integer :: maxLen            ! length of a list
           integer :: cnt               ! max number of data in nodes
           integer :: i

           maxLen = 0
           cnt = 0

!          get attributes from an integer list
           if ( present(iList) ) then
              allocate(p)
              p = iList
              call getMaxLenCnt(maxLen, cnt, iList=iList)
              if ( present(nIntAtt) ) nIntAtt = cnt
              allocate(intAttCnts(cnt), intAttNames(cnt), intAtts(cnt,maxLen))
              if (present(vNames)) allocate(vNames(cnt))
              i = 1
              do while ( associated(p) )
                  intAttNames(i) = trim(p%name)
                  if (present(vNames)) vNames(i) = trim(p%vName)
                  intAttCnts(i) = p%count
                  intAtts(i,:) = 0
                  intAtts(i,1:size(p%intData)) = p%intData
                  p => p%next
                  i = i + 1
              end do
           end if

!          get attributes from a real list
           if ( present(rList) ) then
              allocate(rp)
              rp = rList
              call getMaxLenCnt(maxLen, cnt, rList=rList)
              if (present(nRealAtt)) nRealAtt = cnt
              allocate(realAttCnts(cnt),realAttNames(cnt),realAtts(cnt,maxLen))
              if (present(vNames)) allocate(vNames(cnt))
              i = 1
              do while ( associated(rp) )
                  realAttNames(i) = trim(rp%name)
                  realAttCnts(i) = rp%count
                  if (present(vNames)) vNames(i) = trim(rp%vName)
                  realAtts(i,1:size(rp%realData)) = rp%realData
                  rp => rp%next
                  i = i + 1
              end do
           end if

!          get attributes from a char list
           if ( present(cList) ) then
              allocate(cp)
              cp = cList
              call getMaxLenCnt(maxLen, cnt, cList=cList)
              if ( present(nCharAtt) ) nCharAtt = cnt
              allocate(charAttCnts(cnt), charAttNames(cnt), charAtts(cnt))
              if (present(vNames)) allocate(vNames(cnt))
              i = 1
              do while ( associated(cp) )
                  charAttNames(i) = trim(cp%name)
                  if (present(vNames)) vNames(i) = trim(cp%vName)
                  charAttCnts(i) = cp%count
                  charAtts(i) = cp%charData
                  cp => cp%next
                  i = i + 1
              end do
           end if

        end subroutine getList