module Graphics.Gloss.Data.Picture
        ( Picture       (..)
        , Point, Vector, Path

        -- * Aliases for Picture constructors
        , blank
        , polygon
        , line
        , circle, thickCircle
        , arc,    thickArc
        , text
        , bitmap
        , bitmapSection
        -- , bitmap
        , color
        , translate, rotate, scale
        , pictures

        -- * Compound shapes
        , lineLoop
        , circleSolid
        , arcSolid
        , sectorWire
        , rectanglePath
        , rectangleWire
        , rectangleSolid
        , rectangleUpperPath
        , rectangleUpperWire
        , rectangleUpperSolid)
where
import Graphics.Gloss.Rendering
import Graphics.Gloss.Geometry.Angle


-- Constructors ----------------------------------------------------------------
-- NOTE: The docs here should be identical to the ones on the constructors.

-- | A blank picture, with nothing in it.
blank :: Picture
blank :: Picture
blank   = Picture
Blank

-- | A convex polygon filled with a solid color.
polygon :: Path -> Picture
polygon :: Path -> Picture
polygon = Path -> Picture
Polygon

-- | A line along an arbitrary path.
line :: Path -> Picture
line :: Path -> Picture
line    = Path -> Picture
Line

-- | A circle with the given radius.
circle  :: Float  -> Picture
circle :: Float -> Picture
circle  = Float -> Picture
Circle

-- | A circle with the given thickness and radius.
--   If the thickness is 0 then this is equivalent to `Circle`.
thickCircle  :: Float -> Float -> Picture
thickCircle :: Float -> Float -> Picture
thickCircle = Float -> Float -> Picture
ThickCircle

-- | A circular arc drawn counter-clockwise between two angles (in degrees)
--   at the given radius.
arc     :: Float -> Float -> Float -> Picture
arc :: Float -> Float -> Float -> Picture
arc = Float -> Float -> Float -> Picture
Arc

-- | A circular arc drawn counter-clockwise between two angles (in degrees),
--   with the given radius  and thickness.
--   If the thickness is 0 then this is equivalent to `Arc`.
thickArc :: Float -> Float -> Float -> Float -> Picture
thickArc :: Float -> Float -> Float -> Float -> Picture
thickArc = Float -> Float -> Float -> Float -> Picture
ThickArc

-- | Some text to draw with a vector font.
text :: String -> Picture
text :: String -> Picture
text = String -> Picture
Text

-- | A bitmap image
bitmap  :: BitmapData -> Picture
bitmap :: BitmapData -> Picture
bitmap BitmapData
bitmapData = BitmapData -> Picture
Bitmap BitmapData
bitmapData

-- | a subsection of a bitmap image
--   first argument selects a sub section in the bitmap
--   second argument determines the bitmap data
bitmapSection  :: Rectangle -> BitmapData -> Picture
bitmapSection :: Rectangle -> BitmapData -> Picture
bitmapSection = Rectangle -> BitmapData -> Picture
BitmapSection

-- | A picture drawn with this color.
color :: Color -> Picture -> Picture
color :: Color -> Picture -> Picture
color = Color -> Picture -> Picture
Color

-- | A picture translated by the given x and y coordinates.
translate :: Float -> Float -> Picture -> Picture
translate :: Float -> Float -> Picture -> Picture
translate = Float -> Float -> Picture -> Picture
Translate

-- | A picture rotated clockwise by the given angle (in degrees).
rotate  :: Float -> Picture -> Picture
rotate :: Float -> Picture -> Picture
rotate = Float -> Picture -> Picture
Rotate

-- | A picture scaled by the given x and y factors.
scale   :: Float -> Float -> Picture -> Picture
scale :: Float -> Float -> Picture -> Picture
scale = Float -> Float -> Picture -> Picture
Scale

-- | A picture consisting of several others.
pictures :: [Picture] -> Picture
pictures :: [Picture] -> Picture
pictures = [Picture] -> Picture
Pictures


-- Other Shapes ---------------------------------------------------------------
-- | A closed loop along a path.
lineLoop :: Path -> Picture
lineLoop :: Path -> Picture
lineLoop []     = Path -> Picture
Line []
lineLoop (Point
x:Path
xs) = Path -> Picture
Line ((Point
xPoint -> Path -> Path
forall a. a -> [a] -> [a]
:Path
xs) Path -> Path -> Path
forall a. [a] -> [a] -> [a]
++ [Point
x])


-- Circles and Arcs -----------------------------------------------------------
-- | A solid circle with the given radius.
circleSolid :: Float -> Picture
circleSolid :: Float -> Picture
circleSolid Float
r
        = Float -> Float -> Picture
