Annotation of embedaddon/curl/packages/vms/build_gnv_curl_pcsi_desc.com, revision 1.1.1.1
1.1 misho 1: $! File: Build_GNV_CURL_PCSI_DESC.COM
2: $!
3: $! $Id$
4: $!
5: $! Build the *.pcsi$text file in the following sections:
6: $! Required software dependencies.
7: $! install/upgrade/postinstall steps.
8: $! 1. Duplicate filenames need an alias procedure. (N/A for curl)
9: $! 2. ODS-5 filenames need an alias procedure. (N/A for curl)
10: $! 3. Special alias links for executables (curl. -> curl.exe)
11: $! if a lot, then an alias procedure is needed.
12: $! 4. Rename the files to lowercase.
13: $! Move Release Notes to destination
14: $! Source kit option
15: $! Create directory lines
16: $! Add file lines for curl.
17: $! Add Link alias procedure file (N/A for curl)
18: $! Add [.SYS$STARTUP]curl_startup file
19: $! Add Release notes file.
20: $!
21: $! The file PCSI_GNV_CURL_FILE_LIST.TXT is read in to get the files other
22: $! than the release notes file and the source backup file.
23: $!
24: $! The PCSI system can really only handle ODS-2 format filenames and
25: $! assumes that there is only one source directory. It also assumes that
26: $! all destination files with the same name come from the same source file.
27: $! Fortunately CURL does not trip most of these issues, so those steps
28: $! above are marked N/A.
29: $!
30: $! A rename action section is needed to make sure that the files are
31: $! created in the GNV$GNU: in the correct case, and to create the alias
32: $! link [usr.bin]curl. for [usr.bin]curl.exe.
33: $!
34: $! Copyright 2009 - 2020, John Malmberg
35: $!
36: $! Permission to use, copy, modify, and/or distribute this software for any
37: $! purpose with or without fee is hereby granted, provided that the above
38: $! copyright notice and this permission notice appear in all copies.
39: $!
40: $! THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
41: $! WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
42: $! MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
43: $! ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
44: $! WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
45: $! ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT
46: $! OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
47: $!
48: $!
49: $! 15-Jun-2009 J. Malmberg
50: $!
51: $!===========================================================================
52: $!
53: $ kit_name = f$trnlnm("GNV_PCSI_KITNAME")
54: $ if kit_name .eqs. ""
55: $ then
56: $ write sys$output "@MAKE_PCSI_CURL_KIT_NAME.COM has not been run."
57: $ goto all_exit
58: $ endif
59: $ producer = f$trnlnm("GNV_PCSI_PRODUCER")
60: $ if producer .eqs. ""
61: $ then
62: $ write sys$output "@MAKE_PCSI_CURL_KIT_NAME.COM has not been run."
63: $ goto all_exit
64: $ endif
65: $ filename_base = f$trnlnm("GNV_PCSI_FILENAME_BASE")
66: $ if filename_base .eqs. ""
67: $ then
68: $ write sys$output "@MAKE_PCSI_CURL_KIT_NAME.COM has not been run."
69: $ goto all_exit
70: $ endif
71: $!
72: $!
73: $! Parse the kit name into components.
74: $!---------------------------------------
75: $ producer = f$element(0, "-", kit_name)
76: $ base = f$element(1, "-", kit_name)
77: $ product = f$element(2, "-", kit_name)
78: $ mmversion = f$element(3, "-", kit_name)
79: $ majorver = f$extract(0, 3, mmversion)
80: $ minorver = f$extract(3, 2, mmversion)
81: $ updatepatch = f$element(4, "-", kit_name)
82: $ if updatepatch .eqs. "-" then updatepatch = ""
83: $!
84: $! kit type of "D" means a daily build
85: $ kit_type = f$edit(f$extract(0, 1, majorver), "upcase")
86: $!
87: $!
88: $ product_line = "product ''producer' ''base' ''product'"
89: $ if updatepatch .eqs. ""
90: $ then
91: $ product_name = " ''majorver'.''minorver'"
92: $ else
93: $ product_name = " ''majorver'.''minorver'-''updatepatch'"
94: $ endif
95: $ product_line = product_line + " ''product_name' full;"
96: $!write sys$output product_line
97: $!
98: $!
99: $!
100: $! Create the file as a VMS text file.
101: $!----------------------------------------
102: $ base_file = kit_name
103: $ create 'base_file'.pcsi$desc
104: $!
105: $!
106: $! Start building file.
107: $!----------------------
108: $ open/append pdsc 'base_file'.pcsi$desc
109: $!
110: $ write pdsc product_line
111: $!
112: $! Required product dependencies.
113: $!----------------------------------
114: $ vmsprd = "DEC"
115: $ if base .eqs. "I64VMS" then vmsprd = "HP"
116: $ vsiprd = "VSI"
117: $!
118: $ write pdsc " software ''vmsprd' ''base' VMS ;"
119: $ arch_type = f$getsyi("ARCH_NAME")
120: $ node_swvers = f$getsyi("node_swvers")
121: $ vernum = f$extract(1, f$length(node_swvers), node_swvers)
122: $ majver = f$element(0, ".", vernum)
123: $ minverdash = f$element(1, ".", vernum)
124: $ minver = f$element(0, "-", minverdash)
125: $ dashver = f$element(1, "-", minverdash)
126: $ if dashver .eqs. "-" then dashver = ""
127: $ vmstag = majver + minver + dashver
128: $ code = f$extract(0, 1, arch_type)
129: $ arch_code = f$extract(0, 1, arch_type)
130: $ line_out = -
131: " if ((not <software ''vsiprd' ''base' VMS version minimum" + -
132: " ''node_swvers'>) and" + -
133: " (not <software ''vmsprd' ''base' VMS version minimum ''node_swvers'>));"
134: $ write pdsc line_out
135: $ write pdsc " error NEED_VMS''vmstag';"
136: $ write pdsc " end if;"
137: $!
138: $write pdsc " software VMSPORTS ''base' ZLIB ;"
139: $write pdsc -
140: " if (not <software VMSPORTS ''base' ZLIB version minimum V1.2-8>) ;"
141: $write pdsc " error NEED_ZLIB;"
142: $write pdsc " end if;"
143: $!
144: $!
145: $!
146: $! install/upgrade/postinstall steps.
147: $!-----------------------------------
148: $! 1. Duplicate filenames need an alias procedure. (N/A for curl)
149: $! 2. ODS-5 filenames need an alias procedure. (N/A for curl)
150: $! 3. Special alias links for executables (curl. -> curl.exe)
151: $! if a lot, then an alias procedure is needed.
152: $! 4. Rename the files to lowercase.
153: $!
154: $!
155: $! Alias links needed.
156: $!-------------------------
157: $ add_alias_lines = ""
158: $ rem_alias_lines = ""
159: $ line_out = ""
160: $!
161: $! Read through the file list to set up aliases and rename commands.
162: $!---------------------------------------------------------------------
163: $ open/read flst pcsi_gnv_curl_file_list.txt
164: $!
165: $inst_alias_loop:
166: $ read/end=inst_alias_loop_end flst line_in
167: $ line_in = f$edit(line_in,"compress,trim,uncomment")
168: $ if line_in .eqs. "" then goto inst_alias_loop
169: $ pathname = f$element(0, " ", line_in)
170: $ linkflag = f$element(1, " ", line_in)
171:
172: $ if linkflag .nes. "->" then goto inst_alias_write
173: $!
174: $ linktarget = f$element(2, " ", line_in)
175: $ if kit_type .eqs. "D"
176: $ then
177: $ old_start = f$locate("[gnv.usr", pathname)
178: $ if old_start .lt. f$length(pathname)
179: $ then
180: $ pathname = "[gnv.beta" + pathname - "[gnv.usr"
181: $ linktarget = "[gnv.beta" + linktarget - "[gnv.usr"
182: $ endif
183: $ endif
184: $ nlink = "pcsi$destination:" + pathname
185: $ ntarg = "pcsi$destination:" + linktarget
186: $ new_add_alias_line = -
187: """if f$search(""""''nlink'"""") .eqs. """""""" then" + -
188: " set file/enter=''nlink' ''ntarg'"""
189: $ if add_alias_lines .nes. ""
190: $ then
191: $ add_alias_lines = add_alias_lines + "," + new_add_alias_line
192: $ else
193: $ add_alias_lines = new_add_alias_line
194: $ endif
195: $!
196: $ new_rem_alias_line = -
197: """if f$search(""""''nlink'"""") .nes. """""""" then" + -
198: " set file/remove ''nlink';"""
199: $ if rem_alias_lines .nes. ""
200: $ then
201: $ rem_alias_lines = rem_alias_lines + "," + new_rem_alias_line
202: $ else
203: $ rem_alias_lines = new_rem_alias_line
204: $ endif
205: $!
206: $ goto inst_alias_loop
207: $!
208: $inst_alias_write:
209: $!
210: $! execute install / remove
211: $ write pdsc " execute install ("
212: $! add aliases
213: $ i = 0
214: $ex_ins_loop:
215: $ line = f$element(i, ",", add_alias_lines)
216: $ i = i + 1
217: $ if line .eqs. "" then goto ex_ins_loop
218: $ if line .eqs. "," then goto ex_ins_loop_end
219: $ if line_out .nes. "" then write pdsc line_out,","
220: $ line_out = line
221: $ goto ex_ins_loop
222: $ex_ins_loop_end:
223: $ write pdsc line_out
224: $ line_out = ""
225: $ write pdsc " )"
226: $ write pdsc " remove ("
227: $! remove aliases
228: $ i = 0
229: $ex_rem_loop:
230: $ line = f$element(i, ",", rem_alias_lines)
231: $ i = i + 1
232: $ if line .eqs. "" then goto ex_rem_loop
233: $ if line .eqs. "," then goto ex_rem_loop_end
234: $ if line_out .nes. "" then write pdsc line_out,","
235: $ line_out = line
236: $ goto ex_rem_loop
237: $ex_rem_loop_end:
238: $ write pdsc line_out
239: $ line_out = ""
240: $ write pdsc " ) ;"
241: $!
242: $! execute upgrade
243: $ write pdsc " execute upgrade ("
244: $ i = 0
245: $ex_upg_loop:
246: $ line = f$element(i, ",", rem_alias_lines)
247: $ i = i + 1
248: $ if line .eqs. "" then goto ex_upg_loop
249: $ if line .eqs. "," then goto ex_upg_loop_end
250: $ if line_out .nes. "" then write pdsc line_out,","
251: $ line_out = line
252: $ goto ex_upg_loop
253: $ex_upg_loop_end:
254: $ write pdsc line_out
255: $ line_out = ""
256: $! remove aliases
257: $ write pdsc " ) ;"
258: $!
259: $! execute postinstall
260: $ write pdsc " execute postinstall ("
261: $ if arch_code .nes. "V"
262: $ then
263: $ line_out = " ""set process/parse=extended"""
264: $ endif
265: $ i = 0
266: $ex_pins_loop:
267: $ line = f$element(i, ",", add_alias_lines)
268: $ i = i + 1
269: $ if line .eqs. "" then goto ex_pins_loop
270: $ if line .eqs. "," then goto ex_pins_loop_end
271: $ if line_out .nes. "" then write pdsc line_out,","
272: $ line_out = line
273: $ goto ex_pins_loop
274: $ex_pins_loop_end:
275: $ if line_out .eqs. "" then line_out = " ""continue"""
276: $! write pdsc line_out
277: $! line_out = ""
278: $! add aliases and follow with renames.
279: $!
280: $goto inst_dir
281: $!
282: $inst_dir_loop:
283: $ read/end=inst_alias_loop_end flst line_in
284: $ line_in = f$edit(line_in,"compress,trim,uncomment")
285: $ if line_in .eqs. "" then goto inst_dir_loop
286: $inst_dir:
287: $ pathname = f$element(0, " ", line_in)
288: $ if kit_type .eqs. "D"
289: $ then
290: $ if pathname .eqs. "[gnv]usr.dir"
291: $ then
292: $ pathname = "[gnv]beta.dir"
293: $ else
294: $ old_start = f$locate("[gnv.usr", pathname)
295: $ if old_start .lt. f$length(pathname)
296: $ then
297: $ pathname = "[gnv.beta" + pathname - "[gnv.usr"
298: $ endif
299: $ endif
300: $ endif
301: $!
302: $! Ignore the directory entries for now.
303: $!-----------------------------------------
304: $ filedir = f$parse(pathname,,,"DIRECTORY")
305: $ if pathname .eqs. filedir then goto inst_dir_loop
306: $!
307: $! process .dir extensions for rename
308: $! If this is not a directory then start processing files.
309: $!-------------------------
310: $ filetype = f$parse(pathname,,,"TYPE")
311: $ filetype_u = f$edit(filetype, "upcase")
312: $ filename = f$parse(pathname,,,"NAME")
313: $ if filetype_u .nes. ".DIR" then goto inst_file
314: $!
315: $! process directory lines for rename.
316: $!--------------------------------------
317: $ if line_out .nes. ""
318: $ then
319: $ write pdsc line_out,","
320: $ line_out = ""
321: $ endif
322: $ if arch_code .nes. "V"
323: $ then
324: $ if line_out .nes. "" then write pdsc line_out,","
325: $ line_out = " ""rename pcsi$destination:''pathname' ''filename'.DIR"""
326: $ else
327: $ if line_out .nes. "" then write pdsc line_out
328: $ line_out = ""
329: $ endif
330: $ goto inst_dir_loop
331: $!
332: $!
333: $! process file lines for rename
334: $!---------------------------------
335: $inst_file_loop:
336: $ read/end=inst_alias_loop_end flst line_in
337: $ line_in = f$edit(line_in,"compress,trim,uncomment")
338: $ if line_in .eqs. "" then goto inst_dir_loop
339: $ pathname = f$element(0, " ", line_in)
340: $ if kit_type .eqs. "D"
341: $ then
342: $ if pathname .eqs. "[gnv]usr.dir"
343: $ then
344: $ pathname = "[gnv]beta.dir"
345: $ else
346: $ old_start = f$locate("[gnv.usr", pathname)
347: $ if old_start .lt. f$length(pathname)
348: $ then
349: $ pathname = "[gnv.beta" + pathname - "[gnv.usr"
350: $ endif
351: $ endif
352: $ endif
353: $!
354: $! Filenames with $ in them are VMS special and do not need to be lowercase.
355: $! --------------------------------------------------------------------------
356: $ if f$locate("$", pathname) .lt. f$length(pathname) then goto inst_file_loop
357: $!
358: $ filetype = f$parse(pathname,,,"TYPE")
359: $ filename = f$parse(pathname,,,"NAME") + filetype
360: $inst_file:
361: $ if arch_code .nes. "V"
362: $ then
363: $ if line_out .nes. "" then write pdsc line_out,","
364: $ filetype = f$parse(pathname,,,"TYPE")
365: $ filename = f$parse(pathname,,,"NAME") + filetype
366: $ line_out = " ""rename pcsi$destination:''pathname' ''filename'"""
367: $ else
368: $ if line_out .nes. "" then write pdsc line_out
369: $ line_out = ""
370: $ endif
371: $ goto inst_file_loop
372: $!
373: $inst_alias_loop_end:
374: $!
375: $write pdsc line_out
376: $write pdsc " ) ;"
377: $close flst
378: $!
379: $! Move Release Notes to destination
380: $!-------------------------------------
381: $write pdsc " information RELEASE_NOTES phase after ;"
382: $!
383: $! Source kit option
384: $!---------------------
385: $write pdsc " option SOURCE default 0;"
386: $write pdsc " directory ""[gnv.common_src]"" PROTECTION PUBLIC ;"
387: $write pdsc -
388: " file ""[gnv.common_src]''filename_base'_original_src.bck"""
389: $write pdsc -
390: " source [common_src]''filename_base'_original_src.bck ;"
391: $if f$search("gnv$gnu:[vms_src]''filename_base'_vms_src.bck") .nes. ""
392: $then
393: $ write pdsc " directory ""[gnv.vms_src]"" PROTECTION PUBLIC ;"
394: $ write pdsc " file ""[gnv.vms_src]''filename_base'_vms_src.bck"""
395: $ write pdsc " source [vms_src]''filename_base'_vms_src.bck ;"
396: $endif
397: $write pdsc " end option;"
398: $!
399: $!
400: $! Read through the file list again.
401: $!----------------------------------
402: $open/read flst pcsi_gnv_curl_file_list.txt
403: $!
404: $!
405: $! Create directory lines
406: $!-------------------------
407: $flst_dir_loop:
408: $ read/end=flst_loop_end flst line_in
409: $ line_in = f$edit(line_in,"compress,trim,uncomment")
410: $ if line_in .eqs. "" then goto flst_dir_loop
411: $!
412: $ filename = f$element(0, " ", line_in)
413: $ linkflag = f$element(1, " ", line_in)
414: $ if linkflag .eqs. "->" then goto flst_dir_loop
415: $!
416: $! Ignore .dir extensions
417: $!-------------------------
418: $ filetype = f$edit(f$parse(filename,,,"TYPE"), "upcase")
419: $ if filetype .eqs. ".DIR" then goto flst_dir_loop
420: $!
421: $ destname = filename
422: $ if kit_type .eqs. "D"
423: $ then
424: $ old_start = f$locate("[gnv.usr", destname)
425: $ if old_start .lt. f$length(destname)
426: $ then
427: $ destname = "[gnv.beta" + destname - "[gnv.usr"
428: $ endif
429: $ endif
430: $!
431: $! It should be just a directory then.
432: $!-------------------------------------
433: $ filedir = f$edit(f$parse(filename,,,"DIRECTORY"), "lowercase")
434: $! If this is not a directory then start processing files.
435: $!---------------------------------------------------------
436: $ if filename .nes. filedir then goto flst_file
437: $!
438: $ write pdsc " directory ""''destname'"" PROTECTION PUBLIC ;"
439: $ goto flst_dir_loop
440: $!
441: $!
442: $! Add file lines for curl.
443: $!---------------------------
444: $flst_file_loop:
445: $ read/end=flst_loop_end flst line_in
446: $ line_in = f$edit(line_in,"compress,trim,uncomment")
447: $ if line_in .eqs. "" then goto inst_file_loop
448: $ filename = f$element(0, " ", line_in)
449: $ destname = filename
450: $ if kit_type .eqs. "D"
451: $ then
452: $ old_start = f$locate("[gnv.usr", destname)
453: $ if old_start .lt. f$length(destname)
454: $ then
455: $ destname = "[gnv.beta" + destname - "[gnv.usr"
456: $ endif
457: $ endif
458: $flst_file:
459: $ srcfile = filename - "gnv."
460: $ write pdsc " file ""''destname'"" "
461: $ write pdsc " source ""''srcfile'"" ;"
462: $ goto flst_file_loop
463: $!
464: $flst_loop_end:
465: $ close flst
466: $!
467: $! Add Link alias procedure file (N/A for curl)
468: $!------------------------------------------------
469: $!
470: $! Add [.SYS$STARTUP]curl_startup file
471: $!---------------------------------------
472: $ if kit_type .eqs. "D"
473: $ then
474: $ write pdsc " file ""[sys$startup]curl_daily_startup.com"""
475: $ else
476: $ write pdsc " file ""[sys$startup]curl_startup.com"""
477: $ endif
478: $ write pdsc " source [usr.lib]curl_startup.com ;"
479: $!
480: $! Add Release notes file.
481: $!------------------------------
482: $ write pdsc -
483: " file ""[SYSHLP]''filename_base'.release_notes"" release notes ;"
484: $!
485: $! Close the product file
486: $!------------------------
487: $ write pdsc "end product;"
488: $!
489: $close pdsc
490: $!
491: $all_exit:
492: $ exit
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>