File: Circle.hs

package info (click to toggle)
haskell-gloss-rendering 1.13.1.2-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 112 kB
  • sloc: haskell: 798; makefile: 4
file content (264 lines) | stat: -rw-r--r-- 9,312 bytes parent folder | download | duplicates (3)
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
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash    #-}
{-# OPTIONS_HADDOCK hide #-}

-- | Fast(ish) rendering of circles.
module Graphics.Gloss.Internals.Rendering.Circle
        ( renderCircle
        , renderArc)
where
import  Graphics.Gloss.Internals.Rendering.Common
import  GHC.Exts
import  qualified Graphics.Rendering.OpenGL.GL          as GL


-------------------------------------------------------------------------------
-- | Decide how many line segments to use to render the circle.
--   The number of segments we should use to get a nice picture depends on
--   the size of the circle on the screen, not its intrinsic radius.
--   If the viewport has been zoomed-in then we need to use more segments.
circleSteps :: Float -> Int
circleSteps sDiam
        | sDiam < 8     = 8
        | sDiam < 16    = 16
        | sDiam < 32    = 32
        | otherwise     = 64
{-# INLINE circleSteps #-}


-- Circle ---------------------------------------------------------------------
-- | Render a circle with the given thickness
renderCircle :: Float -> Float -> Float -> Float -> Float -> IO ()
renderCircle posX posY scaleFactor radius_ thickness_
 = go (abs radius_) (abs thickness_)
 where go radius thickness

        -- If the circle is smaller than a pixel, render it as a point.
        | thickness     == 0
        , radScreen     <- scaleFactor * (radius + thickness / 2)
        , radScreen     <= 1
        = GL.renderPrimitive GL.Points
            $ GL.vertex $ GL.Vertex2 (gf posX) (gf posY)

        -- Render zero thickness circles with lines.
        | thickness == 0
        , radScreen     <- scaleFactor * radius
        , steps         <- circleSteps radScreen
        = renderCircleLine  posX posY steps radius

        -- Some thick circle.
        | radScreen     <- scaleFactor * (radius + thickness / 2)
        , steps         <- circleSteps radScreen
        = renderCircleStrip posX posY steps radius thickness


-- | Render a circle as a line.
renderCircleLine :: Float -> Float -> Int -> Float -> IO ()
renderCircleLine (F# posX) (F# posY) steps (F# rad)
 = let  n               = fromIntegral steps
        !(F# tStep)     = (2 * pi) / n
        !(F# tStop)     = (2 * pi)

   in   GL.renderPrimitive GL.LineLoop
         $ renderCircleLine_step posX posY tStep tStop rad 0.0#
{-# INLINE renderCircleLine #-}


-- | Render a circle with a given thickness as a triangle strip
renderCircleStrip :: Float -> Float -> Int -> Float -> Float -> IO ()
renderCircleStrip (F# posX) (F# posY) steps r width
 = let  n               = fromIntegral steps
        !(F# tStep)     = (2 * pi) / n
        !(F# tStop)     = (2 * pi) + (F# tStep) / 2
        !(F# r1)        = r - width / 2
        !(F# r2)        = r + width / 2

   in   GL.renderPrimitive GL.TriangleStrip
         $ renderCircleStrip_step posX posY tStep tStop r1 0.0# r2
                (tStep `divideFloat#` 2.0#)
{-# INLINE renderCircleStrip #-}


-- Arc ------------------------------------------------------------------------
-- | Render an arc with the given thickness.
renderArc
 :: Float -> Float -> Float -> Float -> Float -> Float -> Float -> IO ()
renderArc posX posY scaleFactor radius_ a1 a2 thickness_
 = go (abs radius_) (abs thickness_)
 where
       go radius thickness
        -- Render zero thickness arcs with lines.
        | thickness == 0
        , radScreen     <- scaleFactor * radius
        , steps         <- circleSteps radScreen
        = renderArcLine posX posY steps radius a1 a2

        -- Some thick arc.
        | radScreen     <- scaleFactor * (radius + thickness / 2)
        , steps         <- circleSteps radScreen
        = renderArcStrip posX posY steps radius a1 a2 thickness


-- | Render an arc as a line.
renderArcLine
 :: Float -> Float -> Int -> Float -> Float -> Float -> IO ()
renderArcLine (F# posX) (F# posY) steps (F# rad) a1 a2
 = let  n               = fromIntegral steps
        !(F# tStep)     = (2 * pi) / n
        !(F# tStart)    = degToRad a1
        !(F# tStop)     = degToRad a2 + if a1 >= a2 then 2 * pi else 0

        -- force the line to end at the desired angle
        endVertex       = addPointOnCircle posX posY rad tStop

   in   GL.renderPrimitive GL.LineStrip
         $ do   renderCircleLine_step posX posY tStep tStop rad tStart
                endVertex
{-# INLINE renderArcLine #-}


-- | Render an arc with a given thickness as a triangle strip
renderArcStrip
 :: Float -> Float -> Int -> Float -> Float -> Float -> Float -> IO ()
renderArcStrip (F# posX) (F# posY) steps r a1 a2 width
 = let  n               = fromIntegral steps
        tStep           = (2 * pi) / n

        t1              = normalizeAngle $ degToRad a1

        a2'             = normalizeAngle $ degToRad a2
        t2              = if a2' == 0 then 2*pi else a2'

        (tStart, tStop) = if t1 <= t2 then (t1, t2) else (t2, t1)
        tDiff           = tStop - tStart
        tMid            = tStart + tDiff / 2

        !(F# tStep')    = tStep
        !(F# tStep2')   = tStep / 2
        !(F# tStart')   = tStart
        !(F# tStop')    = tStop
        !(F# tCut')     = tStop - tStep
        !(F# tMid')     = tMid
        !(F# r1')       = r - width / 2
        !(F# r2')       = r + width / 2

   in   GL.renderPrimitive GL.TriangleStrip
         $ do   -- start vector
                addPointOnCircle posX posY r1' tStart'
                addPointOnCircle posX posY r2' tStart'

                -- If we don't have a complete step then just drop a point
                -- between the two ending lines.
                if tDiff < tStep
                  then do
                        addPointOnCircle posX posY r1' tMid'

                        -- end vectors
                        addPointOnCircle posX posY r2' tStop'
                        addPointOnCircle posX posY r1' tStop'

                  else do
                        renderCircleStrip_step posX posY
                                tStep' tCut' r1' tStart' r2'
                                (tStart' `plusFloat#` tStep2')

                        -- end vectors
                        addPointOnCircle posX posY r1' tStop'
                        addPointOnCircle posX posY r2' tStop'
{-# INLINE renderArcStrip #-}


-- Step functions -------------------------------------------------------------
renderCircleLine_step
        :: Float# -> Float#
        -> Float# -> Float#
        -> Float# -> Float#
        -> IO ()

renderCircleLine_step posX posY tStep tStop rad tt
        | 1# <- tt `geFloat#` tStop
        = return ()

        | otherwise
        = do    addPointOnCircle posX posY rad tt
                renderCircleLine_step posX posY tStep tStop rad
                        (tt `plusFloat#` tStep)
{-# INLINE renderCircleLine_step #-}


renderCircleStrip_step
        :: Float# -> Float#
        -> Float# -> Float#
        -> Float# -> Float#
        -> Float# -> Float# -> IO ()

renderCircleStrip_step posX posY tStep tStop r1 t1 r2 t2
        | 1# <- t1 `geFloat#` tStop
        = return ()

        | otherwise
        = do    addPointOnCircle posX posY r1 t1
                addPointOnCircle posX posY r2 t2
                renderCircleStrip_step posX posY tStep tStop r1
                        (t1 `plusFloat#` tStep) r2 (t2 `plusFloat#` tStep)
{-# INLINE renderCircleStrip_step #-}


addPoint :: Float# -> Float# -> IO ()
addPoint x y =
  GL.vertex $ GL.Vertex2 (gf (F# x)) (gf (F# y))
{-# INLINE addPoint #-}


addPointOnCircle :: Float# -> Float# -> Float# -> Float# -> IO ()
addPointOnCircle posX posY rad tt =
  addPoint
    (posX `plusFloat#` (rad `timesFloat#` (cosFloat# tt)))
    (posY `plusFloat#` (rad `timesFloat#` (sinFloat# tt)))
{-# INLINE addPointOnCircle #-}


-- | Convert degrees to radians
degToRad :: Float -> Float
degToRad d      = d * pi / 180
{-# INLINE degToRad #-}


-- | Normalise an angle to be between 0 and 2*pi radians
normalizeAngle :: Float -> Float
normalizeAngle f = f - 2 * pi * floor' (f / (2 * pi))
 where  floor' :: Float -> Float
        floor' x = fromIntegral (floor x :: Int)
{-# INLINE normalizeAngle #-}


{- Unused sector drawing code.
   Sectors are currently drawn as compound Pictures,
   but we might want this if we end up implementing the ThickSector
   version as well.

-- | Render a sector as a line.
renderSectorLine :: Float -> Float -> Int -> Float -> Float -> Float -> IO ()
renderSectorLine pX@(F# posX) pY@(F# posY) steps (F# rad) a1 a2
 = let  n               = fromIntegral steps
        !(F# tStep)     = (2 * pi) / n
        !(F# tStart)    = degToRad a1
        !(F# tStop)     = degToRad a2 + if a1 >= a2 then 2 * pi else 0

        -- need to set up the edges of the start/end triangles
        startVertex     = GL.vertex $ GL.Vertex2 (gf pX) (gf pY)
        endVertex       = addPointOnCircle posX posY rad tStop

   in   GL.renderPrimitive GL.LineLoop
         $ do   startVertex
                renderCircleLine_step posX posY tStep tStop rad tStart
                endVertex

-- | Render a sector.
renderSector :: Float -> Float -> Float -> Float -> Float -> Float -> IO ()
renderSector posX posY scaleFactor radius a1 a2
        | radScreen     <- scaleFactor * radius
        , steps         <- circleSteps (2 * radScreen)
        = renderSectorLine posX posY steps radius a1 a2
-}