[BACK]Return to buildvms.com CVS log [TXT][DIR] Up to [local] / OpenXM_contrib / gnuplot

Annotation of OpenXM_contrib/gnuplot/buildvms.com, Revision 1.1.1.2

1.1       maekawa     1: $ ! for batch operation, set default to the gnuplot directory
                      2: $ !
                      3: $ ! buildvms.com
                      4: $ ! Command file to compile/link gnuplot, gnuplot_x11, and make gnuplot.hlb
                      5: $ !
                      6: $ ! lph: modified for compatibility with VMS 4.x (which lacks 'if ... endif'),
                      7: $ ! but made the default DECC
                      8: $ !
                      9: $! set noon
                     10: $ ON ERROR THEN GOTO FINISH
                     11: $!
                     12: $! detect compiler - drd
                     13: $! if DECC is around, assume that, else gcc is preferred. Finally vaxc
                     14: $ its_decc = (f$search("SYS$SYSTEM:DECC$COMPILER.EXE") .nes. "")
                     15: $ its_gnuc = 0  ! comment out the next line to use VAXC if gcc is also present
                     16: $ its_gnuc = .not.its_decc .and. (f$trnlnm("gnu_cc").nes."")
                     17: $ its_vaxc = .not. (its_decc .or. its_gnuc)
                     18: $ its_decw = (f$trnlnm("DECW$INCLUDE") .nes. "")
                     19: $!
                     20: $! configure
                     21: $
                     22: $ pfix = "/prefix=all"
                     23: $ rtl  = "DECCRTL"
                     24: $   if .NOT. its_decc then pfix = "/nolist"
                     25: $   if .NOT. its_decc then rtl  = "VAXCRTL"
                     26: $!
                     27: $ x11 = ""
                     28: $ if its_decw then x11 = "X11,"
                     29: $!
                     30: $!-----------------------------------------------------------------
                     31: $!-----------------------------------------------------------------
                     32: $! customize CFLAGS for version of VMS, CRTL, and C compiler.
                     33: $!-----------------------------------------------------------------
1.1.1.2 ! maekawa    34: $ IF F$GETSYI("ARCH_TYPE") .EQ. 1
        !            35: $ THEN
        !            36: $!  these defines work for OpenVMS VAX v6.2 and DEC C v5.7
        !            37: $ CFLAGS = "/define=(ANSI_C,HAVE_UNISTD_H,HAVE_GETCWD,"-
        !            38:  +"HAVE_SLEEP,''x11'NO_GIH,PIPES,DECCRTL)''pfix'"
        !            39: $ ELSE
1.1       maekawa    40: $!  these defines work for OpenVMS Alpha v6.2 and DEC C v5.3
1.1.1.2 ! maekawa    41: $ CFLAGS = "/define=(ANSI_C,HAVE_LGAMMA,HAVE_ERF,HAVE_UNISTD_H,HAVE_GETCWD,"-
        !            42:  +"HAVE_SLEEP,''x11'NO_GIH,PIPES,DECCRTL)''pfix'"
        !            43: $ ENDIF
