This file is indexed.

/usr/share/doc/libplplot12/examples/f95/x03f.f90 is in libplplot-dev 5.10.0+dfsg-1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

 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
!    $Id: x03f.f90 12094 2011-12-03 08:35:52Z andrewross $
!    Generates polar plot with, 1-1 scaling
!
!    Copyright (C) 2004  Alan W. Irwin
!
!    This file is part of PLplot.
!
!    PLplot is free software; you can redistribute it and/or modify
!    it under the terms of the GNU Library General Public License as
!    published by the Free Software Foundation; either version 2 of the
!    License, or (at your option) any later version.
!
!    PLplot is distributed in the hope that it will be useful,
!    but WITHOUT ANY WARRANTY; without even the implied warranty of
!    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
!    GNU Library General Public License for more details.
!
!    You should have received a copy of the GNU Library General Public
!    License along with PLplot; if not, write to the Free Software
!    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA

program x03f95
    use plplot, PI => PL_PI
    use plf95demolib
    implicit none

    character (len=3) :: text
    real(kind=plflt), dimension(0:360) :: x0, y0, x, y
    real(kind=plflt) :: dtr, theta, dx, dy, offset
    integer :: i
!    Process command-line arguments
    call plparseopts(PL_PARSE_FULL)

!   Set orientation to portrait - note not all device drivers
!   support this, in particular most interactive drivers do not.
    call plsori(1)

    dtr = PI/180.0_plflt
    x0 = cos(dtr * arange(0,361))
    y0 = sin(dtr * arange(0,361))

!    Initialize PLplot

    call plinit()

!    Set up viewport and window, but do not draw box

    call plenv(-1.3_plflt, 1.3_plflt, -1.3_plflt, 1.3_plflt, 1, -2)
!   Draw circles for polar grid
    do i = 1,10
      call plarc(0.0_plflt, 0.0_plflt, 0.1_plflt*i, 0.1_plflt*i, &
           0.0_plflt, 360.0_plflt, 0.0_plflt, 0)
    enddo
    call plcol0(2)
    do i = 0,11
      theta = 30.0_plflt*i
      dx = cos(dtr*theta)
      dy = sin(dtr*theta)

!      Draw radial spokes for polar grid

      call pljoin(0.0_plflt, 0.0_plflt, dx, dy)
      write (text,'(i3)') nint(theta)

!      Write labels for angle

      text = adjustl(text)

      if (theta .lt. 9.99) then
         offset = 0.45
      elseif (theta .lt. 99.9) then
         offset = 0.30
      else
         offset = 0.15
      endif
!      Slightly off zero to avoid floating point logic flips at
!      90 and 270 deg.
      if (dx >= -0.00001_plflt) then
        call plptex(dx, dy, dx, dy, -offset, text)
      else
        call plptex(dx, dy, -dx, -dy, 1._plflt+offset, text)
      end if
    enddo
!    Draw the graph

    x = x0 * sin(5.0_plflt * dtr * arange(0,361))
    y = y0 * sin(5.0_plflt * dtr * arange(0,361))

    call plcol0(3)
    call plline(x,y)

    call plcol0(4)
    call plmtex('t', 2.0_plflt, 0.5_plflt, 0.5_plflt, &
      '#frPLplot Example 3 - r(#gh)=sin 5#gh')

!    Close the plot at end

    call plend
end program x03f95