!-----<<< for generating Manual page Illustrations >>>----- ! integer,parameter :: iwhite = -255, igray = -128, iblack = 0, none = -999 integer,parameter :: iblue = 255, iyellow = (255*256 + 255) * 256 character(2) :: mark real :: f(151,101) external cviken !---------- real :: v(151,101) real :: g(2,2) = reshape((/ -110., -110., +110., +110./), (/2,2/)) real :: h(2,2) = reshape((/ 0., 1., 0., 1./), (/2,2/)) real :: xm(9) = (/ 0.0, 0.0, 2.5, 0.5, 1.5, 2.5, 0.5, 3.0, 3.0 /) real :: ym(9) = (/ 0.0, 3.0, 2.0, 1.0, 0.5, 1.0, 2.0, 3.0, 0.0 /) real :: pos(2,4) = reshape((/ 5., 0., 5., 2., 8., 0., 8., 2. /), (/2,4/)) real :: q(3,2) = reshape((/ 0., 1., 2., 1., 2., 0. /), (/3,2/)) do i=1,151 x = float(i-76); a = float(i-86) do j=1,101 y = float(j-51); b = float(j-31) r = sqrt(x*x + y*y); s = sqrt(a*a + b*b) v(i,j) = r*3. - s*2. + 17.; if(r > 50.) v(i,j) = 999. enddo enddo call psopn('pspaint.ps', 'a4p') call plots(2., 2.) call dfcols(0) call dframe(0., 12., 15., 10., 151, 101) call paintm(v, -80., 120., 999.) call newpen(3) call wrect(0., 12., 15., 10.) call dfpcol(1, 255*256*256) call paintr(2., 19., 3., 3.) call dframe(10., 0., 5., 10., 2, 2) call paintw(g, -100., 100., 999., h) call dfpcol(0, 200) call paintp(xm, ym, 9, 1) call newpen(2) call plot(xm(9), ym(9), 3) do i=1,9; call plot(xm(i), ym(i), 2); enddo call paintp(pos(1,1), pos(2,1), 4, 2) call dftone(0) call dframe(0., 5., 8., 4., 3, 2) call paintm(q, 0., 2., 99.) call dfpcol(1, 255*256+255) call paintc(2., 7., 0.7) call plote call pscls ! stop ! end !---------- ! integer,parameter :: iwhite = -255, igray = -128, iblack = 0, none = -999 ! integer,parameter :: iblue = 255, iyellow = (255*256 + 255) * 256 call psopn('ptext.ps', 'A4P'); call plots(2., 2.) call dfpcol(0, 200) call paintr(0., 0., 15., 9.) call lstyle('HB', 1., 0., iblack, none) call ptext('Helvetica-Bold', 14, 1., 7., 0) call lstyle('ti', 1., 30., iwhite, iblack) call ptext('Times-Italic', 12, 12., 7., 2) call pcstr(15., 6., 1., 'Courier', 30., -7) call lstyle('Kbi', 1., 0., iyellow, igray) call ptext('Testテスト', 10, 6., 4., 1) call ptext('Testテスト', 10, 6., 4., 2) call lstyle('M', 1., 180., iblue, iwhite) call ptext('Testテスト', 10, 6., 2., 0) call lstyle('S', 1.5, 0., iblack, iyellow) call ptext('W=abc', 5, 9.5, 1., 0) call plote; call pscls ! stop ! end !---------- call psopn('ptext2.ps', 'A4P') call plots(2., 2.) do i=32,127,16 y = 14. - float(i/8) do j=0,15 if (((i+j)==32) .or. ((i+j)==127)) cycle x = float(j)*0.8 call lstyle('C', 0.4, 0., 0, none) call ptext(char(i+j), 1, x, y+1., 0) call lstyle('S', 0.8, 0., 0, none) call ptext(char(i+j), 1, x, y, 0) enddo enddo call plote call pscls ! stop ! end !---------- ! character(2) :: mark call psopn('pmark.ps', 'a4p') call plots(2., 2.) call dfpcol(1, -200) call paintr(0., 0., 15.5, 4.8) do i=0,9 x = float(i)*1.5 + 1. write(mark,'(i2)') i call pcstr(x-0.5, 4.2, 0.3, mark, 0., 2) call pmark(i, x, 3.4, 1., 0.1, -255) call pmark(i, x, 2.1, 1., 0.03, 0) call pmark(i, x, 0.8, 1., 0. , -128) enddo call plote call pscls ! stop ! end !---------- ! real :: f(151,101) do i=1,151 x = float(i-76); a = float(i-86) do j=1,101 y = float(j-51); b = float(j-31) r = sqrt(x*x + y*y); s = sqrt(a*a + b*b) f(i,j) = r*3. - s*2. + 17.; if(r > 50.) f(i,j) = 999. enddo enddo call psopn('cont.ps', 'a4p') call plots(0., 0.) call wrect(2., 2., 15., 10.) call conts(2., 2., 15., 10., 151, 101, 0.12) call contx(f, 999., 1, 5,-100, -11, 0) call contx(f, 999., 1, 5, -10, 0, 10) call contx(f, 999., 1, 5, 1, 25, 11) call contx(f, 999., 1, 5, 26, 50, 14) call contx(f, 999., 1, 5, 51, 75, 2) call contx(f, 999., 1, 5, 76, 100, 12) call contx(f, 999., 1, 5, 101, 200, 3) call plot( 4., 15., -3) call plot( 7.,-2.5, 2) call plot(11., 0.5, 2) call plot( 4., 3. , 2) call plot( 0., 0. , 2) call dfcols(0) call dframo(0., 0., 7., -2.5, 4., 3., 151, 101) call contso(0., 0., 7., -2.5, 4., 3., 151, 101) call paintm(f, 0., 100., 999.) call contx(f, 999., 5, 4, -50, 150, 0) call plote call pscls ! stop ! end !---------- ! external cviken call cvinit(100, 35.*60., 135.*60., 0., 0.) call psopn("wshore.ps","A4P") call plots(2., 2.) call plot(8., 7., -3) call wshore(0., 0., 12, 250., cviken) do i=20,50,5 call cviken(float(i*60), 7200., xe, yn) call plot(xe/250., yn/250., 3) do k=121,155 call cviken(float(i*60), float(k*60), xe, yn) call plot(xe/250., yn/250., 2) enddo enddo do k=120,155,5 call cviken(1200., float(k*60), xe, yn) call plot(xe/250., yn/250., 3) do i=21,50 call cviken(float(i*60), float(k*60), xe, yn) call plot(xe/250., yn/250., 2) enddo enddo call plot(0., 16., -3) call wrect(-8., -8., 16., 10.) call scisor(-8., -8., 16., 10.) call cvinit(53, 0., 0., 0., 0.) call cviken(float(35*60), float(135*60), xo, yo) call rshore(1, 34, 36, 133, 136) call pshore(-xo/12., -yo/12., 212, 12., cviken) call plot(-8., 0., 3) do k=-90,90 call cviken(float(35*60), float(135*60+k), xe, yn) call plot((xe-xo)/12., (yn-yo)/12., 2) enddo do k=134,136 call plot(0., -8., 3) do i=-60,30 call cviken(float(35*60+i), float(k*60), xe, yn) call plot((xe-xo)/12., (yn-yo)/12., 2) enddo enddo call plote call pscls ! stop ! end !------------------ stop end