⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 mfnormal3f.cls

📁 3ds文件浏览程序
💻 CLS
字号:
VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
  Persistable = 0  'NotPersistable
  DataBindingBehavior = 0  'vbNone
  DataSourceBehavior  = 0  'vbNone
  MTSTransactionMode  = 0  'NotAnMTSObject
END
Attribute VB_Name = "MFNormal3f"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Explicit
'*************************************************************************
'FUNCTION: holds an array of x,y,z values defining normals
'AUTHOR: edx - edx@hk.super.net, Oct 98 - all rights reserved
'HISTORY: -
'NOTES: - this class is used to hold normal data, which is 3 points
'*************************************************************************

Public FieldID As FieldNameIDConstants
Public ID&
Public ChunkID%
Public Parent As CNode
Public TreeNode As Node
'
Dim m_Count&
Dim m_Values() As POINT3F
'
Private Type GLMnode
    Count As Long
    Size As Long
    TriangleIndices() As Long
    Averaged() As Boolean
End Type

Private Sub Class_Initialize()
    '
End Sub

Private Sub Class_Terminate()
'
End Sub

'----------------------------------------------------------------------------
'set the points defining a normal
'----------------------------------------------------------------------------
Public Sub SetValue(Index&, v!())
    If Index > m_Count Then
        Debug.Assert 0
        ReDim Preserve m_Values(0 To Index)
        m_Count = Index + 1
    End If
    m_Values(Index).p(0) = v(0)
    m_Values(Index).p(1) = v(1)
    m_Values(Index).p(2) = v(2)
End Sub

Public Sub GetValue(Index&, v!())
    v(0) = m_Values(Index).p(0)
    v(1) = m_Values(Index).p(1)
    v(2) = m_Values(Index).p(2)
End Sub

'----------------------------------------------------------------------------
'you must set the count before adding values to this class.
'----------------------------------------------------------------------------
Public Property Get Count&()
    Count = m_Count
End Property

Public Property Let Count(ByVal NewValue&)
    If NewValue > 0 Then
        ReDim m_Values(0 To NewValue - 1)
        m_Count = NewValue
    Else
        ReDim m_Values(0 To 0)
        m_Count = 0
    End If
End Property

'----------------------------------------------------------------------------
'add this object to the treeview
'----------------------------------------------------------------------------
Public Sub FillTree()
    Set TreeNode = frmMain.TV1.Nodes.Add(Parent.TreeNode, tvwChild, , ChunkName(ChunkID), IMG_FIELD)
End Sub

'----------------------------------------------------------------------------
'gl drawing routine
'----------------------------------------------------------------------------
Public Sub DrawNormals()
    glNormalPointer GL_FLOAT, Len(m_Values(1)), m_Values(0).p(0)
End Sub

'----------------------------------------------------------------------------
'return a ptr to the array, if drawing is to be done elsewhere
'----------------------------------------------------------------------------
Public Function DataPointer&()
    DataPointer = VarPtr(m_Values(0).p(0))
End Function

'----------------------------------------------------------------------------
' for gl drawing routines
'----------------------------------------------------------------------------
Public Property Get Stride&()
    Stride = Len(m_Values(1))
End Property

'----------------------------------------------------------------------------
'Generates facet normals for a model (by taking the
' cross product of the two vectors derived from the sides of each
' triangle).  Assumes a counter-clockwise winding.
'----------------------------------------------------------------------------
Public Sub GenFacetNormals(Vertices As MFVec3f, Faces As MFVec3L)
Dim i&, u!(0 To 2), v!(0 To 2)
Dim ndx&(0 To 2), p0!(0 To 2), p1!(0 To 2), p2!(0 To 2)
    ' clobber any old facetnormals
    ' allocate memory for the new facet normals
    Count = Faces.Count
    For i = 0 To m_Count - 1
        Faces.GetValue i, ndx
        Vertices.GetValue ndx(0), p0
        Vertices.GetValue ndx(1), p1
        Vertices.GetValue ndx(2), p2
        u(0) = p1(0) - p0(0)
        u(1) = p1(1) - p0(1)
        u(2) = p1(2) - p0(2)
        '
        v(0) = p2(0) - p0(0)
        v(1) = p2(1) - p0(1)
        v(2) = p2(2) - p0(2)
        '
        Cross u, v, m_Values(i).p
        Normalize m_Values(i).p
    Next
End Sub

'----------------------------------------------------------------------------
' VertexNormals: Generates smooth vertex normals for a model.
' First builds a list of all the triangles each vertex is in.  Then
' loops through each vertex in the the list averaging all the facet
' normals of the triangles each vertex is in.  Finally, sets the
' normal index in the triangle for the vertex to the generated smooth
' normal.  If the dot product of a facet normal and the facet normal
' associated with the first triangle in the list of triangles the
' current vertex is in is greater than the cosine of the angle
' parameter to the function, that facet normal is not added into the
' average normal calculation and the corresponding vertex is given
' the facet normal.  This tends to preserve hard edges.  The angle to
' use depends on the model, but 90 degrees is usually a good start.
' *
' angle - maximum angle (in degrees) to smooth across
'----------------------------------------------------------------------------
Public Sub GenVertexNormals(Vertices As MFVec3f, Faces As MFVec3L, _
                                    FacetNorms As MFNormal3f) ', angle!)
