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