{-|
Module      : Graphics.OscPacking.Examples
Description : Examples to study
Copyright   : (c) Christopher Howard, 2016
License     : GPL-3
Maintainer  : ch.howard@zoho.com

Please be aware that breaking changes to example functions will not be
represented as such for purposes of package versioning. Do not link to
example functions from production code.
-}

module Graphics.OscPacking.Examples where

import Graphics.Gloss.Data.Color (black)
import Graphics.OscPacking
import Prelude ((/), ($), Maybe(..), putStrLn, IO)

-- |Packs a rectangle with circles.
--
-- @
-- example1 :: IO()
-- example1 =
--   do putStrLn \"Packing. Please be patient.\"
--      displayWindow (800, 600) black $
--        buildPicture interpretation packing totalcircles
--   where packing = defaultPacking { boxWidth = 800.0,
--                                    boxHeight = 600.0,
--                                    seedX = 42,
--                                    seedY = 11,
--                                    boundary = Just (rectB (20, 20) 760 560),
--                                    startingCircles =
--                                      [Graphics.OscPacking.Circle
--                                        { position = (400, 300), radius = 10 }] }
--         totalcircles = 1500
--         interpretation = cycling 0.05 200
-- @
example1 :: IO()
example1 =
  do putStrLn "Packing. Please be patient."
     displayWindow (800, 600) black $
       buildPicture interpretation packing totalcircles
  where packing = defaultPacking { boxWidth = 800.0,
                                   boxHeight = 600.0,
                                   seedX = 42,
                                   seedY = 11,
                                   boundary = Just (rectB (20, 20) 760 560),
                                   startingCircles =
                                     [Graphics.OscPacking.Circle
                                       { position = (400, 300), radius = 10 }] }
        totalcircles = 1500
        interpretation = cycling 0.05 200

-- |Packs a circle with circles.
--
-- @
-- example2 :: IO()
-- example2 =
--   do putStrLn \"Packing. Please be patient.\"
--      displayWindow (800, 600) black $
--        buildPicture interpretation packing totalcircles
--   where packing = defaultPacking { boxWidth = 600.0,
--                                    boxHeight = 600.0,
--                                    seedX = 331,
--                                    seedY = 2010,
--                                    boundary = Just (circleB
--                                                     (600.0 \/ 2, 600.0 \/ 2) 250),
--                                    startingCircles =
--                                      [Graphics.OscPacking.Circle
--                                        { position = (300, 300), radius = 10 }] }
--         totalcircles = 1500
--         interpretation = colorful 270
-- @
example2 :: IO()
example2 =
  do putStrLn "Packing. Please be patient."
     displayWindow (800, 600) black $
       buildPicture interpretation packing totalcircles
  where packing = defaultPacking { boxWidth = 600.0,
                                   boxHeight = 600.0,
                                   seedX = 331,
                                   seedY = 2010,
                                   boundary = Just (circleB
                                                    (600.0 / 2, 600.0 / 2) 250),
                                   startingCircles =
                                     [Graphics.OscPacking.Circle
                                       { position = (300, 300), radius = 10 }] }
        totalcircles = 1500
        interpretation = colorful 270