hexagon logo

Measuring Thickness at Specific Points Using Scan Data

Hi Guys,

We make a lot of relatively thin, flat parts, many of which are in a high-nickel ferrous alloy (so they're a pain to machine well) and many of which have tight tolerances on the thickness and/or flatness of the large sides. Because the parts are thin, the thickness tends to vary a bit across the part, and in order to check it thoroughly we would take points directly opposite each other in a dozen or more places and report the distance between them. It worked (and still works) great on our TP20 systems. However, we recently purchased a Global S 9-12-8 with a scanning head, and are hoping to use the scanning functionality to speed up our measuring routines considerably. In order to do the same "point-to-point" thickness measurement, we need to be able to identify particular hits that are opposite each other so we can dimension to them using the scn.hit notation. Here's a sketch:

I was about to post a screenshot of an actual part, and then realized it was ITAR. No good. Imagine the curvy series of green points comprising a scan on one side of a part, and the red series a scan on the other. What I'm trying to do is report the thickness between the points inside of each of the purple circles.

Is there any way to get PC-DMIS to do something like this automatically?

Having exhausted my own attempts to find a positive answer to that question, I wrote a subroutine to do it:


            SUBROUTINE/SCANTHICK,
                SCN1 =  : THE FIRST SCAN,
                SCN2 =  : THE SECOND SCAN,
                UCENT =  : THE U-COORDINATE (X OR Y) OF THE SEARCH ZONE CENTER,
                VCENT =  : THE V-COORDINATE (Y OR Z) OF THE SEARCH ZONE CENTER,
                PLANE =  : "XY" "XZ" or "YZ",
                RADIUS =  : RADIUS AROUND CENTER IN WHICH TO SEARCH,
                TOLERANCE =  : MAXIMUM ACCEPTABLE (IN-PLANE) DISTANCE BETWEEN FOUND POINTS,
                NOMINAL =  : NOMINAL THICKNESS BETWEEN SCANS,
                PLUSTOL =  : PLUS TOLERANCE ON THICKNESS,
                MINUSTOL =  : MINUS TOLERANCE ON THICKNESS,
                 =
$$ NO,
            Convert to UV coordinates
            IF/PLANE=="XY"
              ASSIGN/U1=SCN1.HIT[1..SCN1.NUMHITS].X
              ASSIGN/V1=SCN1.HIT[1..SCN1.NUMHITS].Y
              ASSIGN/U2=SCN2.HIT[1..SCN2.NUMHITS].X
              ASSIGN/V2=SCN2.HIT[1..SCN2.NUMHITS].Y
            END_IF/
            ELSE_IF/PLANE=="XZ"
              ASSIGN/U1=SCN1.HIT[1..SCN1.NUMHITS].X
              ASSIGN/V1=SCN1.HIT[1..SCN1.NUMHITS].Z
              ASSIGN/U2=SCN2.HIT[1..SCN2.NUMHITS].X
              ASSIGN/V2=SCN2.HIT[1..SCN2.NUMHITS].Z
            END_ELSEIF/
            ELSE_IF/PLANE=="YZ"
              ASSIGN/U1=SCN1.HIT[1..SCN1.NUMHITS].Y
              ASSIGN/V1=SCN1.HIT[1..SCN1.NUMHITS].Z
              ASSIGN/U2=SCN2.HIT[1..SCN2.NUMHITS].Y
              ASSIGN/V2=SCN2.HIT[1..SCN2.NUMHITS].Z
            END_ELSEIF/
            ELSE/
              COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
              Subroutine SCANTHICK: Invalid Plane argument given! Exiting.
              ROUTINE/END
            END_ELSE/
$$ NO,
            Identify points within search radius
            ASSIGN/GOOD_I_SCN1=ARRAY(-1)
            ASSIGN/K=1
            ASSIGN/I=1
            WHILE/I<=SCN1.NUMHITS
              IF/SQRT((U1[I] - UCENT)^2 + (V1[I] - VCENT)^2) < RADIUS
                ASSIGN/GOOD_I_SCN1[K]=I
                ASSIGN/K=K+1
              END_IF/
              ASSIGN/I=I+1
            END_WHILE/
            IF/GOOD_I_SCN1[1] == -1
              COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
              Subroutine SCANTHICK: No valid SCN1 points found within search radius. Exiting.
              ROUTINE/END
            END_IF/
            ASSIGN/GOOD_I_SCN2=ARRAY(-1)
            ASSIGN/K=1
            ASSIGN/I=1
            WHILE/I<=SCN1.NUMHITS
              IF/SQRT((U2[I] - UCENT)^2 + (V2[I] - VCENT)^2) < RADIUS
                ASSIGN/GOOD_I_SCN2[K]=I
                ASSIGN/K=K+1
              END_IF/
              ASSIGN/I=I+1
            END_WHILE/
            IF/GOOD_I_SCN2[1] == -1
              COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
              Subroutine SCANTHICK: No valid SCN2 points found within search radius. Exiting.
              ROUTINE/END
            END_IF/
$$ NO,
            Brute force search for minimum distance (in UV plane)
            ASSIGN/SMALLEST_SO_FAR=RADIUS*2
            ASSIGN/SMALLEST_SCN1=-1
            ASSIGN/SMALLEST_SCN2=-1
            ASSIGN/ILOOP=1
            WHILE/ILOOP <= LEN(GOOD_I_SCN1)
              ASSIGN/I=GOOD_I_SCN1[ILOOP]
              ASSIGN/JLOOP=1
              WHILE/JLOOP <= LEN(GOOD_I_SCN2)
                ASSIGN/J=GOOD_I_SCN2[JLOOP]
                ASSIGN/DISTANCE=SQRT((U1[I] - U2[J])^2 + (V1[I] - V2[J])^2)
                WORKPLANE/ZPLUS
                IF/DISTANCE < SMALLEST_SO_FAR
                  ASSIGN/SMALLEST_SO_FAR=DISTANCE
                  ASSIGN/SMALLEST_SCN1=I
                  ASSIGN/SMALLEST_SCN2=J
                END_IF/
                ASSIGN/JLOOP=JLOOP+1
              END_WHILE/
              ASSIGN/ILOOP=ILOOP+1
            END_WHILE/
            IF/SMALLEST_SCN1 == -1 OR SMALLEST_SCN2 == -1
              COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
              Subroutine SCANTHICK: No points closer than radius*2 were found (???). Exiting.
              ROUTINE/END
            END_IF/
$$ NO,
            Check if we've satisfied the result tolerance and output result
            IF/SMALLEST_SO_FAR > TOLERANCE
              COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
              Subroutine SCANTHICK: Closest pair of points found were further apart than the tolerance. Exiting.
              ROUTINE/END
            END_IF/
            IF/PLANE=="XY"
              WORKPLANE/XPLUS
  DIM DIST1= 2D DISTANCE FROM  SCN1.HIT[SMALLEST_SCN1] TO  SCN2.HIT[SMALLEST_SCN2] PAR TO   ZAXIS,NO_RADIUS  UNITS=IN,$
  GRAPH=OFF  TEXT=OFF  MULT=10.00  OUTPUT=BOTH
  AX    NOMINAL       +TOL       -TOL       MEAS        MAX        MIN        DEV     OUTTOL
  M    NOMINAL  PLUSTOL  MINUSTOL     0.0000     0.0000     0.0000     0.0000     0.0000 #-------
            END_IF/
            ELSE_IF/PLANE=="XZ"
              WORKPLANE/XPLUS
  DIM DIST2= 2D DISTANCE FROM  SCN1.HIT[SMALLEST_SCN1] TO  SCN2.HIT[SMALLEST_SCN2] PAR TO   YAXIS,NO_RADIUS  UNITS=IN,$
  GRAPH=OFF  TEXT=OFF  MULT=10.00  OUTPUT=BOTH
  AX    NOMINAL       +TOL       -TOL       MEAS        MAX        MIN        DEV     OUTTOL
  M    NOMINAL  PLUSTOL  MINUSTOL     0.0000     0.0000     0.0000     0.0000     0.0000 #-------
            END_ELSEIF/
            ELSE/
              WORKPLANE/YPLUS
  DIM DIST3= 2D DISTANCE FROM  SCN1.HIT[SMALLEST_SCN1] TO  SCN2.HIT[SMALLEST_SCN2] PAR TO   XAXIS,NO_RADIUS  UNITS=IN,$
  GRAPH=OFF  TEXT=OFF  MULT=10.00  OUTPUT=BOTH
  AX    NOMINAL       +TOL       -TOL       MEAS        MAX        MIN        DEV     OUTTOL
  M    NOMINAL  PLUSTOL  MINUSTOL     0.0000     0.0000     0.0000     0.0000     0.0000 #-------
            END_ELSE/
            ENDSUB/



An example of the calling code would be:

CS2        =CALLSUB/SCANTHICK,"SCAN_THICKNESS":{SCNA},{SCN_FRONT_TOP},-2.37,-.46,"XZ",.05,.01,.243,.0015,.0015,$
                ,


Here, SCNA has 784 points and SCN_FRONT_TOP has 206. The dimensions are in inches.

Frustratingly, this is super-slow to execute. I have to call it for each intersection I want to find, and each call takes about 2 minutes to complete. My latest program only has four points, which I'm dealing with for now, but some of our stuff has closer to 30 point-to-point measurements if not more.

Unless I find another way, I'll mess around with this a bit longer and then see if the algorithm above runs much faster in Visual Basic. Though, in that case, if I end up needing to use file IO and it takes more than a few seconds to read the entire scan out and back in, I'll be up a creek.

In conclusion:
  1. Does anyone know of a way within PC-DMIS to do what I'm trying to do without coding it myself?
  2. If not, does anyone see any major performance issues with my code that I should address?
  3. If not either of those, can anyone tell me if Visual Basic will be substantially better?

P. S. Another potential option would be to use this or something similar the first time, and then hard-code the hit indices for production. But that would stink if I ever need to change scan parameters for something and shift the points a bit. Also, are hits guaranteed to stay in the same spot from one run to the next even with the same parameters?

Attached Files
  • I'm running 2019 R1, but the thickness gauge tool doesn't seem to support my scan type. Thanks for letting me know about it, though.
  • We have used the method Jeffman suggests extensively for reporting wall thickness. You scan, then create a constructed curve from the scan. The constructed curve allows the scan data to be interpreted as continuous instead of as discrete points. Then you intersect the constructed curves with planes at the locations where you want to evaluate the thickness. This gives you discrete points at exact, known locations. You can then evaluate the distance between those points. Scan point locations are always variable. Even with defined scans your points can easily shift by the value of the point density. This method lets you use the speed of scanning but still have the certainty that you have points to evaluate at exactly defined locations. This will be more accurate than your old TP20 method since you will have no machine drift whatsoever. If you’re plane is defined at x=10 your intersect points will be at x=10 and not 1 micron different than that.

    Also, time to read scan point data from PCDMIS into a VBA or VB routine is extremely fast. Milliseconds or seconds depending on how large the scan is.
  • Thank you! I'm most of the way through implementing my search code in VB. Regarding the plane method: if the scan drifts side to side (in a direction perpendicular to its path), wouldn't that cause the location of the constructed point to vary?
  • To wrap up (at least for now), I moved the loops in my original algorithm to Visual Basic, and the execution time dropped from ~2 minutes in my test case to less than a second. Here's the final PC-DMIS subroutine:

    
    SUBROUTINE/SCANTHICK,
                    SCN1 =  : THE FIRST SCAN,
                    SCN2 =  : THE SECOND SCAN,
                    UCENT =  : THE U-COORDINATE (X OR Y) OF THE SEARCH ZONE CENTER,
                    VCENT =  : THE V-COORDINATE (Y OR Z) OF THE SEARCH ZONE CENTER,
                    PLANE =  : "XY" "XZ" or "YZ",
                    RADIUS =  : RADIUS AROUND CENTER IN WHICH TO SEARCH,
                    TOLERANCE =  : MAXIMUM ACCEPTABLE (IN-PLANE) DISTANCE BETWEEN FOUND POINTS,
                    NOMINAL =  : NOMINAL THICKNESS BETWEEN SCANS,
                    PLUSTOL =  : PLUS TOLERANCE ON THICKNESS,
                    MINUSTOL =  : MINUS TOLERANCE ON THICKNESS,
                     =
    $$ NO,
                Convert to UV coordinates
                IF/PLANE=="XY"
                  ASSIGN/U1=SCN1.HIT[1..SCN1.NUMHITS].X
                  ASSIGN/V1=SCN1.HIT[1..SCN1.NUMHITS].Y
                  ASSIGN/U2=SCN2.HIT[1..SCN2.NUMHITS].X
                  ASSIGN/V2=SCN2.HIT[1..SCN2.NUMHITS].Y
                END_IF/
                ELSE_IF/PLANE=="XZ"
                  ASSIGN/U1=SCN1.HIT[1..SCN1.NUMHITS].X
                  ASSIGN/V1=SCN1.HIT[1..SCN1.NUMHITS].Z
                  ASSIGN/U2=SCN2.HIT[1..SCN2.NUMHITS].X
                  ASSIGN/V2=SCN2.HIT[1..SCN2.NUMHITS].Z
                END_ELSEIF/
                ELSE_IF/PLANE=="YZ"
                  ASSIGN/U1=SCN1.HIT[1..SCN1.NUMHITS].Y
                  ASSIGN/V1=SCN1.HIT[1..SCN1.NUMHITS].Z
                  ASSIGN/U2=SCN2.HIT[1..SCN2.NUMHITS].Y
                  ASSIGN/V2=SCN2.HIT[1..SCN2.NUMHITS].Z
                END_ELSEIF/
                ELSE/
                  COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
                  Subroutine SCANTHICK: Invalid Plane argument given! Exiting.
                  ROUTINE/END
                END_ELSE/
    $$ NO,
                Run VB Script to do actual math
                ASSIGN/FILENAME="pcdmis_scan_thickness_finder_script_io.txt"
    OUTFILE    =FILE/OPEN,FILENAME,WRITE
                FILE/WRITELINE,OUTFILE,U1
                FILE/WRITELINE,OUTFILE,V1
                FILE/WRITELINE,OUTFILE,U2
                FILE/WRITELINE,OUTFILE,V2
                FILE/CLOSE,OUTFILE,KEEP
                ASSIGN/EXITSTATUS=0
                ASSIGN/SMALLEST_SCN1=-1
                ASSIGN/SMALLEST_SCN2=-1
    CS1        =SCRIPT/FILENAME= M:\CMM\PROGRAMS\SUBROUTINES\SCAN_THICKNESS_BACKEND.BAS
                FUNCTION/Main,SHOW=YES,ARG1=FILENAME,ARG2=SCN1.NUMHITS,ARG3=SCN2.NUMHITS,ARG4=UCENT,ARG5=VCENT,ARG6=RADIUS,$
                    ARG7=TOLERANCE,,
                STARTSCRIPT/
                FILE/DELETE,FILENAME
                SELECT/EXITSTATUS
                  CASE/0
        $$ NO,
                    Success! Continue on...
                  END_CASE/
                  CASE/1
                    COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
                    Subroutine SCANTHICK: No SCN1 points found in search radius. Exiting.
                    ROUTINE/END
                  END_CASE/
                  CASE/2
                    COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
                    Subroutine SCANTHICK: No SCN2 points found in search radius. Exiting.
                    ROUTINE/END
                  END_CASE/
                  CASE/3
                    COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
                    Subroutine SCANTHICK: No points closer than radius*2 found. (?) Exiting.
                    ROUTINE/END
                  END_CASE/
                  CASE/4
                    COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
                    Subroutine SCANTHICK: No points found closer than the result tolerance. Exiting.
                    ROUTINE/END
                  END_CASE/
                  DEFAULT_CASE/
                    COMMENT/OPER,NO,FULL SCREEN=NO,AUTO-CONTINUE=NO,
                    "Subroutine SCANTHICK: Unknown error in VB backend - exit status " + EXITSTATUS + ". Exiting."
                    ROUTINE/END
                  END_DEFAULTCASE/
                END_SELECT/
    $$ NO,
                Output result
                IF/PLANE=="XY"
                  WORKPLANE/XPLUS
      DIM DIST1= 2D DISTANCE FROM  SCN1.HIT[SMALLEST_SCN1] TO  SCN2.HIT[SMALLEST_SCN2] PAR TO   ZAXIS,NO_RADIUS  UNITS=IN,$
      GRAPH=OFF  TEXT=OFF  MULT=10.00  OUTPUT=BOTH
      AX    NOMINAL       +TOL       -TOL       MEAS        MAX        MIN        DEV     OUTTOL
      M    NOMINAL  PLUSTOL  MINUSTOL     0.0000     0.0000     0.0000     0.0000     0.0000 #-------
                END_IF/
                ELSE_IF/PLANE=="XZ"
                  WORKPLANE/XPLUS
      DIM DIST2= 2D DISTANCE FROM  SCN1.HIT[SMALLEST_SCN1] TO  SCN2.HIT[SMALLEST_SCN2] PAR TO   YAXIS,NO_RADIUS  UNITS=IN,$
      GRAPH=OFF  TEXT=OFF  MULT=10.00  OUTPUT=BOTH
      AX    NOMINAL       +TOL       -TOL       MEAS        MAX        MIN        DEV     OUTTOL
      M    NOMINAL  PLUSTOL  MINUSTOL     0.0000     0.0000     0.0000     0.0000     0.0000 #-------
                END_ELSEIF/
                ELSE/
                  WORKPLANE/YPLUS
      DIM DIST3= 2D DISTANCE FROM  SCN1.HIT[SMALLEST_SCN1] TO  SCN2.HIT[SMALLEST_SCN2] PAR TO   XAXIS,NO_RADIUS  UNITS=IN,$
      GRAPH=OFF  TEXT=OFF  MULT=10.00  OUTPUT=BOTH
      AX    NOMINAL       +TOL       -TOL       MEAS        MAX        MIN        DEV     OUTTOL
      M    NOMINAL  PLUSTOL  MINUSTOL     0.0000     0.0000     0.0000     0.0000     0.0000 #-------
                END_ELSE/
                ENDSUB/
    
    


    And this is the Visual Basic script (I'm sure my coding style is pretty bad, since this was my first time touching VB):

    
    Sub main( infile As String, scn1pntcnt As Long, scn2pntcnt As Long, Utarget As Double, Vtarget As Double, radius As Double, tolerance As Double )
      Dim U1 () As Double
      Dim V1 () As Double
      Dim U2 () As Double
      Dim V2 () As Double
      ReDim U1 (scn1pntcnt)
      ReDim V1 (scn1pntcnt)
      ReDim U2 (scn2pntcnt)
      ReDim V2 (scn2pntcnt)
    
      'Read In file data
      Dim file As Integer
      file = 1
      Open infile For Input As #file
      readarray U1, file, scn1pntcnt
      readarray V1, file, scn1pntcnt
      readarray U2, file, scn2pntcnt
      readarray V2, file, scn2pntcnt
      Close #file
    
      'Filter points To those within search radius
      Dim good_i_scn1 () As Long
      Dim good_i_scn2 () As Long
      ReDim good_i_scn1(scn1pntcnt)
      ReDim good_i_scn2(scn2pntcnt)
      filterpnts good_i_scn1, U1, V1, Utarget, Vtarget, radius
      filterpnts good_i_scn2, U2, V2, Utarget, Vtarget, radius
      If UBound(good_i_scn1) < 0 Then
        returnValues 1, -1, -1
        Exit Sub
      End If
      If UBound(good_i_scn2) < 0 Then
        returnValues 2, -1, -1
        Exit Sub
      End If
    
      'Brute force search For minimum distance within filtered points
      Dim smallest As Double
      Dim smallest_scn1 As Long
      Dim smallest_scn2 As Long
      smallest = (radius*2)^2
      smallest_scn1 = -1
      smallest_scn2 = -1
      bruteSearch smallest, smallest_scn1, smallest_scn2, good_i_scn1, good_i_scn2, U1, V1, U2, V2
      If smallest_scn1 = -1 Or smallest_scn2 = -1 Then
        returnValues 3, -1, -1
        Exit Sub
      End If
    
      'Check Tolerance
      If smallest > tolerance^2 Then
        returnValues 4, -1, -1
        Exit Sub
      End If
    
      'Return results, correcting For array indexing starting With 1 In pc-dmis
      smallest_scn1 = smallest_scn1 + 1
      smallest_scn2 = smallest_scn2 + 1
      returnValues 0, smallest_scn1, smallest_scn2
    End Sub
    
    
    Sub readarray( arr() As Double, infile As Integer, length As Long )
      Dim fileline As String
      Dim spcpos As Integer
      Dim lastpos As Integer
      Dim i As Integer
      Line Input #infile, fileline
      'Strip parentheses from String, slap space On End To make splitting up happy
      fileline = Mid(fileline, 2, len(fileline)-3) & " "
      spcpos = 1
      lastpos = 1
      For i  = 0 To length-1   
        spcpos = InStr(spcpos+1, fileline, " ")
        arr(i) = CDbl(Mid(fileline, lastpos, spcpos-lastpos))
        lastpos = spcpos
      Next
    End Sub
    
    
    Sub filterpnts( good_i() As Long, U() As Double, V() As Double, Utarget As Double, Vtarget As Double, radius As Double)
      Dim k As Long
      Dim i As Long
      k = 0
      For i = LBound(U) To UBound(U)
        If ((U(i) - Utarget)^2 + (V(i) - Vtarget)^2) < radius^2 Then
          good_i(k) = i
          k = k+1
        End If
      Next
      ReDim Preserve good_i (k-1)
    End Sub
    
    
    Sub bruteSearch(smallest As Double, smallest_scn1 As Long, smallest_scn2 As Long, _
                              good_i_scn1() As Long, good_i_scn2() As Long, U1() As Double, V1() As Double, U2() As Double, V2() As Double)
      Dim i As Long
      Dim j As Long
      Dim iloop As Long
      Dim jloop As Long
      Dim distsq As Double
      For iloop = LBound(good_i_scn1) To UBound(good_i_scn1)
        i = good_i_scn1(iloop)
        For jloop = LBound(good_i_scn2) To UBound(good_i_scn2)
          j = good_i_scn2(jloop)
          distsq = (U1(i) - U2(j))^2 + (V1(i) - V2(j))^2
          If distsq < smallest Then
            smallest = distsq
            smallest_scn1 = i
            smallest_scn2 = j
          End If
        Next
      Next
    End Sub
    
    Sub returnValues( ExitStatus As Integer, smallest_scn1 As Long, smallest_scn2 As Long )
      Dim app As Object
      Set app=CreateObject("PCDLRN.Application")
      Dim part As Object
      Set part=app.ActivePartProgram
      Dim var As Object
      Set var = part.GetVariableValue("EXITSTATUS")
      var.LongValue = ExitStatus
      part.SetVariableValue "EXITSTATUS", var
      Set var = part.GetVariableValue("SMALLEST_SCN1")
      var.LongValue = smallest_scn1
      part.SetVariableValue "SMALLEST_SCN1", var
      Set var = part.GetVariableValue("SMALLEST_SCN2")
      var.LongValue = smallest_scn2
      part.SetVariableValue "SMALLEST_SCN2", var
      'Does your head hurt yet?
    End Sub
    
    


    I wanted to throw that out there for the sake of the next poor guy who needs to do something like this. Slight smile Thank you for your suggestions, everybody! I may also try the curve-plane intersection technique at some point, but this is working for now.
  • Yes, you can get some drift perpendicular to the path direction. If you use closed loop scanning there will be almost none since the controller actively works to stay on the cut plane. If you use defined path scanning there can be a bit more since there is nothing in the controller algorithm that forces it back to the cutplane if it starts to drift. In any of my applications this sort of drift has never been significant. If it matters to you then you can easily write a routine to project the scan points perpendicular to their normal vectors back to the cut plane. That would be a piece of cake compared to the code you just posted below.
  • Thank you for explaining that further. The VB script is working well so far - I'll keep the geometric solution in mind, though.