1.1       maekawa    44: $!
                     45: $!-----------------------------------------------------------------
                     46: $!
                     47: $! A generic starting point
                     48: $!-----------------------------------------------------------------
                     49: $!
                     50: $!$ CFLAGS = "/NOWARN/NOOP/DEFINE=(''x11'NO_GIH,PIPES,''rtl')''pfix'"
                     51: $!
                     52: $! ----------------------------------------------------------------
                     53: $!
                     54: $! For  VMS 4.7 and VAX C v2.4
                     55: $! ("Compiler abort - virtual memory limits exceeded" if attempt
                     56: $!  to include all applicable terminals, but otherwise builds OK.
                     57: $!  Runtime problem: an exit handler error, also w/ gcc build;
                     58: $!  a VAXCRTL atexit bug?)
                     59: $!
                     60: $! Note: VAX uses  D_FLOAT, maximum exponent ca 10e +/- 38;
                     61: $!       will cause problems with some of the demos
                     62: $!
                     63: $!$ CFLAGS    = "/NOOP/DEFINE=(NO_STRSTR, NO_SYS_TYPES_H, "-
                     64: $!               +"HAVE_GETCWD, HAVE_SLEEP, NO_LOCALE_H,"-
                     65: $!               +"SHORT_TERMLIST, NO_GIH,PIPES, ''rtl')"
                     66: $!$!
                     67: $!
                     68: $!-----------------------------------------------------------------
                     69: $!
                     70: $! This will build with gcc v1.42 on VMS 4.7
                     71: $! (no virtual memory limit problem)
                     72: $!
                     73: $! gcc v1.42 string.h can prefix str routines w/ gnu_ (ifdef GCC_STRINGS)
                     74: $! but the routines in GCCLIB are not prefixed w/ gcc_  :-(
                     75: $! link with GCCLIB, then ignore the link warnings about multiple
                     76: $! definitions of STR... in C$STRINGS
                     77: $!
                     78: $! GCC v1.42 has a locale.h, but neither gcc nor VMS v4.7 VAXCRTL has
                     79: $! the  setlocale function
                     80: $!
                     81: $!
                     82: $! Note: _assert.c defines assert_gcc, if ndef NDEBUG, but
                     83: $!        cgm.trm undefines NDEBUG, so we always compile/link  _assert.c
                     84: $!
                     85: $!$ CFLAGS    = "/NOOP/DEFINE=(''x11'NO_STRSTR, HAVE_GETCWD,"-
                     86: $!             +" HAVE_SLEEP, NO_LOCALE_H, NO_GIH, PIPES, ''rtl')"
                     87: $!
                     88: $!-----------------------------------------------------------------
                     89: $!-----------------------------------------------------------------
                     90: $!
                     91: $ TERMFLAGS = "/INCLUDE=([],[.term])"
                     92: $
                     93: $ EXTRALIB = ""
                     94: $ if its_gnuc then cc := GCC/NOCASE
                     95: $ if its_gnuc then EXTRALIB = ",[]_assert,GNU_CC:[000000]GCCLIB/LIB"
                     96: $
                     97: $
                     98: $ CFLAGS="''cflags'" + "''pfix'"
                     99: $ LINKOPT=""
                    100: $!
                    101: $ if .NOT. its_decc then -
                    102:       LINKOPT=",sys$disk:[]linkopt.vms/opt"
                    103: $!
                    104: $!
                    105: $ if its_decw then DEFINE/NOLOG X11 DECW$INCLUDE
                    106: $ if its_decw then DEFINE/NOLOG SYS SYS$LIBRARY
                    107: $!
                    108: $ set verify
                    109: $ cc 'CFLAGS' alloc.c
                    110: $ cc 'CFLAGS' binary.c
                    111: $ cc 'CFLAGS' bitmap.c
                    112: $ cc 'CFLAGS' command.c
                    113: $ cc 'CFLAGS' contour.c
                    114: $ cc 'CFLAGS' datafile.c
                    115: $ cc 'CFLAGS' eval.c
                    116: $ cc 'CFLAGS' fit.c
                    117: $ cc 'CFLAGS' graphics.c
                    118: $ cc 'CFLAGS' graph3d.c
1.1.1.2 ! maekawa   119: $ cc 'CFLAGS' help.c
1.1       maekawa   120: $ cc 'CFLAGS' hidden3d.c
                    121: $ cc 'CFLAGS' internal.c
                    122: $ cc 'CFLAGS' interpol.c
                    123: $ cc 'CFLAGS' matrix.c
                    124: $ cc 'cflags' misc.c
                    125: $ cc 'CFLAGS' parse.c
                    126: $ cc 'CFLAGS' plot.c
                    127: $ cc 'CFLAGS' plot2d.c
                    128: $ cc 'CFLAGS' plot3d.c
                    129: $ cc 'CFLAGS' scanner.c
                    130: $ cc 'CFLAGS' set.c
                    131: $ cc 'CFLAGS' show.c
                    132: $ cc 'CFLAGS' specfun.c
                    133: $ cc 'CFLAGS' standard.c
                    134: $ cc 'CFLAGS' stdfn.c
                    135: $ cc 'cflags' 'TERMFLAGS' term.c
                    136: $ cc 'cflags' time.c
                    137: $ cc 'CFLAGS' util.c
                    138: $ cc 'CFLAGS' util3d.c
                    139: $ cc 'CFLAGS' version.c
                    140: $ cc 'CFLAGS' vms.c
                    141: $ if its_gnuc then cc 'CFLAGS' GNU_CC_INCLUDE:[000000]_assert.c
                    142: $!
1.1.1.2 ! maekawa   143: $ link/exe=gnuplot.exe -
        !           144: bitmap.obj,command.obj,contour.obj,eval.obj,graphics.obj,graph3d.obj,help.obj,-
        !           145: vms.obj,binary.obj,specfun.obj,interpol.obj,fit.obj,matrix.obj,internal.obj,-
        !           146: misc.obj,parse.obj,plot.obj,plot2d.obj,plot3d.obj,scanner.obj,set.obj,-
        !           147: show.obj,datafile.obj,alloc.obj,standard.obj,stdfn.obj,term.obj,util.obj,-
        !           148: version.obj,util3d.obj,hidden3d.obj,time.obj'extralib''LINKOPT'
1.1       maekawa   149: $!
                    150: $ cc 'CFLAGS' bf_test.c
                    151: $ link /exe=bf_test bf_test,binary,alloc 'extralib''LINKOPT'
                    152: $ if .NOT. its_decw  then goto do_docs
                    153: $!
1.1.1.2 ! maekawa   154: $ CC 'CFLAGS' GPLT_X11
        !           155: $ CC 'CFLAGS' stdfn.c
1.1       maekawa   156: $ LINK /exe=GNUPLOT_X11 gplt_x11,stdfn 'extralib''LINKOPT',SYS$INPUT:/OPT
                    157: SYS$SHARE:DECW$XLIBSHR/SHARE
                    158: $!
                    159: $DO_DOCS:
                    160: $ SET DEF [.DOCS]
                    161: $ if f$locate("ALL_TERM_DOC",CFLAGS).ne.f$length(CFLAGS) then -
                    162:        copy /concatenate [-.term]*.trm []allterm.h
                    163: $ cc 'CFLAGS' /OBJ=doc2rnh.obj/include=([],[-],[-.term]) doc2rnh.c
1.1.1.2 ! maekawa   164: $ cc 'CFLAGS' /OBJ=termdoc.obj/include=([],[-],[-.term]) termdoc.c
1.1       maekawa   165: $ SET DEF [-]          ! LINKOPT is defined as being in []
1.1.1.2 ! maekawa   166: $ link [.docs]doc2rnh.obj,termdoc.obj /exe=[.docs]doc2rnh 'extralib''LINKOPT'
1.1       maekawa   167: $ doc2rnh := $sys$disk:[.docs]doc2rnh
                    168: $ doc2rnh [.docs]gnuplot.doc [.docs]gnuplot.rnh
                    169: $ RUNOFF [.docs]gnuplot.rnh
                    170: $ library/create/help sys$disk:[]gnuplot.hlb gnuplot.hlp
                    171: $!
1.1.1.2 ! maekawa   172: $ set default [.demo]
        !           173: $ run [-]bf_test
        !           174: $ set default [-]
1.1       maekawa   175: $ if its_decw then -
                    176:   write sys$output "%define GNUPLOT_X11 :== $Disk:[directory]GNUPLOT_X11"
                    177: $!
                    178: $FINISH:
                    179: $ set noverify
                    180: $ if its_decw then deassign x11
                    181: $ exit

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>