-- |
-- Module: Graphics.Chalkboard.Shapes
-- Copyright: (c) 2009 Andy Gill
-- License: BSD3
--
-- Maintainer: Andy Gill <andygill@ku.edu>
-- Stability: unstable
-- Portability: ghc
--
-- This module contains some basic shape generators, expressed as @Board Bool@.
--

module Graphics.Chalkboard.Shapes where

import Graphics.Chalkboard.Board
import Graphics.Chalkboard.Utils
import Graphics.Chalkboard.Types

import Control.Applicative

-- | unit circle, radius 0.5, over origin.
circle :: Board Bool
circle =  (\ (x,y) -> x*x + y*y <= 0.5 * 0.5) <$> coord

-- | unit vertical bar,  1 wide over origin.
vbar :: Board Bool
vbar =  (\ (_x,y) -> y <= 0.5 && y >= -0.5) <$> coord

-- | unit horizontal bar, 1 high over origin.
hbar :: Board Bool
hbar =  (\ (x,_y) -> x <= 0.5 && x >= -0.5) <$> coord

-- | unit square, 1x1 over origin.
square :: Board Bool
square = liftA2 (&&) vbar hbar

-- | cheacker board, with squares 1x1.
checker :: Board Bool
checker = (\ (x,y) -> even ((floor x + floor y) :: Int)) <$> coord

-- | Given two @Point@s, and a thickness, draw a line between the points.
-- line :: Line -> Double -> Board Bool

straightline :: (Point,Point) -> R -> Board Bool
straightline ((x1,y1),(x2,y2)) width = (\ (x,y) ->
---	distance (x1,y1) (x,y) <= width ||
--	distance (x2,y2) (x,y) <= width ||
	(  let 	u = intervalOnLine ((x1,y1),(x2,y2))  (x,y)
	   in u >= 0 
	   && u <= 1 
	   && distance (lerp (x1,y1) (x2,y2) u) (x,y) <= width
	)) <$> coord

-- | A line generated by sampling a function from @R@ to @Point@s,
-- with a specific width. There needs to be at least 2 sample points.

functionline :: (R -> Point) -> R -> Int -> Board Bool
functionline line width steps = stack
		 [ straightline (p1,p2) width
		| (p1,p2) <- zip samples (tail samples)
		] `over` stack
		[ dotAt p | p <- tail (init samples) ]
    where
	samples = map line (outerSteps steps)
	dotAt p = move p $ scale (width * 2) circle

-- | arrowhead is a triangle, pointing straight up, height 1, width 1, with the (0,0) at the center of the base.
arrowhead :: Point -> Radian -> R -> Board Bool
arrowhead p rad sz = move p $ rotate rad $ scale sz $ (\ (x,y) -> y >= 0 && y <= 1 && abs x * 2 <= 1 - y) <$> coord