Dim average!(0 To 2), m_dot!
'dim cos_angle!
Dim i&, avg&, j&
Dim u!(0 To 2), v!(0 To 2), ndx&(0 To 2)
Dim members() As GLMnode
Dim FaceIndex&
'Dim Node As GLMNode
''  GLMnode*  tail;
''  GLfloat*  normals;
'Dim numnormals&
    ' calculate the cosine of the angle (in degrees)
    'cos_angle = Cos(angle * PI / 180)
    ' allocate space for new normals
    Count = Vertices.Count
    ' allocate a structure that will hold a linked list of triangle
    ' indices for each vertex. This list corresponds to the vertex array
    ReDim members(0 To m_Count - 1)
    ' for every triangle, there are 3 vertices; tell each vertex
    'that it is part of this triangle. Add the index of the face
    ' to the internal list of faces for that vertex. T
    For i = 0 To Faces.Count - 1
        Faces.GetValue i, ndx
        m_AddTriangle members(ndx(0)), i
        m_AddTriangle members(ndx(1)), i
        m_AddTriangle members(ndx(2)), i
    Next

    ' calculate the average normal for each vertex
    For j = 0 To m_Count - 1
        ' calculate an average normal for this vertex by averaging the
        ' facet normal of every triangle this vertex is in
        If members(j).Count = 0 Then
            Debug.Print "VertexNormals(): vertex w/o a triangle"
            'Debug.Assert 0
        Else
            average(0) = 0
            average(1) = 0
            average(2) = 0
            avg = 0
            'for clarity:
            FaceIndex = members(j).TriangleIndices(1)
            FacetNorms.GetValue FaceIndex, v
            For i = 1 To members(j).Count
                ' only average if the dot product of the angle between the two
                ' facet normals is greater than the cosine of the threshold
                ' angle -- or, said another way, the angle between the two
                ' facet normals is less than (or equal to) the threshold angle
                'dot = _glmDot(facetnorms[T(node->index).findex],
                '      facetnorms[ T(members[i]->index).findex]);
                'get the 3 indexes. The
                FacetNorms.GetValue members(j).TriangleIndices(i), u
                'm_dot = Dot(u, v)
                'If m_dot > cos_angle Then
                    members(j).Averaged(i) = True
                    'average[0] += model->facetnorms[3 * T(node->index).findex + 0];
                    average(0) = average(0) + u(0)
                    average(1) = average(1) + u(1)
                    average(2) = average(2) + u(2)
                    avg = 1
                'Else
                   ' members(j).Averaged(i) = GL_FALSE
                'End If
            Next
    
            'If avg Then
                ' normalize the averaged normal
                Normalize average
            'End If
    
            ' add the normal to the vertex normals list
            m_Values(j).p(0) = average(0)
            m_Values(j).p(1) = average(1)
            m_Values(j).p(2) = average(2)
            'avg = numnormals
            'numnormals = numnormals + 1
    
    '        ' set the normal of this vertex in each triangle it is in
    '        'node = members(i);
    '        'while (node) {
    '        For i = 1 To members(j).Count
    '            If members(j).Averaged(i) Then
    '                ' if this node was averaged, use the average normal
    '                if (Faces(node.index).vindices(0) == i)
    '                  Faces(node.index).nindices(0) = avg;
    '                else if (Faces(node.index).vindices(1) == i)
    '                  Faces(node.index).nindices(1) = avg;
    '                else if (Faces(node.index).vindices(2) == i)
    '                  Faces(node.index).nindices(2) = avg;
    '          } else {
    '        ' if this node wasn't averaged, use the facet normal
    '        m_normals(3 * numnormals + 0) =
    '          facetnorms(3 * Faces(node.index).findex + 0);
    '        m_normals(3 * numnormals + 1) =
    '          facetnorms(3 * Faces(node.index).findex + 1);
    '        m_normals(3 * numnormals + 2) =
    '          facetnorms(3 * Faces(node.index).findex + 2);
    '        if (Faces(node.index).vindices(0) == i)
    '          Faces(node.index).nindices(0) = numnormals;
    '        else if (Faces(node.index).vindices(1) == i)
    '          Faces(node.index).nindices(1) = numnormals;
    '        else if (Faces(node.index).vindices(2) == i)
    '          Faces(node.index).nindices(2) = numnormals;
    '        numnormals++;
    '          }
    '          node = node.next;
    '        }
    '        }
    '
    '    m_numnormals = numnormals - 1;
    '
    '    ' free the member information
    '    for (i = 1; i <= m_numvertices; i++) {
    '      node = members(i);
    '      while (node) {
    '        tail = node;
    '        node = node.next;
    '        free(tail);
    '      }
        End If
    Next
'    free(members);
'
'    ' pack the normals array (we previously allocated the maximum
'       number of normals that could possibly be created (numtriangles *
'       3), so get rid of some of them (usually alot unless none of the
'       facet normals were averaged))
'    normals = m_normals;
'    m_normals = (GLfloat*)malloc(sizeof(GLfloat)* 3* (m_numnormals+1));
'    for (i = 1; i <= m_numnormals; i++) {
'      m_normals(3 * i + 0) = normals(3 * i + 0);
'      m_normals(3 * i + 1) = normals(3 * i + 1);
'      m_normals(3 * i + 2) = normals(3 * i + 2);
'    }
'    free(normals);

End Sub

Private Sub m_AddTriangle(m As GLMnode, Index&)
    m.Count = m.Count + 1
    If m.Count > m.Size Then
        m.Size = m.Size + 8
        ReDim Preserve m.TriangleIndices(1 To m.Size)
        ReDim Preserve m.Averaged(1 To m.Size)
    End If
    m.TriangleIndices(m.Count) = Index
End Sub


⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -