Compartir a través de


Propiedad LookupTableEntry.FullName (Project)

Obtiene el nombre completo para el nivel especificado y los niveles principales de LookupTableEntry para el código de esquema que se completa con la cadena separadora entre los niveles. String de solo lectura.

Sintaxis

expresión. Fullname

Expresión Variable que representa un objeto LookupTableEntry .

Ejemplo:

El ejemplo de macro CreateLocationOutlineCode establece tres niveles LookupTableEntry para un código de esquema de tarea personalizado denominado Location. Después de ejecuta la macro CreateLocationOutlineCode, al escribir la línea siguiente en la ventana inmediato del Editor de Visual Basic (VBE), devuelve el resultado que se muestra.

Print ActiveProject.OutlineCodes.Item(1).LookupTable.Item(4).FullName 
WA.KING.RED

A continuación se muestra la macro CreateLocationOutlineCode.

Sub CreateLocationOutlineCode() 
    Dim objOutlineCode As OutlineCode 
    On Error GoTo ErrorHandler 
 
    Set objOutlineCode = ActiveProject.OutlineCodes.Add( _
        pjCustomTaskOutlineCode1, "Location") 
 
    objOutlineCode.OnlyLookUpTableCodes = True 
 
    DefineLocationCodeMask objOutlineCode.CodeMask 
    EditLocationLookupTable objOutlineCode.LookupTable 
 End 
 
ErrorHandler: 
    MsgBox "CreateLocationOutlineCode(): Error Number: " 
 & Err.Number & _ 
    vbCrLf & " Error Description: " & Err.Description 
End Sub 
 
 
Sub DefineLocationCodeMask(objCodeMask As CodeMask) 
    objCodeMask.Add _ 
        Sequence:=pjCustomOutlineCodeUppercaseLetters, _
        Length:=2, Separator:="." 
 
    objCodeMask.Add 
        Sequence:=pjCustomOutlineCodeUppercaseLetters, _
        Separator:="." 
 
    objCodeMask.Add _
        Sequence:=pjCustomOutlineCodeUppercaseLetters, _
        Length:=3, Separator:="." 
End Sub 
 
 
Sub EditLocationLookupTable(objLookupTable As LookupTable) 
    Dim objStateEntry As LookupTableEntry 
    Dim objCountyEntry As LookupTableEntry 
    Dim objCityEntry As LookupTableEntry 
 
    Set objStateEntry = objLookupTable.AddChild("WA") 
    objStateEntry.Description = "Washington" 
 
    Set objCountyEntry = objLookupTable.AddChild("KING", _
        objStateEntry.UniqueID) 
    objCountyEntry.Description = "King County" 
 
    Set objCityEntry = objLookupTable.AddChild("SEA", _
        objCountyEntry.UniqueID) 
    objCityEntry.Description = "Seattle" 
 
    Set objCityEntry = objLookupTable.AddChild("RED", _
        objCountyEntry.UniqueID) 
    objCityEntry.Description = "Redmond" 
 
    Set objCityEntry = objLookupTable.AddChild("KIR", _
        objCountyEntry.UniqueID) 
    objCityEntry.Description = "Kirkland" 
End Sub

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.