0% found this document useful (0 votes)
109 views12 pages

Excel VBA ActiveX Controls - Easy Excel Macros

The document describes Autolisp functions for drawing cross sections in AutoCAD, calculating areas and distances. It includes functions to draw cross sections (c:ms), calculate the area of a selected entity and write it to a file (c:as), and calculate the total distance between selected points and write it to a file (c:ds). It provides settings, commands and logic to select entities, calculate values, and output text.

Uploaded by

kavyadeepam
Copyright
© © All Rights Reserved
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
109 views12 pages

Excel VBA ActiveX Controls - Easy Excel Macros

The document describes Autolisp functions for drawing cross sections in AutoCAD, calculating areas and distances. It includes functions to draw cross sections (c:ms), calculate the area of a selected entity and write it to a file (c:as), and calculate the total distance between selected points and write it to a file (c:ds). It provides settings, commands and logic to select entities, calculate values, and output text.

Uploaded by

kavyadeepam
Copyright
© © All Rights Reserved
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
You are on page 1/ 12

6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances

http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 1/12
applications
my vb or matlab or autolisp or
c++ applications
previous posts
Autolisp : Prepare Long
Section Data
Autolisp : Draw Trench
Autolisp : Set Contour
Elevations
AutoLisp Code For
Calculating Sum Of Line
Segments...
VB6 :General 2D
Transformation
My File Statistics in VB(
Forms + modules)
MATLAB : WGS84 to EN
FILE STATISTICS
tuesday, august 31, 2004
Autolisp : Draw Cross Sections/Calculate Area/
Distances
VOLUTIL.LSP
------------------------
(defun c:ad()
(setq layer_number (getstring "Enter No. Of Layer :"))

;settings
(setq topo_layer "topography_line_of_ff")
(setq proj_layer "project_line_of_ff")
(setq area_layer (strcat "area" layer_number))
(setq excavation_level_layer (strcat "exc_lev" layer_number))
(setq area_layer_color "242")

(command "layer" "thaw" "*"
"on" "*"
""
""
)

(command "layer" "m" area_layer
"s" area_layer
"c" area_layer_color
""
""
)

(setq lay1 (strcat proj_layer layer_number))
(setq lay2 (strcat topo_layer layer_number))

;freez/off all layers except current layer
(command "layer" "f" "*" "")

;thaw and on proj_line and topo_line and excavation_level of current
number of layers
(command "layer" "thaw" lay2 "on" lay2 "")
; (command "layer" "thaw" excavation_level_layer "on"
; excavation_level_layer "")
(command "layer" "thaw" lay1 "on" lay1 "")

)

;**********************************************************
; ALI-ZAMIR ROSHAN , TEHRAN UNIVERSITY
; FACULTY OF ENGINEERING
; SURVEYING ENGINEEERING DEPARTMENT
0

More

Next Blog Create Blog

Sign In
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 2/12
;**********************************************************

