Annotation of embedaddon/curl/packages/vms/generate_config_vms_h_curl.com, revision 1.1.1.1
1.1 misho 1: $! File: GENERATE_CONFIG_H_CURL.COM
2: $!
3: $! $Id$
4: $!
5: $! Curl like most open source products uses a variant of a config.h file.
6: $! Depending on the curl version, this could be config.h or curl_config.h.
7: $!
8: $! For GNV based builds, the configure script is run and that produces
9: $! a [curl_]config.h file. Configure scripts on VMS generally do not
10: $! know how to do everything, so there is also a [-.lib]config-vms.h file
11: $! that has VMS specific code that compensates for bugs in some of the
12: $! VMS shared images.
13: $!
14: $! This generates a [curl_]config.h file and also a config_vms.h file,
15: $! which is used to supplement that file. Note that the config_vms.h file
16: $! and the [.lib]config-vms.h file do two different tasks and that the
17: $! filenames are slightly different.
18: $!
19: $!
20: $! Copyright 2013 - 2020, John Malmberg
21: $!
22: $! Permission to use, copy, modify, and/or distribute this software for any
23: $! purpose with or without fee is hereby granted, provided that the above
24: $! copyright notice and this permission notice appear in all copies.
25: $!
26: $! THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
27: $! WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
28: $! MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
29: $! ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
30: $! WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
31: $! ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT
32: $! OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
33: $!
34: $!
35: $! 06-Jan-2013 J. Malmberg
36: $!
37: $!=========================================================================
38: $!
39: $! Allow arguments to be grouped together with comma or separated by spaces
40: $! Do no know if we will need more than 8.
41: $args = "," + p1 + "," + p2 + "," + p3 + "," + p4 + ","
42: $args = args + p5 + "," + p6 + "," + p7 + "," + p8 + ","
43: $!
44: $! Provide lower case version to simplify parsing.
45: $args_lower = f$edit(args, "LOWERCASE")
46: $!
47: $args_len = f$length(args)
48: $!
49: $if (f$getsyi("HW_MODEL") .lt. 1024)
50: $then
51: $ arch_name = "VAX"
52: $else
53: $ arch_name = ""
54: $ arch_name = arch_name + f$edit(f$getsyi("ARCH_NAME"), "UPCASE")
55: $ if (arch_name .eqs. "") then arch_name = "UNK"
56: $endif
57: $!
58: $!
59: $nossl = 0
60: $nohpssl = 1
61: $hpssl = 0
62: $libidn = 0
63: $libssh2 = 0
64: $noldap = 0
65: $nozlib = 0
66: $nokerberos = 0
67: $!
68: $! First check to see if SSL is disabled.
69: $!---------------------------------------
70: $if f$locate(",nossl,", args_lower) .lt. args_len then nossl = 1
71: $if .not. nossl
72: $then
73: $!
74: $! ssl$* logicals means HP ssl is present
75: $!----------------------------------------
76: $ if f$trnlnm("ssl$root") .nes. ""
77: $ then
78: $ nohpssl = 0
79: $ hpssl = 1
80: $ endif
81: $!
82: $! HP defines OPENSSL as SSL$INCLUDE as a convenience for linking.
83: $! As it is a violation of VMS standards for this to be provided,
84: $! some sites may have removed it, but if present, assume that
85: $! it indicates which OpenSSL to use.
86: $!------------------------------------
87: $ openssl_lnm = f$trnlnm("OPENSSL")
88: $ if (openssl_lnm .nes. "SYS$INCLUDE")
89: $ then
90: $! Non HP SSL is installed, default to use it.
91: $ nohpssl = 1
92: $ hpssl = 0
93: $ endif
94: $!
95: $! Now check to see if hpssl has been specifically disabled
96: $!----------------------------------------------------------
97: $ if f$locate(",nohpssl,", args_lower) .lt. args_len
98: $ then
99: $ nohpssl = 1
100: $ hpssl = 0
101: $ endif
102: $!
103: $! Finally check to see if hp ssl has been specifically included.
104: $!----------------------------------------------------------------
105: $ if f$locate(",nohpssl,", args_lower) .lt. args_len
106: $ then
107: $ nohpssl = 1
108: $ hpssl = 0
109: $ endif
110: $endif
111: $!
112: $! Did someone port LIBIDN in the GNV compatible way?
113: $!------------------------------------------------------
114: $if f$trnlnm("GNV$LIBIDNSHR") .nes. ""
115: $then
116: $ write sys$output "NOTICE: A LIBIDN port has been detected."
117: $ write sys$output " This port of curl for VMS has not been tested with it."
118: $ if f$locate(",libidn,", args_lower) .lt. args_len
119: $ then
120: $ libidn = 1
121: $ endif
122: $ if .not. libidn
123: $ then
124: $ write sys$output " LIBIDN support is not enabled."
125: $ write sys$output "Run with the ""libidn"" parameter to attempt to use."
126: $ else
127: $ write sys$output " Untested LIBIDN support requested."
128: $ endif
129: $endif
130: $!
131: $! Did someone port LIBSSH2 in the GNV compatible way?
132: $!------------------------------------------------------
133: $if f$trnlnm("GNV$LIBSSH2SHR") .nes. ""
134: $then
135: $ write sys$output "NOTICE: A LIBSSH2 port has been detected."
136: $ write sys$output " This port of curl for VMS has not been tested with it."
137: $ if f$locate(",libssh2,", args_lower) .lt. args_len
138: $ then
139: $ libssh2 = 1
140: $ endif
141: $ if .not. libssh2
142: $ then
143: $ write sys$output " LIBSSH2 support is not enabled."
144: $ write sys$output "Run with the ""libssh2"" parameter to attempt to use."
145: $ else
146: $ write sys$output " Untested LIBSSH2 support requested."
147: $ endif
148: $endif
149: $!
150: $! LDAP suppressed?
151: $if f$locate(",noldap,", args_lower) .lt. args_len
152: $then
153: $ noldap = 1
154: $endif
155: $if f$search("SYS$SHARE:LDAP$SHR.EXE") .eqs. ""
156: $then
157: $ noldap = 1
158: $endif
159: $!
160: $if f$locate(",nokerberos,", args_lower) .lt. args_len then nokerberos = 1
161: $if .not. nokerberos
162: $then
163: $! If kerberos is installed: sys$share:gss$rtl.exe exists.
164: $ if f$search("sys$shsare:gss$rtl.exe") .eqs. ""
165: $ then
166: $ nokerberos = 1
167: $ endif
168: $endif
169: $!
170: $!
171: $! Is GNV compatible LIBZ present?
172: $!------------------------------------------------------
173: $if f$trnlnm("GNV$LIBZSHR") .nes. ""
174: $then
175: $ if f$locate(",nozlib,", args_lower) .lt. args_len
176: $ then
177: $ nozlib = 1
178: $ endif
179: $! if .not. nozlib
180: $! then
181: $! write sys$output " GNV$LIBZSHR support is enabled."
182: $! else
183: $! write sys$output " GNV$LIBZSHR support is disabled by nozlib."
184: $! endif
185: $else
186: $ nozlib = 1
187: $endif
188: $!
189: $!
190: $! Start the configuration file.
191: $! Need to do a create and then an append to make the file have the
192: $! typical file attributes of a VMS text file.
193: $create sys$disk:[curl.lib]config_vms.h
194: $open/append cvh sys$disk:[curl.lib]config_vms.h
195: $!
196: $! Write the defines to prevent multiple includes.
197: $! These are probably not needed in this case,
198: $! but are best practice to put on all header files.
199: $write cvh "#ifndef __CONFIG_VMS_H__"
200: $write cvh "#define __CONFIG_VMS_H__"
201: $write cvh ""
202: $write cvh "/* Define cpu-machine-OS */"
203: $!
204: $! Curl uses an OS macro to set the build environment.
205: $!----------------------------------------------------
206: $! Now the DCL builds usually say xxx-HP-VMS and configure scripts
207: $! may put DEC or COMPAQ or HP for the middle part.
208: $!
209: $write cvh "#if defined(__alpha)"
210: $write cvh "#define OS ""ALPHA-HP-VMS"""
211: $write cvh "#elif defined(__vax)"
212: $write cvh "#define OS ""VAX-HP-VMS"""
213: $write cvh "#elif defined(__ia64)"
214: $write cvh "#define OS ""IA64-HP-VMS""
215: $write cvh "#else"
216: $write cvh "#define OS ""UNKNOWN-HP-VMS""
217: $write cvh "#endif"
218: $write cvh ""
219: $!
220: $! We are now setting this on the GNV build, so also do this
221: $! for compatibility.
222: $write cvh "/* Location of default ca path */"
223: $write cvh "#define curl_ca_path ""gnv$curl_ca_path"""
224: $!
225: $! NTLM_WB_ENABLED requires fork() but configure does not know this
226: $! We have to disable this in the configure command line.
227: $! config_h.com finds that configure defaults to it being enabled so
228: $! reports it. So we need to turn it off here.
229: $!
230: $write cvh "#ifdef NTLM_WB_ENABLED"
231: $write cvh "#undef NTLM_WB_ENABLED"
232: $write cvh "#endif"
233: $!
234: $! The config_h.com finds a bunch of default disable commands in
235: $! configure and will incorrectly disable these options. The config_h.com
236: $! is a generic procedure and it would break more things to try to fix it
237: $! to special case it for curl. So we will fix it here.
238: $!
239: $! We do them all here, even the ones that config_h.com currently gets correct.
240: $!
241: $write cvh "#ifdef CURL_DISABLE_COOKIES"
242: $write cvh "#undef CURL_DISABLE_COOKIES"
243: $write cvh "#endif"
244: $write cvh "#ifdef CURL_DISABLE_CRYPTO_AUTH"
245: $write cvh "#undef CURL_DISABLE_CRYPTO_AUTH"
246: $write cvh "#endif"
247: $write cvh "#ifdef CURL_DISABLE_DICT"
248: $write cvh "#undef CURL_DISABLE_DICT"
249: $write cvh "#endif"
250: $write cvh "#ifdef CURL_DISABLE_FILE"
251: $write cvh "#undef CURL_DISABLE_FILE"
252: $write cvh "#endif"
253: $write cvh "#ifdef CURL_DISABLE_FTP"
254: $write cvh "#undef CURL_DISABLE_FTP"
255: $write cvh "#endif"
256: $write cvh "#ifdef CURL_DISABLE_GOPHER"
257: $write cvh "#undef CURL_DISABLE_GOPHER"
258: $write cvh "#endif"
259: $write cvh "#ifdef CURL_DISABLE_HTTP"
260: $write cvh "#undef CURL_DISABLE_HTTP"
261: $write cvh "#endif"
262: $write cvh "#ifdef CURL_DISABLE_IMAP"
263: $write cvh "#undef CURL_DISABLE_IMAP"
264: $write cvh "#endif"
265: $if .not. noldap
266: $then
267: $ write cvh "#ifdef CURL_DISABLE_LDAP"
268: $ write cvh "#undef CURL_DISABLE_LDAP"
269: $ write cvh "#endif"
270: $ if .not. nossl
271: $ then
272: $ write cvh "#ifdef CURL_DISABLE_LDAPS"
273: $ write cvh "#undef CURL_DISABLE_LDAPS"
274: $ write cvh "#endif"
275: $ endif
276: $endif
277: $write cvh "#ifdef CURL_DISABLE_LIBCURL_OPTION"
278: $write cvh "#undef CURL_DISABLE_LIBCURL_OPTION"
279: $write cvh "#endif"
280: $write cvh "#ifndef __VAX"
281: $write cvh "#ifdef CURL_DISABLE_NTLM"
282: $write cvh "#undef CURL_DISABLE_NTLM"
283: $write cvh "#endif"
284: $write cvh "#else"
285: $! NTLM needs long long or int64 support, missing from DECC C.
286: $write cvh "#ifdef __DECC
287: $write cvh "#ifndef CURL_DISABLE_NTLM"
288: $write cvh "#define CURL_DISABLE_NTLM 1"
289: $write cvh "#endif"
290: $write cvh "#endif"
291: $write cvh "#endif"
292: $write cvh "#ifdef CURL_DISABLE_POP3"
293: $write cvh "#undef CURL_DISABLE_POP3"
294: $write cvh "#endif"
295: $write cvh "#ifdef CURL_DISABLE_PROXY"
296: $write cvh "#undef CURL_DISABLE_PROXY"
297: $write cvh "#endif"
298: $write cvh "#ifdef CURL_DISABLE_RTSP"
299: $write cvh "#undef CURL_DISABLE_RTSP"
300: $write cvh "#endif"
301: $write cvh "#ifdef CURL_DISABLE_SMTP"
302: $write cvh "#undef CURL_DISABLE_SMTP"
303: $write cvh "#endif"
304: $write cvh "#ifdef CURL_DISABLE_TELNET"
305: $write cvh "#undef CURL_DISABLE_TELNET"
306: $write cvh "#endif"
307: $write cvh "#ifdef CURL_DISABLE_TFTP"
308: $write cvh "#undef CURL_DISABLE_TFTP"
309: $write cvh "#endif"
310: $write cvh "#ifdef CURL_DISABLE_POP3"
311: $write cvh "#undef CURL_DISABLE_POP3"
312: $write cvh "#endif"
313: $if .not. nossl
314: $then
315: $ write cvh "#ifdef CURL_DISABLE_TLS_SRP"
316: $ write cvh "#undef CURL_DISABLE_TLS_SRP"
317: $ write cvh "#endif"
318: $!
319: $endif
320: $write cvh "#ifdef CURL_DISABLE_VERBOSE_STRINGS"
321: $write cvh "#undef CURL_DISABLE_VERBOSE_STRINGS"
322: $write cvh "#endif"
323: $!
324: $! configure defaults to USE_*, a real configure on VMS chooses different.
325: $write cvh "#ifdef USE_ARES"
326: $write cvh "#undef USE_ARES"
327: $write cvh "#endif"
328: $write cvh "#ifdef USE_WOLFSSL"
329: $write cvh "#undef USE_WOLFSSL"
330: $write cvh "#endif"
331: $write cvh "#ifdef USE_GNUTLS"
332: $write cvh "#undef USE_GNUTLS"
333: $write cvh "#endif"
334: $write cvh "#ifdef USE_GNUTLS_NETTLE"
335: $write cvh "#undef USE_GNUTLS_NETTLE"
336: $write cvh "#endif"
337: $write cvh "#ifdef USE_LIBRTMP"
338: $write cvh "#undef USE_LIBRTMP"
339: $write cvh "#endif"
340: $write cvh "#ifdef USE_MANUAL"
341: $write cvh "#undef USE_MANUAL"
342: $write cvh "#endif"
343: $write cvh "#ifdef USE_NGHTTP2"
344: $write cvh "#undef USE_NGHTTP2"
345: $write cvh "#endif"
346: $write cvh "#ifdef USE_NSS"
347: $write cvh "#undef USE_NSS"
348: $write cvh "#endif"
349: $write cvh "#ifdef USE_OPENLDAP"
350: $write cvh "#undef USE_OPENLDAP"
351: $write cvh "#endif"
352: $write cvh "#ifdef USE_THREADS_POSIX"
353: $write cvh "#undef USE_THREADS_POSIX"
354: $write cvh "#endif"
355: $write cvh "#ifdef USE_TLS_SRP"
356: $write cvh "#undef USE_TLS_SRP"
357: $write cvh "#endif"
358: $write cvh "#ifdef USE_UNIX_SOCKETS"
359: $write cvh "#undef USE_UNIX_SOCKETS"
360: $write cvh "#endif"
361: $!
362: $write cvh "#ifndef HAVE_OLD_GSSMIT"
363: $write cvh "#define gss_nt_service_name GSS_C_NT_HOSTBASED_SERVICE"
364: $write cvh "#endif"
365: $!
366: $!
367: $! Note:
368: $! The CURL_EXTERN_SYMBOL is used for platforms that need the compiler
369: $! to know about universal symbols. VMS does not need this support so
370: $! we do not set it here.
371: $!
372: $!
373: $! I can not figure out where the C compiler is finding the ALLOCA.H file
374: $! in the text libraries, so CONFIG_H.COM can not find it either.
375: $! Usually the header file name is the module name in the text library.
376: $! It does not appear to hurt anything to not find header file, so we
377: $! are not overriding it here.
378: $!
379: $!
380: $! Check to see if OpenSSL is present.
381: $!----------------------------------
382: $ssl_include = f$trnlnm("OPENSSL")
383: $if ssl_include .eqs. ""
384: $then
385: $ ssl_include = f$trnlnm("ssl$include")
386: $endif
387: $if ssl_include .eqs. "" then nossl = 1
388: $!
389: $if .not. nossl
390: $then
391: $!
392: $ write cvh "#ifndef USE_OPENSSL"
393: $ write cvh "#define USE_OPENSSL 1"
394: $ write cvh "#endif"
395: $ if arch_name .eqs. "VAX"
396: $ then
397: $ old_mes = f$environment("message")
398: $ set message/notext/nofaci/noseve/noident
399: $ search/output=nla0: ssl$include:*.h CONF_MFLAGS_IGNORE_MISSING_FILE
400: $ status = $severity
401: $ set message'old_mes'
402: $ if status .nes. "1"
403: $ then
404: $ write cvh "#define VMS_OLD_SSL 1"
405: $ endif
406: $ endif
407: $endif
408: $!
409: $!
410: $! LibIDN not ported to VMS at this time.
411: $! This is for international domain name support.
412: $! Allow explicit experimentation.
413: $if libidn
414: $then
415: $ write cvh "#define HAVE_IDNA_STRERROR 1"
416: $ write cvh "#define HAVE_IDNA_FREE 1"
417: $ write cvh "#define HAVE_IDNA_FREE_H 1"
418: $ write cvh "#define HAVE_LIBIDN 1"
419: $else
420: $ write cvh "#ifdef HAVE_LIBIDN"
421: $ write cvh "#undef HAVE_LIBIDN"
422: $ write cvh "#endif"
423: $endif
424: $!
425: $!
426: $! LibSSH2 not ported to VMS at this time.
427: $! Allow explicit experimentation.
428: $if libssh2
429: $then
430: $ write cvh "#define HAVE_LIBSSH2_EXIT 1"
431: $ write cvh "#define HAVE_LIBSSH2_H 1"
432: $ write cvh "#define HAVE_LIBSSH2_INIT 1"
433: $ write cvh "#define HAVE_LIBSSH2_SCP_SEND64 1"
434: $ write cvh "#define HAVE_LIBSSH2_SESSION_HANDSHAKE 1"
435: $ write cvh "#define HAVE_LIBSSH2_VERSION 1
436: $ write cvh "#define HAVE_LIBSSH2 1
437: $!
438: $ write cvh "#ifndef USE_LIBSSH2"
439: $ write cvh "#define USE_LIBSSH2 1"
440: $ write cvh "#endif"
441: $else
442: $ write cvh "#ifdef USE_LIBSSH2"
443: $ write cvh "#undef USE_LIBSSH2"
444: $ write cvh "#endif"
445: $endif
446: $!
447: $!
448: $!
449: $if .not. nozlib
450: $then
451: $ write cvh "#define HAVE_LIBZ 1"
452: $ write cvh "#define HAVE_ZLIB_H 1"
453: $endif
454: $!
455: $!
456: $! Suppress a message in curl_gssapi.c compile.
457: $write cvh "#pragma message disable notconstqual"
458: $!
459: $! Close out the file
460: $!
461: $write cvh ""
462: $write cvh "#endif /* __CONFIG_VMS_H__ */"
463: $close cvh
464: $!
465: $all_exit:
466: $exit
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>