File: image.f90

package info (click to toggle)
wsjtx 2.7.0%2Brepack-1
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 70,440 kB
  • sloc: cpp: 75,379; f90: 46,460; python: 27,241; ansic: 13,367; fortran: 2,382; makefile: 197; sh: 133
file content (336 lines) | stat: -rwxr-xr-x 8,307 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
subroutine imopen(plotfile)
  character*(*) plotfile
  common/imcom/ lu,npage

  lu=80
  open(lu,file=plotfile,status='unknown')
  write(lu,1000) 
1000 format('%!PS-Adobe-2.0'/                                            &
          '/rightshow { dup stringwidth pop neg 0 rmoveto show } def'/   &
          '/centershow { dup stringwidth pop neg 2 div ',                &
          '0 rmoveto show } def'/                                        &
          '/lt { lineto } def'/'%%Page: 1 1')
  npage=1

  return
end subroutine imopen

subroutine impalette(palette)
  character*(*) palette
  integer r(0:8),g(0:8),b(0:8)
  integer rr,gg,bb
  common/imcom/ lu,npage
  common/imcom2/rr(0:255),gg(0:255),bb(0:255)

  if(palette.eq.'afmhot') then
     do i=0,255
        j=255-i
        rr(i)=min(255,2*j)
        gg(i)=max(0,min(255,2*j-128))
        bb(i)=max(0,min(255,2*j-256))
     enddo
  else if(palette.eq.'hot') then
     do i=0,255
        j=255-i
        rr(i)=min(255,3*j)
        gg(i)=max(0,min(255,3*j-256))
        bb(i)=max(0,min(255,3*j-512))
     enddo
  else
     open(11,file="Palettes/"//palette,status="old")
     do j=0,8
        read(11,*) r(j),g(j),b(j)
     enddo
     close(11)
     do i=0,255
        j0=i/32
        j1=j0+1
        k=i-32*j0
        rr(i)=r(j0) + int((k*(r(j1)-r(j0)))/31 + 0.5)
        gg(i)=g(j0) + int((k*(g(j1)-g(j0)))/31 + 0.5)
        bb(i)=b(j0) + int((k*(b(j1)-b(j0)))/31 + 0.5)
     enddo

  endif

  return
end subroutine impalette

subroutine imclose
  common/imcom/ lu,npage
  write(lu,1000)
1000 format('showpage'/'%%Trailer')
  close(lu)
  return
end subroutine imclose

subroutine imnewpage
  common/imcom/ lu,npage
  npage=npage+1
  write(lu,1000) npage,npage
1000 format('showpage'/'%%Page:',2i4)
  return
end subroutine imnewpage

subroutine imxline(x,y,dx)
! Draw a line from (x,y) to (x+dx,y)  integer r,g,b
  common/imcom/ lu,npage
  write(lu,1000) 72.0*x,72.0*y,72.0*dx
1000 format('newpath',2f7.1,' moveto',f7.1,' 0 rlineto stroke')
  return
end subroutine imxline

subroutine imyline(x,y,dy)
! Draw a line from (x,y) to (x,y+dy)
  common/imcom/ lu,npage
  write(lu,1000) 72.0*x,72.0*y,72.0*dy
1000 format('newpath',2f7.1,' moveto 0',f7.1,' rlineto stroke')
  return
end subroutine imyline

subroutine imwidth(width)
  common/imcom/ lu,npage
  write(lu,1000) width
1000 format(f7.1,' setlinewidth')
  return
end subroutine imwidth

subroutine imfont(fontname,npoints)
  character*(*) fontname
  common/imcom/ lu,npage
  write(lu,1000) fontname,npoints
1000 format('/',a,' findfont',i4,' scalefont setfont')
  return
end subroutine imfont

subroutine imstring(string,x,y,just,ndeg)
  character*(*) string
  common/imcom/ lu,npage
  write(lu,1000) 72.0*x,72.0*y,ndeg,string
1000 format(2f7.1,' moveto',i4,' rotate'/'(',a,')')
  if(just.eq.1) write(lu,*) 'rightshow'
  if(just.eq.2) write(lu,*) 'centershow'
  if(just.eq.3) write(lu,*) 'show'
  write(lu,1010) -ndeg
1010 format(i4,' rotate'/)
  return
end subroutine imstring

subroutine imr4mat(z,IP,JP,imax,jmax,zz1,zz2,x,y,dx,dy,nbox)
  real z(IP,JP)
  integer idat(2048)
  common/imcom/ lu,npage

  z1=zz1
  z2=zz2
  if(z1.eq.0.0 .and. z2.eq.0.0) then
     z1=z(1,1)
     z2=z1
     do i=1,imax
        do j=1,jmax
           z1=min(z(i,j),z1)
           z2=max(z(i,j),z2)
        enddo
     enddo
  endif
  scale=255.99/(z2-z1)

  write(lu,1002) 72.0*x,72.0*y,72.0*dx,72.0*dy
1002 format(2f7.1,' translate',2f7.1,' scale')
  write(lu,*) imax,jmax,8,' [',imax,0,0,jmax,0,0,']'
  write(lu,*) '{<'

  do j=1,jmax
     do i=1,imax
        idat(i)=scale*(z(i,j)-z1)
        idat(i)=max(idat(i),0)
        idat(i)=min(idat(i),255)
        idat(i)=255-idat(i)
     enddo
     write(lu,1004) (idat(i),i=1,imax)
1004 format(30z2.2)
  enddo
  write(lu,*) '>} image'
  write(lu,1006) 1.0/(72.0*dx),1.0/(72.0*dy),-72.0*x,-72.0*y
1006 format(2f9.6,' scale',2f7.1,' translate')

  if(nbox.ne.0) then
     write(lu,1010) 72.0*x,72.0*y,72.0*dx,72.0*dy,-72*dx
1010 format('newpath',2f7.1,' moveto',f7.1,' 0 rlineto 0',             &
          f7.1,' rlineto',f7.1,' 0 rlineto closepath stroke')
  endif

  return
end subroutine imr4mat

subroutine imr4mat_color(z,IP,JP,imax,jmax,zz1,zz2,x,y,dx,dy,nbox)
  real z(IP,JP)
  integer idat(2048,3)
  integer rr,gg,bb
  common/imcom/ lu,npage
  common/imcom2/rr(0:255),gg(0:255),bb(0:255)

  z1=zz1
  z2=zz2
  if(z1.eq.0.0 .and. z2.eq.0.0) then
     z1=z(1,1)
     z2=z1
     do i=1,imax
        do j=1,jmax
           z1=min(z(i,j),z1)
           z2=max(z(i,j),z2)
        enddo
     enddo
  endif
  scale=255.99/(z2-z1)

  write(lu,1002) 72.0*x,72.0*y,72.0*dx,72.0*dy
1002 format(2f7.1,' translate',2f7.1,' scale')
  write(lu,1003) imax,jmax,8,imax,0,0,jmax,0,0
1003 format(3i5,' [',6i4,']')
  write(lu,1004) imax
1004 format('{currentfile 3',i4,' mul string readhexstring pop} bind'/   &
          'false 3 colorimage')

  do j=1,jmax
     do i=1,imax
        n=scale*(z(i,j)-z1)
        n=max(n,0)
        n=min(n,255)
        idat(i,1)=rr(n)
        idat(i,2)=gg(n)
        idat(i,3)=bb(n)
     enddo
     write(lu,1005) (idat(i,1),idat(i,2),idat(i,3),i=1,imax)
1005 format(30z2.2)
  enddo

  write(lu,1006) 1.0/(72.0*dx),1.0/(72.0*dy),-72.0*x,-72.0*y
1006 format(2f9.6,' scale',2f7.1,' translate')

  if(nbox.ne.0) then
     write(lu,1010) 72.0*x,72.0*y,72.0*dx,72.0*dy,-72*dx
1010 format('newpath',2f7.1,' moveto',f7.1,' 0 rlineto 0',             &
          f7.1,' rlineto',f7.1,' 0 rlineto closepath stroke')
  endif

  return
end subroutine imr4mat_color

subroutine imr4pro(p,imax,yy1,yy2,x,y,dx,dy,nbox)
  real p(imax)
  common/imcom/ lu,npage

  y1=yy1
  y2=yy2
  if(y1.eq.0.0 .and. y2.eq.0.0) then
     y1=p(1)
     y2=y1
     do i=1,imax
        y1=min(p(i),y1)
        y2=max(p(i),y2)
     enddo
  endif

  xscale=72.0*dx/imax
  xoff=72.0*x
  yscale=72.0*dy
  if(y1.ne.y2) yscale=yscale/(y2-y1)
  yoff=72.0*y

  write(lu,*) '1.416 setmiterlimit'
  write(lu,1002) xoff+0.5*xscale,yoff+yscale*(p(1)-y1)
1002 format('newpath',2f7.1,' moveto')

  do i=2,imax
     write(lu,1004) xoff+(i-0.5)*xscale,yoff+yscale*(p(i)-y1)
1004 format(2f6.1,' lt')
  enddo
  write(lu,*) 'stroke'

  if(nbox.ne.0) then
     write(lu,1010) xoff,yoff,72.0*dx,72.0*dy,-72*dx
1010 format('newpath',2f7.1,' moveto',f7.1,' 0 rlineto 0',               &
          f7.1,' rlineto',f7.1,' 0 rlineto closepath stroke')
  endif

  return
end subroutine imr4pro

subroutine imline(x1,y1,x2,y2)
  common/imcom/ lu,npage
  write(lu,1000) 72*x1,72*y1,72*x2,72*y2
1000 format('newpath',2f7.1,' moveto',2f7.1,' lineto stroke')
  return
end subroutine imline

subroutine imcircle(x,y,radius,shade)
  common/imcom/ lu,npage
  write(lu,1000) shade
1000 format(f7.1,' setgray')
  write(lu,1002) 72*x,72*y,72*radius
1002 format('newpath',3f7.1,' 0 360 arc fill')
  write(lu,1000) 0.0
  write(lu,1004) 72*x,72*y,72*radius
1004 format('newpath',3f7.1,' 0 360 arc stroke')
  return
end subroutine imcircle

subroutine imtriangle(x,y,rr,shade)
  common/imcom/ lu,npage
  write(lu,1000) shade
1000 format(f7.1,' setgray')
  write(lu,1002) 72*x,72*(y+rr)
1002 format('newpath',2f7.1,' moveto ')
  write(lu,1004) 72*(x-rr),72*(y-rr)
1004 format(2f7.1,' lineto ')
  write(lu,1004) 72*(x+rr),72*(y-rr)
  write(lu,*) 'closepath fill 0 setgray'
  write(lu,1002) 72*x,72*(y+rr)
  write(lu,1004) 72*(x-rr),72*(y-rr)
  write(lu,1004) 72*(x+rr),72*(y-rr)
  write(lu,*) 'closepath stroke'
  
  return
end subroutine imtriangle

subroutine imr4prov(p,jmax,xx1,xx2,x,y,dx,dy,nbox)
  real p(jmax)
  common/imcom/ lu,npage

  x1=xx1
  x2=xx2
  if(x1.eq.0.0 .and. x2.eq.0.0) then
     x1=p(1)
     x2=x1
     do j=1,jmax
        x1=min(p(j),x1)
        x2=max(p(j),x2)
     enddo
  endif

  xscale=72.0*dx
  xoff=72.0*x
  if(x1.ne.x2) xscale=xscale/(x2-x1)

  yscale=72.0*dy/jmax
  yoff=72.0*y
  
  write(lu,*) '1.416 setmiterlimit'
  write(lu,1002) xoff+xscale*(x2-p(1)),yoff+0.5*yscale
1002 format('newpath',2f7.1,' moveto')
  
  do j=2,jmax
     write(lu,1004) xoff+xscale*(x2-p(j)),yoff+(j-0.5)*yscale
1004 format(2f6.1,' lt')
  enddo
  write(lu,*) 'stroke'

  if(nbox.ne.0) then
     write(lu,1010) xoff,yoff,72.0*dx,72.0*dy,-72*dx
1010 format('newpath',2f7.1,' moveto',f7.1,' 0 rlineto 0',            &
          f7.1,' rlineto',f7.1,' 0 rlineto closepath stroke')
  endif

  return
end subroutine imr4prov