Search notes:

Accessing the MS-Dynamics CRM ODATA interface with VBA

OData_EntityType.cls

'
' vi: ft=basic
'
option explicit

private entityType_ as msxml2.IXMLDOMElement

public  svc_  as OData_Service

sub init(svc as OData_Service, name as string) ' {

    set svc_  = svc

    set entityType_ = svc_.metaData.selectSingleNode("//EntityType[@Name='" & name & "']")

end sub ' }


function properties as collection ' {

    set properties = new collection

    if not entityType_ is nothing then ' {

       dim entityTypeProperties_ as msxml2.IXMLDOMSelection
       set entityTypeProperties_ = entityType_.selectNodes("./Property")

       dim prop as IXMLDOMElement
       for each prop in entityTypeProperties_
           dim odataProperty   as  OData_Property
           set odataProperty = new OData_Property
           call odataProperty.init(me.svc_, prop)
           properties.add odataProperty
       next prop

    end if ' }

end function ' }
Github repository MS-Dynamics-CRM-ODATA, path: /OData_EntityType.cls

OData_Property.cls

'
' vi: ft=basic
'
option explicit

private property_ as msxml2.IXMLDOMElement
private svc_         as OData_Service

sub init(svc as OData_Service, p as msxml2.IXMLDOMElement) ' {
    set svc_        = svc
    set property_   = p
end sub ' }

function name as string ' {
 '
 '  The edm:Property element MUST include a Name attribute whose value is a SimpleIdentifier
 ' 
    name = property_.getAttribute("Name")
end function ' }

function type_ as string ' {
 '
 '  The edm:Property element MUST include a Type attribute.
 '  The value of the Type attribute MUST be the
 '    o  QualifiedName of a primitive type,
 '    o  complex type, or
 '    o  enumeration type in scope, or 
 '    o  a collection of one of these types.
 '
    type_ = property_.getAttribute("Type")
end function ' }

function description as string ' {

   dim xmlAnnotation as msxml2.IXMLDOMElement
   set xmlAnnotation = property_.selectSingleNode("./Annotation[@Term='Org.OData.Core.V1.Description']")
   

   if xmlAnnotation is nothing then
      description = ""
      exit function
   end if

   description = xmlAnnotation.getAttribute("String")

end function ' }
Github repository MS-Dynamics-CRM-ODATA, path: /OData_Property.cls

OData_Service.cls

'
' vi: ft=basic
'
option explicit

public metadata as msxml2.DOMDocument

sub class_initialize() ' {
    set metadata = new msxml2.DOMDocument
end sub ' }

sub init(fileName_or_URL as string) ' {

    metadata.async            = false
    metadata.validateOnParse  = true
    metadata.resolveExternals = true   ' ? 
    
    if not metadata.load(fileName_or_URL) then
       debug.print(metadata.parseError.reason)
       debug.print("Line: " & metadata.parseError.line   )
       debug.print("Pos:  " & metadata.parseError.linepos)
       exit sub
    end if

end sub ' }

function EntityType(name as string) as OData_EntityType ' {

    set  EntityType = new OData_EntityType
    call EntityType.init(me, name)

end function ' }
Github repository MS-Dynamics-CRM-ODATA, path: /OData_Service.cls

Test program

option explicit

const ms_dynamics_service_url_root = "https://odata-service/"

sub showEntityType(entityTypeName as string) ' {


    dim odataService as new OData_Service
    odataService.init(ms_dynamics_service_url_root & "$metadata")
  
    dim odataEntityType as OData_EntityType
    set odataEntityType = odataService.EntityType(entityTypeName)

    dim f as integer
    f = freeFile

    open environ("USERPROFILE") & "\" & entityTypeName & ".properties.txt" for output as #f ' "
    
    dim prop as OData_Property
    for each prop in odataEntityType.properties ' {
        print# f,   prop.name & " - " & prop.type_ & " - " & prop.description
    next prop ' }

    close# f
     
end sub ' }
Github repository MS-Dynamics-CRM-ODATA, path: /main_.bas

TODO

https://zic.ke/xyzprod/api/data/v8.0/EntityDefinitions
https://zic.ke/xyzprod/api/data/v8.0/RelationshipDefinitions
https://zic.ke/xyzprod/api/data/v8.0/GlobalOptionSetDefinitions
https://zic.ke/xyzprod/api/data/v8.0/ManagedPropertyDefinitions

See also

MS Dynamics

Index