home *** CD-ROM | disk | FTP | other *** search
/ Simtel MSDOS - Coast to Coast / simteldosarchivecoasttocoast.iso / printer / cal2tek.lib < prev    next >
Internet Message Format  |  1994-03-07  |  20KB

  1. Date:      Sat, 13 Feb 88 09:57:28 PST
  2. From:     MFENET%MIT.MFENET@NMFECC.ARPA
  3. Subject:   NERUS::CASEY@MIT.MFENET
  4. To:       HICKS@WALKER-EMH.ARPA
  5.  
  6. NOTE: TO RESPOND TO THIS MESSAGE, PUT THE USERNAME INTO THE SUBJECT LINE.
  7.  
  8.  
  9.                                         2/13/88
  10. Hi -
  11.  
  12.         This is the source code for CAL2TEK.  I had put the whole thing
  13. together into an ARC file with an executable, but I don't know how to send
  14. a bit file over ARPAnet mail.  If you want it, let me know how to send it,
  15. or if you're really desperate, I could mail you a disk.  Otherwise, these
  16. are the three other files that I included in the ARC.  1st is the DOC file,
  17. 2nd the FORTRAN source (MS version 4, although it should work with version 3),
  18. 3rd the MASM source for the subroutine -- it really isn't necessary, but 
  19. allows grabbing the filename as a parameter in the DOS command line.  You
  20. could always eliminate the assembly routine and add a query in the FORTRAN
  21. source, but that isn't professional, and it wouldn't be my code.
  22.  
  23.         I emphasize that this is an implementation that was hacked for my
  24. immediate needs, and has now been tested on only two other implementations,
  25. so you may find bugs -- PLEASE let me know of them.  
  26.  
  27.         I also just wrote a similar utility that replaces the PRTSCRN function
  28. with a HERCULES to LN03+ conversion (dumping a file that prints in sixel
  29. format).  Note that this has only the pixel resolution inherent in the
  30. HERC screen, while CAL2TEK plots vectors to the LN03+ printer.  As a 
  31. comparison, you can PLOT with AutoCAD, convert and print using CAL2TEK, and
  32. get a very sexy, publication quality plot.  You can also capture the screen
  33. with HERCLN3 while running AutoCAD, and plot it on the same printer, and it
  34. looks like a crude draft - i.e. a photograph of the screen.  I'm not satisfied
  35. that all the bugs are out of HERCLN3 yet, so if I send it to you, I'd rather
  36. it didn't propagate until I'm happy with it.  Also, I'm not anxious to send
  37. out the source code for it -- I'm dangling it as bait to get some shareware $$
  38. back to me.  You can have the source if you're willing to experiment and
  39. feed back comments.  Go ahead and propagate CAL2TEK anywhere.
  40.  
  41.                                         enjoy!
  42.                                                 Jeff Casey
  43.                                                 (617)861-1752 home
  44.                                                 (617)253-0885 work
  45.  
  46. ----------------- CAL2TEK.DOC ---------------------
  47.  
  48.         Version 1.1
  49.         1/19/88
  50.         CAL2TEK
  51.  
  52.  
  53.         PURPOSE:
  54.             Transform CALCOMP 81 format (such as produced by AutoCAD)
  55.         into a format printable on a DEC LN03+ laserprinter (via uploading
  56.         from IBM PC compatible to local mainframe such as a VAX).
  57.  
  58.  
  59.         USE:
  60.             CAL2TEK followed by the filename (type .PLT assumed) and 
  61.         an optional qualifier (/B) for thicker (bold) linewidths.
  62.         Example:
  63.  
  64.                 CAL2TEK plan /b
  65.  
  66.         converts PLAN.PLT to PLAN.TEK, with thicker linewidths on.
  67.         PLAN.PLT is unaffected.  PLAN.TEK can be uploaded to a mainframe
  68.         and plotted on an LN03.
  69.  
  70.  
  71.         OTHER NOTES:
  72.             This program is a quick kludge for a specific need of the author.
  73.         It has been tested on only one implementation.  The source code
  74.         is included, so that modifications may be made for other setups.
  75.         Only the pen up, pen down, and plot commands were translated,
  76.         as a complete definition of the CALCOMP instruction set was not
  77.         available.  I would appreciate any comments, improvements, or changes.
  78.         If you distribute this to other parties, however, please only 
  79.         distribute the original version complete with all source files
  80.         and this notice.
  81.  
  82.             CAL2TEK was compiled with Microsoft Fortran V4.00.  The subroutine
  83.         GETPAR was assembled with IBM/Microsoft Macro Assembler V2.00.  CAL2TEK
  84.         was linked with Microsoft Linker V3.55.
  85.  
  86.             The LN03 offers improved resolution over the TEKTRONIX graphics
  87.         format, which has been incorporated here.  If this program is used
  88.         for a TEK graphics device that does not support this feature, the
  89.         two lines of code sending the "extra byte" can be commented out,
  90.         (as noted in the source code) and it should(!) work properly.
  91.  
  92.  
  93.         SHAREWARE NOTICE:
  94.             This software is distributed free of charge.  If you use it,
  95.         you were probably in as big a bind as the author, and you will
  96.         be overjoyed to support the shareware philosophy by sending your
  97.         contributions to the address below.  Contributions of $25 or more
  98.         will entitle you to free upgrades of future versions, and a
  99.         TSR (terminate & stay resident) PRTSCRN replacement that will
  100.         convert Hercules format graphics to LN03 output that will be
  101.         written in the near future.
  102.  
  103.         COPYRIGHT/LICENSE/WARRANTY:
  104.             This document, and the current version of the source code 
  105.         files CAL2TEK.FOR and GETPAR.ASM are copyrighted by the author.
  106.         The copyright owner hereby licenses you to: use the software; 
  107.         make as many copies of the program and documentation as you wish;
  108.         give such copies to anyone; and distribute the software and
  109.         documentation via electronic means.
  110.  
  111.             However, you are specifically prohibited from charging, or
  112.         requesting donations, for any such copies, however made.  An
  113.         exception is granted to recognized not-for-profit user's groups
  114.         which are authorized to charge a small fee for materials, handling, 
  115.         postage, and general overhead.  NO FOR-PROFIT ORGANIZATION IS 
  116.         AUTHORIZED TO CHARGE ANY AMOUNT FOR DISTRIBUTION OF COPIES OF THE 
  117.         SOFTWARE OR DOCUMENTATION.
  118.  
  119.         No copy of the software may be distributed or given away without
  120.         this document; and this notice must not be removed.
  121.  
  122.         There is no warranty of any kind, and the copyright owner is not
  123.         liable for damages of any kind.  By using the software, you
  124.         agree to this.
  125.  
  126.         The software and documentation are:
  127.  
  128.                             Copyright (c) 1988 by
  129.                               Jeffrey A. Casey
  130.                            782 Massachusetts Ave.
  131.                             Lexington, MA  02173
  132.                                (617)861-1752
  133.  
  134. -------------------- CAL2TEK.FOR ----------------------------
  135.  
  136. $storage:2
  137.         program cal2tek
  138. c
  139. c                               version 1.1   1/19/88
  140. C
  141. C               TRANSFORMS AutoCAD OUTPUT FOR CALCOMP 81 PLOTTER
  142. C               INTO DEC LN03 (TEKTRONIX) FORMAT
  143. c
  144. c               supports drawing on 2752x1687 field, to tek
  145. c               4096x3072 field; pen up, pen down commands.
  146. c               ignores all else.  can set entire plot to 
  147. c               thicker linewidth with /bold option.
  148. c
  149. c               CAL2TEK file [/bold]
  150. c                 looks for file.PLT as input, translates
  151. c                 to tektronix format, and writes file.TEK
  152. c
  153. c        This software copyrighted by the author.  
  154. c        The copyright owner hereby licenses you to: use the software; 
  155. c        make as many copies of the program and documentation as you wish;
  156. c        give such copies to anyone; and distribute the software and
  157. c        documentation via electronic means.
  158. c
  159. c        However, you are specifically prohibited from charging, or
  160. c        requesting donations, for any such copies, however made.  An
  161. c        exception is granted to recognized not-for-profit user's
  162. c        groups, which are authorized to charge a small fee for 
  163. c        materials, handling, postage, and general
  164. c        overhead.  NO FOR-PROFIT ORGANIZATION IS AUTHORIZED TO CHARGE
  165. c        ANY AMOUNT FOR DISTRIBUTION OF COPIES OF THE SOFTWARE OR
  166. c        DOCUMENTATION.
  167. c
  168. c        No copy of the software may be distributed or given away without
  169. c        the accompanying document; and this notice must not be removed.
  170. c
  171. c        There is no warranty of any kind, and the copyright owner is not
  172. c        liable for damages of any kind.  By using the software, you
  173. c        agree to this.
  174. c
  175. c        The software and documentation are:
  176. c
  177. c                             Copyright (c) 1988 by
  178. c                               Jeffrey A. Casey
  179. c                            782 Massachusetts Ave.
  180. c                           Lexington, MA  02173
  181. c                               (617)861-1752
  182. c
  183. c
  184. c
  185. C
  186.         integer nx, ny, lx, ly
  187.         integer*1 out(200)
  188.         character*1 line(1024), file1(15), file2(15), msg(15)
  189.         character*15 f1,f2
  190.         equivalence (file1(1),f1), (file2(1),f2)
  191.         logical sp, cpen, tpen, eof, bold
  192.         common out, iout, lx, ly
  193. C
  194. C                       GET INPUT PARAMETERS (FILE NAMES)
  195.         bold = .false.
  196.         call getpar (n,50,line)
  197.         if (n .lt. 2) goto 9998
  198.         ifile = 0
  199.         len1 = 0
  200.         do 10 i = 1, n
  201.           sp = .false.
  202.           if ((line(i) .eq. ' ') .or. (line(i) .eq. ',') 
  203.      +          .or. (line(i) .eq. '-') .or. (line(i) .eq. '/')
  204.      +          .or. (line(i) .eq. '.')) sp = .true.
  205.           if (ifile .eq. 0) then
  206.             if (.not. sp) then
  207.               ifile = 1
  208.               len1 = 1
  209.               file1(1) = line(i)
  210.             end if
  211.           else if (ifile .eq. 1) then
  212.             if (sp) then
  213.               ifile = 2
  214.             else
  215.               len1 = len1 + 1
  216.               file1(len1) = line(i)
  217.             end if
  218.           else
  219.             if ((line(i) .eq. 'b') .or. (line(i) .eq. 'B'))
  220.      +          bold = .true.
  221.           end if
  222. 10      continue
  223.         if (len1 .eq. 0) goto 9998
  224. C
  225. 15      file1(len1+1) = '.'
  226.         file1(len1+2) = 'p'
  227.         file1(len1+3) = 'l'
  228.         file1(len1+4) = 't'
  229.         file1(len1+5) = char(0)
  230.         do 16 i = 1, len1+5
  231.           file2(i) = file1(i)
  232. 16      continue
  233.         file2(len1+2) = 't'
  234.         file2(len1+3) = 'e'
  235.         file2(len1+4) = 'k'
  236.         open (1,file=f1,status='old',err=9998,form='binary')
  237.         open (2,file=f2,status='new',err=9998,form='binary')
  238. C
  239. C                       INITIALIZE TEKTRONIX MODE IN ln03
  240. C                       TURN ON GRAPHICS MODE
  241.         if (bold) then
  242.           write (2) char(27), '[','?','3','8','h', char(27), 
  243.      +          'h', char(29)
  244.         else
  245.           write (2) char(27), '[','?','3','8','h', char(29)
  246.         end if
  247.         iout = 0
  248.         imsg = 0
  249.         cpen = .false.
  250.         tpen = .false.
  251.         eof = .false.
  252.         nx = 0
  253.         ny = 0
  254.         lx = 0
  255.         ly = 0
  256.         nstate = 0
  257. C       
  258. C                       INITIALIZE INPUT LINE, READ (APPENDED)
  259. 100     ii = 1
  260.         do 110 i = 1, 1024
  261.           line(i) = char(0)
  262. 110     continue
  263.         read (1,end=1000) (line(i),i=1,1024)
  264. C
  265. C                       PROCESS NEXT CHARACTER
  266. 200     if (line(ii) .ne. ';') then
  267. C
  268. C                       ADD TO MESSAGE
  269.           if ((line(ii) .ge. '0') .and. (line(ii) .le. '9')) then
  270. C
  271. C                       NUMERAL - PROCESS NUMBER
  272.             if (nstate .eq. 1) then
  273. C                       APPEND TO EXISTING x
  274.               if (nxx .ge. 4) then
  275.                 write (*,*) 'abort - X > 9999 found'
  276.                 stop
  277.               end if
  278.               nxx = nxx + 1
  279.               nxt = 10*nxt + ichar(line(ii))-48
  280.             else if (nstate .eq. 3) then
  281. C                       APPEND TO EXISTING y
  282.               if (nyy .ge. 4) then
  283.                 write (*,*) 'abort - Y > 9999 found'
  284.                 stop
  285.               end if
  286.               nyy = nyy + 1
  287.               nyt = 10*nyt + ichar(line(ii))-48
  288.             else if (nstate .eq. 0) then
  289. C                       INITIALIZE x
  290.               nxx = 1
  291.               nxt = ichar(line(ii))-48
  292.               nstate = 1
  293.             else if (nstate .eq. 2) then
  294. C                       INITIALIZE y
  295.               nyy = 1
  296.               nyt = ichar(line(ii))-48
  297.               nstate = 3
  298.             else
  299. C                       IMPOSSIBLE
  300.               write (*,*) 'abort - apparent 3 parameter entry'
  301.               stop
  302.             end if
  303.           else
  304. C                       NOT NUMERAL ENTRY
  305.             if (nstate .eq. 1) then
  306. C                       IN x STATE
  307.               lx = nx
  308.               nx = nxt
  309.               nstate = 2
  310.             else if (nstate .eq. 3) then
  311. C                       IN y STATE
  312.               ly = ny
  313.               ny = nyt
  314.               nstate = 4
  315.             end if
  316.             imsg = imsg + 1
  317.             msg(imsg) = line(ii)
  318.           end if
  319.         else 
  320. C                       THIS IS A COMMAND END ';'
  321.           if ((imsg .eq. 1) .and. (msg(1) .eq. 'H')) then
  322. C                       PEN UP
  323.             cpen = .false.
  324.           else if ((imsg .eq. 1) .and. (msg(1) .eq. 'I')) then
  325. C                       PEN DOWN
  326.             cpen = .true.
  327.           else if (msg(imsg) .eq. 'K') then
  328. C                       PLOT
  329.             if (cpen) then
  330.               if (tpen) then
  331.                 call plot (nx,ny)
  332.               else
  333.                 call plot (lx,ly)
  334.                 call plot (nx,ny)
  335.                 tpen = .true.
  336.               end if
  337.             else
  338.               if (tpen) then
  339.                 iout = iout + 1
  340.                 out(iout) = int1(29)
  341.                 call plot (nx,ny)
  342.               else
  343.                 call plot (nx,ny)
  344.                 tpen = .true.
  345.               end if
  346.             end if
  347. C
  348.           end if
  349.           imsg = 0
  350.           nstate = 0
  351.         end if
  352. C
  353.         ii = ii + 1
  354.         if (ii .gt. 1024) then
  355.           if (eof) goto 2000
  356.           if (.not. eof) goto 100
  357.         end if
  358. C
  359.         if (iout .gt. 128) then
  360.           write (2) (out(i),i=1,128)
  361.           do 900 i = 129, iout
  362.             out(i-128) = out(i)
  363. 900       continue
  364.           iout = iout - 128
  365.         end if
  366. C
  367.         goto 200
  368. C
  369. C                       END OF FILE READ
  370. 1000    eof = .true.
  371.         goto 200
  372. C
  373. 2000    if (iout .ge. 0) write (2) (out(i),i=1,iout),
  374.      +          char(27),'[','!','p'
  375. C                       TEKTRONIX MODE IS NOW OFF AND BUFFER PURGED.    
  376.         goto 9999
  377. C             
  378. 9998    write (*,*) 'useage:  CAL2TEK file [/b]       (no extension)'
  379.         write (*,*) 'transforms:    file.PLT ==> file.TEK'
  380.         write (*,*) 'file.TEK must not exist'
  381.         write (*,*) '/b option uses BOLD (thicker lines)'
  382. 9999    close (1)
  383.         close (2)
  384.         end
  385.  
  386.  
  387.  
  388.         subroutine plot (nx,ny)
  389.         integer*1 out(200)
  390.         integer i(5), nx, ny, lx, ly, n1, n2
  391.         common out, iout, lx, ly
  392.         logical xmin,xmax,ymin,ymax
  393.         data xmin/.false./,xmax/.false./,ymin/.false./,ymax/.false./
  394. C
  395.         if (nx .lt. 0) then
  396.           if (.not. xmin) write (*,*) 'warning, truncating x < 0'
  397.           xmin = .true.
  398.           nx = 0
  399.         else if (nx .gt. 2752) then
  400.           if (.not. xmax) write (*,*) 'warning, truncating x > 2752'
  401.           xmax = .true.
  402.           nx = 2752
  403.         end if
  404.         if (ny .lt. 0) then
  405.           if (.not. ymin) write (*,*) 'warning, truncating y < 0'
  406.           ymin = .true.
  407.           ny = 0
  408.         else if (ny .gt. 1687) then
  409.           if (.not. ymax) write (*,*) 'warning, truncating y > 1687'
  410.           ymax = .true.
  411.           ny = 1687
  412.         end if
  413. C
  414.         n1 = int(float(nx)/2752.*4095.+.5)
  415.         n2 = int(float(ny)/1687.*3071.+.5)
  416. C
  417. C               HI Y BYTE:  BITS 8-12 Y SHIFTED RIGHT, FLAG BIT 6
  418.         iout = iout + 1
  419.         out(iout) = int1(n2/128 + 32)
  420. C               EXTRA BYTE: BITS 1-2 Y SHIFTED LEFT, BITS 1-2 X, FLAG BITS 6&7
  421. c       ***NOTE:  for non LN03 TEKTRONIX graphics devices which do not
  422. c               support the "higher resolution" mode, the next two lines
  423. c               of source must be commented out.
  424.         iout = iout + 1
  425.         out(iout) = int1((n2 - 4*(n2/4))*4 + (n1 - 4*(n1/4)) + 96)
  426. C               LO Y BYTE:  BITS 3-7 Y SHIFTED RIGHT, FLAG BITS 6&7
  427.         iout = iout + 1
  428.         out(iout) = int1((n2 - 128*(n2/128))/4 + 96)
  429.         if (out(iout) .eq. 127) then
  430.           out(iout) = int1(27)
  431.           iout = iout + 1
  432.           out(iout) = int1(63)
  433.         end if
  434. C               HI X BYTE:  BITS 8-12 X SHIFTED RIGHT, FLAG BIT 6
  435.         iout = iout + 1
  436.         out(iout) = int1(n1/128 + 32)
  437. C               LO X BYTE:  BITS 3-7 X SHIFTED RIGHT, FLAG BIT 7
  438.         iout = iout + 1
  439.         out(iout) = int1((n1 - 128*(n1/128))/4 + 64)
  440. C
  441.         return
  442.         end
  443.  
  444. ----------------------- GETPAR.ASM -------------------
  445.  
  446. ;
  447. ;       This software is distributed as support for version 1
  448. ;       of CAL2TEK.  It is copyrighted by the author.  
  449. ;       Conditions of the copyright are listed in the accompanying
  450. ;       file CAL2TEK.DOC.  This software may not be distributed
  451. ;       without the accompanying documentation, and this notice
  452. ;       may not be removed.
  453. ;
  454. ;       There is no warranty of any kind, and the copyright owner is not
  455. ;       liable for damages of any kind.  By using the software, you
  456. ;       agree to this.
  457. ;
  458. ;       The software and documentation are:
  459. ;
  460. ;                             Copyright (c) 1988 by
  461. ;                               Jeffrey A. Casey
  462. ;                            782 Massachusetts Ave.
  463. ;                           Lexington, MA  02173
  464. ;                               (617)861-1752
  465. ;--------------------------------------------------------------------
  466. ;
  467. ;
  468. ;               FORTRAN subroutine GETPAR (N,M,LINE)
  469. ;               returns command line parameters
  470. ;               N (INT*2)  number of characters returned
  471. ;               M (INT*2)  maxlength of LINE
  472. ;               LINE (CHAR*M) array of characters
  473. ;
  474. ;                       J. Casey    5/10/87
  475. ;
  476. TITLE   GETPAR - get calling parameters returned to program
  477. ;       (assy to fortran interface)
  478. ;
  479. CODE    SEGMENT 'CODE'
  480. ASSUME CS:CODE
  481. PUBLIC  GETPAR
  482. ;
  483. ;
  484. GETPAR  PROC    FAR
  485. ;
  486.         PUSH    BP                      ;Save framepointer on stack
  487.         MOV     BP,SP
  488.         push    ds
  489.         push    dx
  490.         push    cx
  491.         push    bx
  492.         push    ax
  493. ;
  494. ;
  495.         mov     ah,62h
  496.         int     21h                     ;get psp address, ret in BX
  497.         mov     ds,bx                   ;set DS to psp address
  498.         mov     bx,80h                  ;set offset to 80H (DOS param line)
  499.         mov     al,[bx]                 ; then steal the count
  500.         mov     ah,0                    ; and make it INT*2 size
  501. ;
  502.         inc     bx                      ;increment to start of string,
  503.         mov     si,bx                   ; save location of param string
  504. ;
  505.         LES     BX,DWORD PTR [BP+14]    ;ES,BX = addr of 1st param
  506.         mov     es:[bx],ax              ; return #chars
  507. ;
  508.         LES     BX,DWORD PTR [BP+10]    ;ES,BX = addr of 2nd param
  509.         mov     cx,es:[bx]              ; cx = max length returned
  510. ;
  511.         LES     BX,DWORD PTR [BP+6]     ;ES,BX = addr of 3rd param (line)
  512. ;
  513. loop:   cmp     ax,0
  514.         jle     home
  515.         cmp     cx,0
  516.         jle     home
  517.         push    bx
  518.         mov     bx,si
  519.         mov     dx,[bx]                 ;dx now has next character of 
  520.         pop     bx                      ;   param string
  521.         mov     es:[bx],dx              ;put it in LINE text string
  522.         inc     bx
  523.         inc     si
  524.         dec     ax
  525.         dec     cx
  526.         jmp     loop
  527. ;
  528. home:   pop     ax
  529.         pop     bx
  530.         pop     cx
  531.         pop     dx
  532.         pop     ds
  533.         MOV     SP,BP                   ;Restore framepointer
  534.         POP     BP
  535.         RET     0CH                     ;return, pop 12 bytes
  536. ;
  537. GETPAR  ENDP
  538. CODE    ENDS
  539. END
  540.