;80/05/12 to write area of an object in file areas.xls
(defun c:as()

;settings
(setq th 2.5);text height
(setq p1 '(3160 1161.3)) ;point to write area and perimeter
(setq current_layer (getvar "clayer"))

;make a region to get area
(setq internal_point (getpoint "\nSelect Internal Point :"))
(command "bpoly" internal_point "")

(command "style" "romanc"
"romanc.shx"
th
"1"
"0"
""
""
""
)
(setq ent (entsel "\nSelect Entity To Get Area :"))
(command "area" "e" ent)
(setq a (getvar "area"))
(setq per (getvar "perimeter"))
(setq aa (strcat "AREA = " (rtos a 2 2)))
(setq pp (strcat "PERIMETER = " (rtos per 2 2)))

(setq area_text (strcat current_layer
" = "
(rtos a 2 3)
)
)

;write area and layer number in file areas.xls
(setq filex (open "areas.xls" "a"));
(princ area_text filex)
(princ "\n" filex)
(princ area_text)
(princ "\n")

(close filex);

; (setq p2 (list (car p1) (- (cadr p1) (* 1.8 th))))
(command "TEXT" p1 0 aa)
; (command "TEXT" p2 0 pp)

)

;**********************************************************
; ALI-ZAMIR ROSHAN , TEHRAN UNIVERSITY
; FACULTY OF ENGINEERING
; SURVEYING ENGINEEERING DEPARTMENT
;**********************************************************
;80/05/27 to write sum of afew distances in file dists.xls
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 3/12
;80/07/14
(defun c:ds()

;settings
(setq th 2);text height
(setq p1 '(3205 1161.3)) ;point to write area and perimeter
(setq curlayer (getvar "clayer"))
(setq surf_length_layer (strcat "surf_length " curlayer))

(command "style" "romanc"
"romanc.shx"
th
"1"
"0"
""
""
""
)
(setq dis 0.0)
(while (setq len (getdist "\nSelect Distance :"))
(setq dis (+ dis len));

)

(setq dd (strcat "Slope Length = " (rtos dis 2 3)))
(setq len_text (strcat surf_length_layer
" = "
(rtos dis 2 3)
)
)

;write surf Length and layer number in file dists.xls
(setq filex (open "dists.xls" "a"));
(princ len_text filex)
(princ "\n" filex)
(princ len_text)
(princ "\n")
(close filex);
(command "TEXT" p1 0 dd)
)
(PRINC "\n")
(princ "CHANGE SECTION : AD ***** ")
(princ "GET AREA : AS ***** ")
(princ "GET DISTS. SUM: DS")(PRINC "\n")
-----------------
MSE5.LSP
-----------------
;**********************************************************
; ALI-ZAMIR ROSHAN , TEHRAN UNIVERSITY
; FACULTY OF ENGINEERING
; SURVEYING ENGINEERING DEPARTMENT
;**********************************************************
;program to draw section from 3dlines or 3dpolylines
;77/11/27
;3:02 AM 2/16/99
;revised for automatic layer management 80/05/09 21:00
;revised for selection of all section lines at once 80/08/9 10:45 am
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 4/12
;!!!warning :in this program 3dlines must not be in x-x or y-y direction
;and each line of topography has to be in its elevation and must not
;be arc or spline ,besides before applying this program all polylines of
;topography have to be exploded and ucs must be world.
;it is recommended to rotate figure ,the direction inwhich section lines
become vertival

(defun c:ms()
;initial settings
(setvar "cmdecho" 0)
(setq pnts nil ;list of coordinates of intersection points
d_lst nil;list of distances to first point
)
;make new current layer

(setq id (load_dialog "mse4"))
(new_dialog "mse4" id)

(setq is_proj 1);
(setq is_topo 0);

(action_tile "mycol" "(do_color)")
(action_tile "proj_line" "(do_proj)")
(action_tile "topo_line" "(do_topo)")
(action_tile "accept" "(done_dialog)")
(start_dialog)

;select section lines
(setq sset (ssget))
(setq n_lines (sslength sset))
(setq l_index 0)

(repeat n_lines
;reset variables for next section
(setvar "cmdecho" 0)
(setq pnts nil ;list of coordinates of intersection points
d_lst nil;list of distances to first point
; b_lst nil
; bb_lst nil
; tem nil
)
(setq b (entget (ssname sset l_index)))

(setq sec_layer (cdr (assoc 8 b))) ;layer of line selected
(setq p1 (cdr (assoc 10 b)))
(setq p2 (cdr (assoc 11 b)))

;make project or topography section line layer name
(PRINC IS_TOPO)(PRINC IS_PROJ)
(if (= 1 is_proj)
(progn
(setq layer (strcat "Project_line_of_" sec_layer))
(command "layer" "m" layer "s" layer "c" col "" "")
)
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 5/12
)
(if (= 1 is_topo)
(progn
(setq layer (strcat "Topography_line_of_" sec_layer))
(command "layer" "m" layer "s" layer "c" col "" "")
)
)
;get x,y of start and end of section line

(setq xyp1 (list (car p1) (cadr p1)))
(setq xyp2 (list (car p2) (cadr p2)))

;to get all lines in crossing of section line ends

(setq ss (ssget "c" xyp1 xyp2))
(setq nn (sslength ss))

;to prepare list of intersection points

(setq ii -1)
(princ nn) (princ "\n")
(repeat nn

;select 3dline (intersecting or not )

(setq ii (1+ ii)) (princ ii)(princ "\n")
(setq na (ssname ss ii))
(setq bb (entget na))

;to see if the entity is line

(setq dd (assoc 0 bb))
(setq typ (cdr dd))
(if (= typ "LINE")
(progn
(setq p3 (cdr (assoc 10 bb)))
(setq p4 (cdr (assoc 11 bb)))

;get x,y of start and end of 3dline

(setq xyp3 (list (car p3) (cadr p3)))
(setq xyp4 (list (car p4) (cadr p4)))

;to see if 3dline intersect section line if so, get x,y of
;intersection point of section (elev = 0)

(setq ip (inters xyp1 xyp2 xyp3 xyp4))

(if (/= ip nil) ;3dline intersects section line
(progn
(setq xip (car ip))
(setq yip (cadr ip))

;get coordinates of start point of 3dline

(setq x3 (car p3))
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 6/12
(setq y3 (cadr p3))
(setq z3 (caddr p3))

;get coordinates of end point of 3dline

(setq x4 (car p4))
(setq y4 (cadr p4))
(setq z4 (caddr p4))

;get z coordinate of intersection point on the 3dline

(setq k (/ (- xip x3) (- x4 x3)))
(setq zip (+ z3 (* k (- z4 z3))))

;to prepare list of intersection points

(setq pnt1 (list xip yip zip))
(setq pnts (append pnts (list pnt1)))
(princ pnt1)(princ "\n")
);progn end
) ;if end
) ;progn end
) ;if end

);repeat end
(princ "out")(princ "\n")

;to prepare list of distances from begining of section line

(setq len (length pnts)) ;number of points in section
(setq pp1 xyp1 );begining of section line
(setq jj 0)
(repeat len
(setq pp (list (car (nth jj pnts)) (cadr (nth jj pnts))))
(setq dj (distance pp pp1))
(setq d_lst (append d_lst (list dj)))
(setq jj (1+ jj))
)
(princ "distances :\n")(princ d_lst)(princ "\n")

;to draw section after sorting selected points

(setq a_lst nil
b_lst d_lst
)
(command "3dpoly") ;draw 3dpoly of section
(repeat len
(setq minim (apply 'min b_lst))

;loop to find index of minim in d_lst

(setq i 0)
(repeat len
(if (= (nth i d_lst) minim)
(setq index i)
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 7/12
)
(setq i (1+ i))
)

;add min(b_lst) to a_lst

(setq a_lst (append a_lst (list minim)))

;remove min(b_lst) from b_lst

(setq i 0)
(setq bb_lst b_lst)
(setq b_lst nil)
(repeat len
(setq tem (nth i bb_lst))
(if (and (/= tem minim) (/= tem nil))
(setq b_lst (append b_lst (list tem)))
)
(setq i (1+ i))
)
(setq pnt (nth index pnts))
(command pnt)
)
(command "")
(princ "l_index end =")(princ l_index)(princ "\n")
(setq l_index (1+ l_index)) ;to go to next section processing
);repeat end for sections

)

(defun do_color()
(setq col (acad_colordlg 220))
)
;select colors as global variables color1 ....color(n)
(defun set_color1()
(setq color1 (acad_colordlg 10))
(start_image "keyimage1")
(setq x (dimx_tile "keyimage1"))
(setq y (dimy_tile "keyimage1"))
(fill_image 0 0 x y color1)
(end_image)





)
(defun set_color2()
(setq color2 (acad_colordlg 20))
(start_image "keyimage2")
(setq x (dimx_tile "keyimage2"))
(setq y (dimy_tile "keyimage2"))
(fill_image 0 0 x y color2)
(end_image)

)
(defun set_color3()
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 8/12
(setq color3 (acad_colordlg 30))
(start_image "keyimage3")
(setq x (dimx_tile "keyimage3"))
(setq y (dimy_tile "keyimage3"))
(fill_image 0 0 x y color3)
(end_image)

)
(defun do_those()
(get_tile "keylayer1")
(setq pnt_lay (get_tile "keylayer1"))
(setq elev_lay (get_tile "keylayer2"))
(setq num_lay (get_tile "keylayer3"))

(setq pnt_col color1)
(setq elev_col color2)
(setq num_col color3)
)
(defun do_proj()
(setq is_proj 1);
(setq is_topo 0);
(PRINC IS_TOPO)(PRINC IS_PROJ)

)

(defun do_topo()
(setq is_topo 1)
(setq is_proj 0);
(PRINC IS_TOPO)(PRINC IS_PROJ)

)
----------------
MSE4.DCL
----------------
mse4:dialog{
label="Draw 3D Section(BBK)";
:boxed_column{
:radio_column{
label="Select Kind Of Section Line ";
:radio_button{
label="Project Line";
key="proj_line";
value="1";
}
:radio_button{
label="Topography Line";
key="topo_line";
mneomonic="T";
}

}
spacer_1;
:row{
:button{
label="Color For Section:";
key="mycol";
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 9/12
width=6;
height=2;
alignment=centered;
value="220";
}
}
spacer_1;
}
ok_only;
}
-------------------
MYAREA.LSP
-------------------
;**********************************************************
; ALI-ZAMIR ROSHAN , TEHRAN UNIVERSITY
; FACULTY OF ENGINEERING
; SURVEYING ENGINEEERING DEPARTMENT
;**********************************************************

;80/05/12 to write area of an object in file areas.xls
(defun c:as()

;settings
(setq th 2.5);text height
(setq p1 '(3160 1161.3)) ;point to write area and perimeter
(setq current_layer (getvar "clayer"))

;make a region to get area
(setq internal_point (getpoint "\nSelect Internal Point :"))
(command "bpoly" internal_point "")

(command "style" "romanc"
"romanc.shx"
th
"1"
"0"
""
""
""
)
(setq ent (entsel "\nSelect Entity To Get Area :"))
(command "area" "e" ent)
(setq a (getvar "area"))
(setq per (getvar "perimeter"))
(setq aa (strcat "AREA = " (rtos a 2 2)))
(setq pp (strcat "PERIMETER = " (rtos per 2 2)))

(setq area_text (strcat current_layer
" = "
(rtos a 2 3)
)
)

;write area and layer number in file areas.xls
(setq filex (open "areas.xls" "a"));
(princ area_text filex)
(princ "\n" filex)
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 10/12
(princ area_text)
(princ "\n")

(close filex);

; (setq p2 (list (car p1) (- (cadr p1) (* 1.8 th))))
(command "TEXT" p1 0 aa)
; (command "TEXT" p2 0 pp)

)
------------------
MYDISTS.LSP
------------------
;**********************************************************
; ALI-ZAMIR ROSHAN , TEHRAN UNIVERSITY
; FACULTY OF ENGINEERING
; SURVEYING ENGINEEERING DEPARTMENT
;**********************************************************
;80/05/27 to write sum of afew distances in file dists.xls
;80/07/14
(defun c:ds()

;settings
(setq th 2);text height
(setq p1 '(3205 1161.3)) ;point to write area and perimeter
(setq curlayer (getvar "clayer"))
(setq surf_length_layer (strcat "surf_length " curlayer))

(command "style" "romanc"
"romanc.shx"
th
"1"
"0"
""
""
""
)
(setq dis 0.0)
(while (setq len (getdist "\nSelect Distance :"))
(setq dis (+ dis len));

)

(setq dd (strcat "Slope Length = " (rtos dis 2 3)))
(setq len_text (strcat surf_length_layer
" = "
(rtos dis 2 3)
)
)

;write surf Length and layer number in file dists.xls
(setq filex (open "dists.xls" "a"));
(princ len_text filex)
(princ "\n" filex)
(princ len_text)
(princ "\n")
(close filex);
6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 11/12
posted by MyDispName @ 6:41 AM
(command "TEXT" p1 0 dd)
)
----------------
NSEC.LSP (lines for Section lines in elevation=0)
-------------------------------------------------
(defun c:nsec()
(setq cur_layer (getvar "clayer"))
;select longsection line
(setq a (entsel "\nselect a line for longsection :\n"))
(setq b (entget (car a)))
(setq pl1 (cdr (assoc 10 b)))
(setq pl2 (cdr (assoc 11 b)))

(setq pl3 (list
(+ (cadr pl1) 10) (car pl1)
)
)
(command "ucs" "3point" pl1 pl2 pl3)

(setq dxsec (getreal "Distance between cross sections:\n"))
(setq xsec_name (getstring "Cross sections name :\n"))
(setq xsec_len (getreal "Cross sections bandwidth :\n"))
(setq n_xsec (getint "Number of Cross sections :\n"))

(setq n_x 1)
(repeat n_xsec
(setq pa (list
(* (1- n_x) dxsec)
(/ xsec_len 2)
0
)
)
(setq pb (list
(* (1- n_x) dxsec)
(/ (* -1 xsec_len) 2)
0
)
)
;make layer name for each cross section
(setq layer_name (strcat xsec_name (itoa n_x)))



(command "layer" "m" layer_name "s" layer_name "c" "60" ""
"")
(command "line" pa pb "")
(setq n_x (1+ n_x))
)

(command "ucs" "")
(setvar "clayer" cur_layer)

)

6/29/2014 Applications: Autolisp : Draw Cross Sections/Calculate Area/ Distances
http://alicodes.blogspot.in/2004/08/autolisp-draw-cross-sectionscalculate.html 12/12
1 Comments:
Anonymous said...
This is a excellent prospect to avail this wonderful Scan Tool.
Pays transport expenditures for youShipping prices can get expensive.
My blog; obd 2 scan tool
5:06 PM
Post a Comment
<< Home

You might also like