File: x02f.f90

package info (click to toggle)
plplot 5.15.0%2Bdfsg-19
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 31,312 kB
  • sloc: ansic: 79,707; xml: 28,583; cpp: 20,033; ada: 19,456; tcl: 12,081; f90: 11,431; ml: 7,276; java: 6,863; python: 6,792; sh: 3,274; perl: 828; lisp: 75; makefile: 50; sed: 34; fortran: 5
file content (160 lines) | stat: -rw-r--r-- 5,286 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
!   Demonstrates multiple windows and color map 0
!
!   Copyright (C) 2004-2016  Alan W. Irwin
!   Copyright (C) 2005  Andrew Ross
!
!   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

!     N.B. the pl_test_flt parameter used in this code is only
!     provided by the plplot module to allow convenient developer
!     testing of either kind(1.0) or kind(1.0d0) floating-point
!     precision regardless of the floating-point precision of the
!     PLplot C libraries.  We do not guarantee the value of this test
!     parameter so it should not be used by users, and instead user
!     code should replace the pl_test_flt parameter by whatever
!     kind(1.0) or kind(1.0d0) precision is most convenient for them.
!     For further details on floating-point precision issues please
!     consult README_precision in this directory.
!
program x02f
    use plplot
    implicit none
    integer :: plparseopts_rc

    !    Process command-line arguments
    plparseopts_rc = plparseopts(PL_PARSE_FULL)
    if(plparseopts_rc .ne. 0) stop "plparseopts error"


    !   Initialize plplot
    call plinit()

    !   Run demos
    call demo1
    call demo2

    call plend

contains

    !--------------------------------------------------------------------------
    !     demo1
    !
    !     Demonstrates multiple windows and default color map 0 palette.
    !--------------------------------------------------------------------------
    subroutine demo1

        call plbop

        !   Divide screen into 16 regions
        call plssub(4,4)

        call draw_windows(16, 0)

        call pleop

    end subroutine demo1


    !--------------------------------------------------------------------------
    !     demo2
    !
    !     Demonstrates multiple windows, user-modified color map 0 palette,
    !     and HLS -> RGB translation.
    !--------------------------------------------------------------------------
    subroutine demo2
        integer, parameter :: tablesize = 116
        integer, dimension(tablesize) :: r, g, b
        integer :: i

        real(kind=pl_test_flt), parameter :: lmin = 0.15_pl_test_flt, lmax = 0.85_pl_test_flt
        real(kind=pl_test_flt) h, l, s, r1, g1, b1

        call plbop

        !   Divide screen into 100 regions
        call plssub(10,10)

        do i=0,99
            !   Bounds on HLS, from plhlsrgb() commentary --
            !   hue		[0., 360.]	degrees
            !   lightness	        [0., 1.]	magnitude
            !   saturation	[0., 1.]	magnitude

            !   Vary hue uniformly from left to right
            h = (360._pl_test_flt/10._pl_test_flt)*mod(i,10)
            !   Vary lightness uniformly from top to bottom, between min and max
            l = lmin + (lmax - lmin) * (i / 10) / 9._pl_test_flt
            !   Use_ max saturation
            s = 1._pl_test_flt

            call plhlsrgb(h, l, s, r1, g1, b1)

            r(i+17) = int(r1*255.001)
            g(i+17) = int(g1*255.001)
            b(i+17) = int(b1*255.001)
        enddo

        do i=1,16
            call plgcol0(i-1,r(i),g(i),b(i))
        enddo

        call plscmap0(r, g, b)

        call draw_windows(100, 16)

        call pleop

    end subroutine demo2

    !--------------------------------------------------------------------------
    !     draw_windows
    !
    !     Draws a set of numbered boxes with colors according to cmap0 entry.
    !--------------------------------------------------------------------------
    subroutine draw_windows( nw, cmap0_offset )

        integer :: nw, cmap0_offset
        integer :: i,j
        real(kind=pl_test_flt) :: vmin, vmax, xj
        character (len=3) :: text

        call plschr(0.0_pl_test_flt, 3.5_pl_test_flt)
        call plfont(4)

        do i=0,nw-1
            call plcol0(i+cmap0_offset)
            write (text,'(i0)') i

            call pladv(0)
            vmin = 0.1_pl_test_flt
            vmax = 0.9_pl_test_flt
            do j=1,3
                xj = j
                call plwidth(xj)
                call plvpor(vmin,vmax,vmin,vmax)
                call plwind(0.0_pl_test_flt, 1.0_pl_test_flt, 0.0_pl_test_flt, 1.0_pl_test_flt)
                call plbox('bc', 0.0_pl_test_flt, 0, 'bc', 0.0_pl_test_flt, 0)
                vmin = vmin + 0.1_pl_test_flt
                vmax = vmax - 0.1_pl_test_flt
            enddo
            call plwidth(1._pl_test_flt)
            call plptex(0.5_pl_test_flt, 0.5_pl_test_flt, 1.0_pl_test_flt, 0.0_pl_test_flt, 0.5_pl_test_flt, text)
        enddo

    end subroutine draw_windows
end program x02f