1$! MKSHARED.COM -- script to created shareable images on VMS
2$!
3$! No command line parameters.  This should be run at the start of the source
4$! tree (the same directory where one finds INSTALL.VMS).
5$!
6$! Input:	[.UTIL]LIBEAY.NUM,[.xxx.EXE.CRYPTO]LIBCRYPTO.OLB
7$!		[.UTIL]SSLEAY.NUM,[.xxx.EXE.SSL]LIBSSL.OLB
8$! Output:	[.xxx.EXE.CRYPTO]LIBCRYPTO.OPT,.MAP,.EXE
9$!		[.xxx.EXE.SSL]LIBSSL.OPT,.MAP,.EXE
10$!
11$! So far, tests have only been made on VMS for Alpha.  VAX will come in time.
12$! ===========================================================================
13$
14$! ----- Prepare info for processing: version number and file info
15$ gosub read_version_info
16$ if libver .eqs. ""
17$ then
18$   write sys$error "ERROR: Couldn't find any library version info..."
19$   exit
20$ endif
21$
22$ if (f$getsyi("cpu").lt.128)
23$ then
24$     arch := VAX
25$ else
26$     arch = f$edit( f$getsyi( "ARCH_NAME"), "UPCASE")
27$     if (arch .eqs. "") then arch = "UNK"
28$ endif
29$
30$ if arch .nes. "VAX"
31$ then
32$   arch_vax = 0
33$   libid  = "Crypto"
34$   libnum = "[.UTIL]LIBEAY.NUM"
35$   libdir = "[.''ARCH'.EXE.CRYPTO]"
36$   libolb = "''libdir'LIBCRYPTO.OLB"
37$   libopt = "''libdir'LIBCRYPTO.OPT"
38$   libmap = "''libdir'LIBCRYPTO.MAP"
39$   libgoal= "''libdir'LIBCRYPTO.EXE"
40$   libref = ""
41$   if f$search(libdir+libolb) .nes. "" then gosub create_nonvax_shr
42$   libid  = "SSL"
43$   libnum = "[.UTIL]SSLEAY.NUM"
44$   libdir = "[.''ARCH'.EXE.SSL]"
45$   libolb = "''libdir'LIBSSL.OLB"
46$   libopt = "''libdir'LIBSSL.OPT"
47$   libmap = "''libdir'LIBSSL.MAP"
48$   libgoal= "''libdir'LIBSSL.EXE"
49$   libref = "[.''ARCH'.EXE.CRYPTO]LIBCRYPTO.EXE"
50$   if f$search(libdir+libolb) .nes. "" then gosub create_nonvax_shr
51$   arch_vax = 0
52$   libid  = "Crypto"
53$   libnum = "[.UTIL]LIBEAY.NUM"
54$   libdir = "[.''ARCH'.EXE.CRYPTO]"
55$   libolb = "''libdir'LIBCRYPTO32.OLB"
56$   libopt = "''libdir'LIBCRYPTO32.OPT"
57$   libmap = "''libdir'LIBCRYPTO32.MAP"
58$   libgoal= "''libdir'LIBCRYPTO32.EXE"
59$   libref = ""
60$   if f$search(libdir+libolb) .nes. "" then gosub create_nonvax_shr
61$   libid  = "SSL"
62$   libnum = "[.UTIL]SSLEAY.NUM"
63$   libdir = "[.''ARCH'.EXE.SSL]"
64$   libolb = "''libdir'LIBSSL32.OLB"
65$   libopt = "''libdir'LIBSSL32.OPT"
66$   libmap = "''libdir'LIBSSL32.MAP"
67$   libgoal= "''libdir'LIBSSL32.EXE"
68$   libref = "[.''ARCH'.EXE.CRYPTO]LIBCRYPTO32.EXE"
69$   if f$search(libdir+libolb) .nes. "" then gosub create_nonvax_shr
70$ else
71$   arch_vax = 1
72$   libtit = "CRYPTO_TRANSFER_VECTOR"
73$   libid  = "Crypto"
74$   libnum = "[.UTIL]LIBEAY.NUM"
75$   libdir = "[.''ARCH'.EXE.CRYPTO]"
76$   libmar = "''libdir'LIBCRYPTO.MAR"
77$   libolb = "''libdir'LIBCRYPTO.OLB"
78$   libopt = "''libdir'LIBCRYPTO.OPT"
79$   libobj = "''libdir'LIBCRYPTO.OBJ"
80$   libmap = "''libdir'LIBCRYPTO.MAP"
81$   libgoal= "''libdir'LIBCRYPTO.EXE"
82$   libref = ""
83$   libvec = "LIBCRYPTO"
84$   if f$search(libdir+libolb) .nes. "" then gosub create_vax_shr
85$   libtit = "SSL_TRANSFER_VECTOR"
86$   libid  = "SSL"
87$   libnum = "[.UTIL]SSLEAY.NUM"
88$   libdir = "[.''ARCH'.EXE.SSL]"
89$   libmar = "''libdir'LIBSSL.MAR"
90$   libolb = "''libdir'LIBSSL.OLB"
91$   libopt = "''libdir'LIBSSL.OPT"
92$   libobj = "''libdir'LIBSSL.OBJ"
93$   libmap = "''libdir'LIBSSL.MAP"
94$   libgoal= "''libdir'LIBSSL.EXE"
95$   libref = "[.''ARCH'.EXE.CRYPTO]LIBCRYPTO.EXE"
96$   libvec = "LIBSSL"
97$   if f$search(libdir+libolb) .nes. "" then gosub create_vax_shr
98$ endif
99$ exit
100$
101$! ----- Subroutines to build the shareable libraries
102$! For each supported architecture, there's a main shareable library
103$! creator, which is called from the main code above.
104$! The creator will define a number of variables to tell the next levels of
105$! subroutines what routines to use to write to the option files, call the
106$! main processor, read_func_num, and when that is done, it will write version
107$! data at the end of the .opt file, close it, and link the library.
108$!
109$! read_func_num reads through a .num file and calls the writer routine for
110$! each line.  It's also responsible for checking that order is properly kept
111$! in the .num file, check that each line applies to VMS and the architecture,
112$! and to fill in "holes" with dummy entries.
113$!
114$! The creator routines depend on the following variables:
115$! libnum	The name of the .num file to use as input
116$! libolb	The name of the object library to build from
117$! libid	The identification string of the shareable library
118$! libopt	The name of the .opt file to write
119$! libtit	The title of the assembler transfer vector file (VAX only)
120$! libmar	The name of the assembler transfer vector file (VAX only)
121$! libmap	The name of the map file to write
122$! libgoal	The name of the shareable library to write
123$! libref	The name of a shareable library to link in
124$!
125$! read_func_num depends on the following variables from the creator:
126$! libwriter	The name of the writer routine to call for each .num file line
127$! -----
128$
129$! ----- Subroutines for non-VAX
130$! -----
131$! The creator routine
132$ create_nonvax_shr:
133$   open/write opt 'libopt'
134$   write opt "identification=""",libid," ",libverstr,""""
135$   write opt libolb,"/lib"
136$   if libref .nes. "" then write opt libref,"/SHARE"
137$   write opt "SYMBOL_VECTOR=(-"
138$   libfirstentry := true
139$   libwrch   := opt
140$   libwriter := write_nonvax_transfer_entry
141$   textcount = 0
142$   gosub read_func_num
143$   write opt ")"
144$   write opt "GSMATCH=",libvmatch,",",libver
145$   close opt
146$   link/map='libmap'/full/share='libgoal' 'libopt'/option
147$   return
148$
149$! The record writer routine
150$ write_nonvax_transfer_entry:
151$   if libentry .eqs. ".dummy" then return
152$   if info_kind .eqs. "VARIABLE"
153$   then
154$     pr:=DATA
155$   else
156$     pr:=PROCEDURE
157$   endif
158$   textcount_this = f$length(pr) + f$length(libentry) + 5
159$   if textcount + textcount_this .gt. 1024
160$   then
161$     write opt ")"
162$     write opt "SYMBOL_VECTOR=(-"
163$     textcount = 16
164$     libfirstentry := true
165$   endif
166$   if libfirstentry
167$   then
168$     write 'libwrch' "    ",libentry,"=",pr," -"
169$   else
170$     write 'libwrch' "    ,",libentry,"=",pr," -"
171$   endif
172$   libfirstentry := false
173$   textcount = textcount + textcount_this
174$   return
175$
176$! ----- Subroutines for VAX
177$! -----
178$! The creator routine
179$ create_vax_shr:
180$   open/write mar 'libmar'
181$   type sys$input:/out=mar:
182;
183; Transfer vector for VAX shareable image
184;
185$   write mar "	.TITLE ",libtit
186$   write mar "	.IDENT /",libid,"/"
187$   type sys$input:/out=mar:
188;
189; Define macro to assist in building transfer vector entries.  Each entry
190; should take no more than 8 bytes.
191;
192	.MACRO FTRANSFER_ENTRY routine
193	.ALIGN QUAD
194	.TRANSFER routine
195	.MASK	routine
196	JMP	routine+2
197	.ENDM FTRANSFER_ENTRY
198;
199; Place entries in own program section.
200;
201$   write mar "	.PSECT $$",libvec,",QUAD,PIC,USR,CON,REL,LCL,SHR,EXE,RD,NOWRT"
202$   write mar libvec,"_xfer:"
203$   libwrch   := mar
204$   libwriter := write_vax_ftransfer_entry
205$   gosub read_func_num
206$   type sys$input:/out=mar:
207;
208; Allocate extra storage at end of vector to allow for expansion.
209;
210$   write mar "	.BLKB 32768-<.-",libvec,"_xfer>	; 64 pages total."
211$!   libwriter := write_vax_vtransfer_entry
212$!   gosub read_func_num
213$   write mar "	.END"
214$   close mar
215$   open/write opt 'libopt'
216$   write opt "identification=""",libid," ",libverstr,""""
217$   write opt libobj
218$   write opt libolb,"/lib"
219$   if libref .nes. "" then write opt libref,"/SHARE"
220$   type sys$input:/out=opt:
221!
222! Ensure transfer vector is at beginning of image
223!
224CLUSTER=FIRST
225$   write opt "COLLECT=FIRST,$$",libvec
226$   write opt "GSMATCH=",libvmatch,",",libver
227$   type sys$input:/out=opt:
228!
229! make psects nonshareable so image can be installed.
230!
231PSECT_ATTR=$CHAR_STRING_CONSTANTS,NOWRT
232$   libwrch   := opt
233$   libwriter := write_vax_psect_attr
234$   gosub read_func_num
235$   close opt
236$   macro/obj='libobj' 'libmar'
237$   link/map='libmap'/full/share='libgoal' 'libopt'/option
238$   return
239$
240$! The record writer routine for VAX functions
241$ write_vax_ftransfer_entry:
242$   if info_kind .nes. "FUNCTION" then return
243$   if libentry .eqs ".dummy"
244$   then
245$     write 'libwrch' "	.BLKB 8" ! Dummy is zeroes...
246$   else
247$     write 'libwrch' "	FTRANSFER_ENTRY ",libentry
248$   endif
249$   return
250$! The record writer routine for VAX variables (should never happen!)
251$ write_vax_psect_attr:
252$   if info_kind .nes. "VARIABLE" then return
253$   if libentry .eqs ".dummy" then return
254$   write 'libwrch' "PSECT_ATTR=",libentry,",NOSHR"
255$   return
256$
257$! ----- Common subroutines
258$! -----
259$! The .num file reader.  This one has great responsability.
260$ read_func_num:
261$   open libnum 'libnum'
262$   goto read_nums
263$
264$ read_nums:
265$   libentrynum=0
266$   liblastentry:=false
267$   entrycount=0
268$   loop:
269$     read/end=loop_end/err=loop_end libnum line
270$     entrynum=f$int(f$element(1," ",f$edit(line,"COMPRESS,TRIM")))
271$     entryinfo=f$element(2," ",f$edit(line,"COMPRESS,TRIM"))
272$     curentry=f$element(0," ",f$edit(line,"COMPRESS,TRIM"))
273$     info_exist=f$element(0,":",entryinfo)
274$     info_platforms=","+f$element(1,":",entryinfo)+","
275$     info_kind=f$element(2,":",entryinfo)
276$     info_algorithms=","+f$element(3,":",entryinfo)+","
277$     if info_exist .eqs. "NOEXIST" then goto loop
278$     truesum = 0
279$     falsesum = 0
280$     negatives = 1
281$     plat_i = 0
282$     loop1:
283$       plat_entry = f$element(plat_i,",",info_platforms)
284$       plat_i = plat_i + 1
285$       if plat_entry .eqs. "" then goto loop1
286$       if plat_entry .nes. ","
287$       then
288$         if f$extract(0,1,plat_entry) .nes. "!" then negatives = 0
289$         if f$getsyi("CPU") .lt. 128
290$         then
291$           if plat_entry .eqs. "EXPORT_VAR_AS_FUNCTION" then -
292$             truesum = truesum + 1
293$           if plat_entry .eqs. "!EXPORT_VAR_AS_FUNCTION" then -
294$             falsesum = falsesum + 1
295$         endif
296$!
297$         if ((plat_entry .eqs. "VMS") .or. -
298            (arch_vax .and. (plat_entry .eqs. "VMSVAX"))) then -
299            truesum = truesum + 1
300$!
301$         if ((plat_entry .eqs. "!VMS") .or. -
302            (arch_vax .and. (plat_entry .eqs. "!VMSVAX"))) then -
303            falsesum = falsesum + 1
304$!
305$	  goto loop1
306$       endif
307$     endloop1:
308$!DEBUG!$     if info_platforms - "EXPORT_VAR_AS_FUNCTION" .nes. info_platforms
309$!DEBUG!$     then
310$!DEBUG!$       write sys$output line
311$!DEBUG!$       write sys$output "        truesum = ",truesum,-
312$!DEBUG!		", negatives = ",negatives,", falsesum = ",falsesum
313$!DEBUG!$     endif
314$     if falsesum .ne. 0 then goto loop
315$     if truesum+negatives .eq. 0 then goto loop
316$     alg_i = 0
317$     loop2:
318$       alg_entry = f$element(alg_i,",",info_algorithms)
319$	alg_i = alg_i + 1
320$       if alg_entry .eqs. "" then goto loop2
321$       if alg_entry .nes. ","
322$       then
323$         if alg_entry .eqs. "KRB5" then goto loop ! Special for now
324$	  if alg_entry .eqs. "STATIC_ENGINE" then goto loop ! Special for now
325$         if f$trnlnm("OPENSSL_NO_"+alg_entry) .nes. "" then goto loop
326$	  goto loop2
327$       endif
328$     endloop2:
329$     if info_platforms - "EXPORT_VAR_AS_FUNCTION" .nes. info_platforms
330$     then
331$!DEBUG!$     write sys$output curentry," ; ",entrynum," ; ",entryinfo
332$     endif
333$   redo:
334$     next:=loop
335$     tolibentry=curentry
336$     if libentrynum .ne. entrynum
337$     then
338$       entrycount=entrycount+1
339$       if entrycount .lt. entrynum
340$       then
341$!DEBUG!$         write sys$output "Info: entrycount: ''entrycount', entrynum: ''entrynum' => 0"
342$         tolibentry=".dummy"
343$         next:=redo
344$       endif
345$       if entrycount .gt. entrynum
346$       then
347$         write sys$error "Decreasing library entry numbers!  Can't continue"
348$         write sys$error """",line,""""
349$         close libnum
350$         return
351$       endif
352$       libentry=tolibentry
353$!DEBUG!$       write sys$output entrycount," ",libentry," ",entryinfo
354$       if libentry .nes. "" .and. libwriter .nes. "" then gosub 'libwriter'
355$     else
356$       write sys$error "Info: ""''curentry'"" is an alias for ""''libentry'"".  Overriding..."
357$     endif
358$     libentrynum=entrycount
359$     goto 'next'
360$   loop_end:
361$   close libnum
362$   return
363$
364$! The version number reader
365$ read_version_info:
366$   libver = ""
367$   open/read vf [.CRYPTO]OPENSSLV.H
368$   loop_rvi:
369$     read/err=endloop_rvi/end=endloop_rvi vf rvi_line
370$     if rvi_line - "SHLIB_VERSION_NUMBER """ .eqs. rvi_line then -
371	goto loop_rvi
372$     libverstr = f$element(1,"""",rvi_line)
373$     libvmajor = f$element(0,".",libverstr)
374$     libvminor = f$element(1,".",libverstr)
375$     libvedit = f$element(2,".",libverstr)
376$     libvpatch = f$cvui(0,8,f$extract(1,1,libvedit)+"@")-f$cvui(0,8,"@")
377$     libvedit = f$extract(0,1,libvedit)
378$     libver = f$string(f$int(libvmajor)*100)+","+-
379	f$string(f$int(libvminor)*100+f$int(libvedit)*10+f$int(libvpatch))
380$     if libvmajor .eqs. "0"
381$     then
382$       libvmatch = "EQUAL"
383$     else
384$       ! Starting with the 1.0 release, backward compatibility should be
385$       ! kept, so switch over to the following
386$       libvmatch = "LEQUAL"
387$     endif
388$   endloop_rvi:
389$   close vf
390$   return
391