thickCircle (Float
rFloat -> Float -> Float
forall a. Fractional a => a -> a -> a
/Float
2) Float
r


-- | A solid arc, drawn counter-clockwise between two angles at the given radius.
arcSolid  :: Float -> Float -> Float -> Picture
arcSolid :: Float -> Float -> Float -> Picture
arcSolid Float
a1 Float
a2 Float
r
        = Float -> Float -> Float -> Float -> Picture
thickArc Float
a1 Float
a2 (Float
rFloat -> Float -> Float
forall a. Fractional a => a -> a -> a
/Float
2) Float
r


-- | A wireframe sector of a circle.
--   An arc is draw counter-clockwise from the first to the second angle at
--   the given radius. Lines are drawn from the origin to the ends of the arc.
---
--   NOTE: We take the absolute value of the radius incase it's negative.
--   It would also make sense to draw the sector flipped around the
--   origin, but I think taking the absolute value will be less surprising
--   for the user.
--
sectorWire :: Float -> Float -> Float -> Picture
sectorWire :: Float -> Float -> Float -> Picture
sectorWire Float
a1 Float
a2 Float
r_
 = let r :: Float
r        = Float -> Float
forall a. Num a => a -> a
abs Float
r_
   in  [Picture] -> Picture
Pictures
        [ Float -> Float -> Float -> Picture
Arc Float
a1 Float
a2 Float
r
        , Path -> Picture
Line [(Float
0, Float
0), (Float
r Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float
forall a. Floating a => a -> a
cos (Float -> Float
degToRad Float
a1), Float
r Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float
forall a. Floating a => a -> a
sin (Float -> Float
degToRad Float
a1))]
        , Path -> Picture
Line [(Float
0, Float
0), (Float
r Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float
forall a. Floating a => a -> a
cos (Float -> Float
degToRad Float
a2), Float
r Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float
forall a. Floating a => a -> a
sin (Float -> Float
degToRad Float
a2))] ]


-- Rectangles -----------------------------------------------------------------
-- NOTE: Only the first of these rectangle functions has haddocks on the
--       arguments to reduce the amount of noise in the extracted docs.

-- | A path representing a rectangle centered about the origin
rectanglePath
        :: Float        -- ^ width of rectangle
        -> Float        -- ^ height of rectangle
        -> Path
rectanglePath :: Float -> Float -> Path
rectanglePath Float
sizeX Float
sizeY
 = let  sx :: Float
sx      = Float
sizeX Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
2
        sy :: Float
sy      = Float
sizeY Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
2
   in   [(-Float
sx, -Float
sy), (-Float
sx, Float
sy), (Float
sx, Float
sy), (Float
sx, -Float
sy)]


-- | A wireframe rectangle centered about the origin.
rectangleWire :: Float -> Float -> Picture
rectangleWire :: Float -> Float -> Picture
rectangleWire Float
sizeX Float
sizeY
        = Path -> Picture
lineLoop (Path -> Picture) -> Path -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Path
rectanglePath Float
sizeX Float
sizeY


-- | A wireframe rectangle in the y > 0 half of the x-y plane.
rectangleUpperWire :: Float -> Float -> Picture
rectangleUpperWire :: Float -> Float -> Picture
rectangleUpperWire Float
sizeX Float
sizeY
        = Path -> Picture
lineLoop (Path -> Picture) -> Path -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Path
rectangleUpperPath Float
sizeX Float
sizeY


-- | A path representing a rectangle in the y > 0 half of the x-y plane.
rectangleUpperPath :: Float -> Float -> Path
rectangleUpperPath :: Float -> Float -> Path
rectangleUpperPath Float
sizeX Float
sy
 = let  sx :: Float
sx      = Float
sizeX Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
2
   in   [(-Float
sx, Float
0), (-Float
sx, Float
sy), (Float
sx, Float
sy), (Float
sx, Float
0)]


-- | A solid rectangle centered about the origin.
rectangleSolid :: Float -> Float -> Picture
rectangleSolid :: Float -> Float -> Picture
rectangleSolid Float
sizeX Float
sizeY
        = Path -> Picture
Polygon (Path -> Picture) -> Path -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Path
rectanglePath Float
sizeX Float
sizeY


-- | A solid rectangle in the y > 0 half of the x-y plane.
rectangleUpperSolid :: Float -> Float -> Picture
rectangleUpperSolid :: Float -> Float -> Picture
rectangleUpperSolid Float
sizeX Float
sizeY
        = Path -> Picture
Polygon  (Path -> Picture) -> Path -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Path
rectangleUpperPath Float
sizeX Float
sizeY