{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE BangPatterns #-}
{-|
Module      : Graphics.WorldTurtle.Commands
Description : The commands used 
Copyright   : (c) Archibald Neil MacDonald, 2020
License     : BSD3
Maintainer  : archibaldnmac@gmail.com
Stability   : experimental
Portability : POSIX

This module contains all commands used to create, move and 
manipulate a turtle.

-}
module Graphics.WorldTurtle.Commands
  (
  -- * Types

    Turtle
  , P.Point
  -- * WorldCommand commands.

  -- ** Creating a turtle.

  , makeTurtle
  , makeTurtle'
  -- ** Canvas commands.

  , clear
  , sleep
  -- * TurtleCommand commands.

  -- ** Movement commands.

  , forward
  , fd
  , backward
  , bk
  , left
  , lt
  , right
  , rt
  , Graphics.WorldTurtle.Commands.circle
  , Graphics.WorldTurtle.Commands.arc
  , goto
  , setPosition
  , home
  , setHeading
  , setSpeed
  , setRotationSpeed
  -- * Styling commands.

  , stamp
  , representation
  -- ** Query turtle's state.

  , position
  , heading
  , speed
  , rotationSpeed
  , penColor
  , penDown
  , penSize
  , visible
  -- ** Mutate turtle's state.

  , branch
  , setPenColor
  , setPenDown
  , setPenSize
  , setRepresentation
  , setVisible
  -- * Common constants

  , east
  , north
  , west
  , south
  ) where

import Data.Maybe (fromMaybe)

import Control.Lens
import Control.Monad

import Graphics.WorldTurtle.Shapes

import Graphics.WorldTurtle.Internal.Commands
import Graphics.WorldTurtle.Internal.Sequence

import qualified Graphics.WorldTurtle.Internal.Turtle as T
import qualified Graphics.WorldTurtle.Internal.Coords as P

import Graphics.Gloss.Data.Color (Color, black)

import Graphics.Gloss.Data.Picture

{- |
Creates a new `Turtle` and displays it on the canvas. This turtle can then be
manipulated! For example, to create a turtle and then move the turtle forward:

   
  >  main:: IO ()
  >  main = runWorld $ do
  >    t <- makeTurtle
  >    t >/> forward 90

The default turtle starts at position @(0, 0)@ and is orientated `north`.

-}
makeTurtle :: WorldCommand Turtle
makeTurtle :: WorldCommand Turtle
makeTurtle = SequenceCommand Turtle -> WorldCommand Turtle
forall a. SequenceCommand a -> WorldCommand a
WorldCommand SequenceCommand Turtle
generateTurtle

{-| This variant of `makeTurtle` takes a starting position, a starting 
    orientation, and a color to apply to the turtle and the turtle's pen.

    
    >  myCommand :: WorldCommand ()
    >  myCommand = do
    >    t1 <- makeTurtle' (0, 0)  0 green
    >    t2 <- makeTurtle' (0, 0) 90 red
    >    (t1 >/> forward 90) \<|\> (t2 >/> forward 90)

    See `makeTurtle`.
-}
makeTurtle' :: Point -- ^ Initial position of the turtle.

            -> Float -- ^ Initial heading of the turtle.

            -> Color -- ^ Color of the turtle and the turtle's pen.

            -> WorldCommand Turtle -- ^ The generated turtle.

makeTurtle' :: Point -> Float -> Color -> WorldCommand Turtle
makeTurtle' Point
p Float
f Color
c = SequenceCommand Turtle -> WorldCommand Turtle
forall a. SequenceCommand a -> WorldCommand a
WorldCommand (SequenceCommand Turtle -> WorldCommand Turtle)
-> SequenceCommand Turtle -> WorldCommand Turtle
forall a b. (a -> b) -> a -> b
$ do 
  Turtle
turtle <- SequenceCommand Turtle
generateTurtle
  let ts :: (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts = Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
turtle
  (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Point -> Identity Point) -> TurtleData -> Identity TurtleData)
-> (Point -> Identity Point)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point -> Identity Point) -> TurtleData -> Identity TurtleData
Lens' TurtleData Point
T.position       ((Point -> Identity Point) -> TSC -> Identity TSC)
-> Point -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Point
p
  (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Float -> Identity Float) -> TurtleData -> Identity TurtleData)
-> (Float -> Identity Float)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Float -> Identity Float) -> TurtleData -> Identity TurtleData
Lens' TurtleData Float
T.heading        ((Float -> Identity Float) -> TSC -> Identity TSC)
-> Float -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Float
f
  (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Picture -> Identity Picture)
    -> TurtleData -> Identity TurtleData)
-> (Picture -> Identity Picture)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Picture -> Identity Picture) -> TurtleData -> Identity TurtleData
Lens' TurtleData Picture
T.representation ((Picture -> Identity Picture) -> TSC -> Identity TSC)
-> Picture -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Color -> Color -> Picture
turtleArrow Color
black Color
c
  (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Color -> Identity Color) -> TurtleData -> Identity TurtleData)
-> (Color -> Identity Color)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Color -> Identity Color) -> TurtleData -> Identity TurtleData
Lens' TurtleData Color
T.penColor       ((Color -> Identity Color) -> TSC -> Identity TSC)
-> Color -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Color
c
  Turtle -> SequenceCommand Turtle
forall (m :: * -> *) a. Monad m => a -> m a
return Turtle
turtle

-- | Move the turtle backward by the specified @distance@, in the direction the 

--   turtle is headed.

backward :: Float -- ^ Distance to move the turtle.

         -> TurtleCommand ()
backward :: Float -> TurtleCommand ()
backward Float
d = Float -> TurtleCommand ()
forward (-Float
d)

-- | Shorthand for `backward`.

bk :: Float -> TurtleCommand ()
bk :: Float -> TurtleCommand ()
bk = Float -> TurtleCommand ()
backward

calculateNewPointF_ :: P.Point -- ^ Starting point

                    -> Float -- ^ Distance

                    -> Float -- ^ Heading in degrees.

                    -> Float -- ^ coefficient [0, 1]

                    -> P.Point
calculateNewPointF_ :: Point -> Float -> Float -> Float -> Point
calculateNewPointF_ !Point
p !Float
d !Float
h !Float
q = let !vec :: Point
vec = Float -> Point -> Point
P.rotateV (Float -> Float
P.degToRad Float
h) (Float
d, Float
0)
                                      !endP :: Point
endP = Point
vec Point -> Point -> Point
P.+ Point
p
                                   in Float -> Point -> Point -> Point
P.lerp Float
q Point
p Point
endP

-- | Move the turtle forward by the specified @distance@, in the direction the 

--   turtle is headed.

forward :: Float -- ^ Distance to move the turtle.

        -> TurtleCommand ()
forward :: Float -> TurtleCommand ()
forward !Float
d = (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> MaybeT TurtleState ()) -> TurtleCommand ())
-> (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a b. (a -> b) -> a -> b
$ \ Turtle
turtle -> do
    !TurtleData
t <- Turtle -> SequenceCommand TurtleData
tData_ Turtle
turtle
    --  Get origin point

    Float
-> Float
-> (Float -> MaybeT TurtleState ())
-> MaybeT TurtleState ()
forall a.
Float -> Float -> (Float -> SequenceCommand a) -> SequenceCommand a
animate' Float
d (TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.speed) ((Float -> MaybeT TurtleState ()) -> MaybeT TurtleState ())
-> (Float -> MaybeT TurtleState ()) -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ \ Float
q -> do
      --  Get new endpoint via percentage

      let !startP :: Point
startP = TurtleData
t TurtleData -> Getting Point TurtleData Point -> Point
forall s a. s -> Getting a s a -> a
^. Getting Point TurtleData Point
Lens' TurtleData Point
T.position
      let !midP :: Point
midP = Point -> Float -> Float -> Float -> Point
calculateNewPointF_ Point
startP Float
d (TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.heading) Float
q
       -- don't draw if pen isn't in down state

      Bool -> MaybeT TurtleState () -> MaybeT TurtleState ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (TurtleData
t TurtleData -> Getting Bool TurtleData Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool TurtleData Bool
Lens' TurtleData Bool
T.penDown) (MaybeT TurtleState () -> MaybeT TurtleState ())
-> MaybeT TurtleState () -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$
        Picture -> MaybeT TurtleState ()
addPicture (Picture -> MaybeT TurtleState ())
-> Picture -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ Color -> Picture -> Picture
color (TurtleData
t TurtleData -> Getting Color TurtleData Color -> Color
forall s a. s -> Getting a s a -> a
^. Getting Color TurtleData Color
Lens' TurtleData Color
T.penColor) 
                   (Picture -> Picture) -> Picture -> Picture
forall a b. (a -> b) -> a -> b
$ Point -> Point -> Float -> Picture
thickLine Point
startP Point
midP (TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.penSize)
        --  Draw line from startPoint to midPoint.

      Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
turtle ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Point -> Identity Point) -> TurtleData -> Identity TurtleData)
-> (Point -> Identity Point)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point -> Identity Point) -> TurtleData -> Identity TurtleData
Lens' TurtleData Point
T.position ((Point -> Identity Point) -> TSC -> Identity TSC)
-> Point -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Point
midP
      --  Update the turtle to a new position


-- | Shorthand for `forward`.

fd :: Float -> TurtleCommand ()
fd :: Float -> TurtleCommand ()
fd = Float -> TurtleCommand ()
forward

-- | Stamp a copy of the turtle shape onto the canvas at the current turtle 

--   position.

stamp :: TurtleCommand ()
stamp :: TurtleCommand ()
stamp = (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> MaybeT TurtleState ()) -> TurtleCommand ())
-> (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a b. (a -> b) -> a -> b
$ Turtle -> SequenceCommand TurtleData
tData_ (Turtle -> SequenceCommand TurtleData)
-> (TurtleData -> MaybeT TurtleState ())
-> Turtle
-> MaybeT TurtleState ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (Picture -> MaybeT TurtleState ()
addPicture (Picture -> MaybeT TurtleState ())
-> (TurtleData -> Picture) -> TurtleData -> MaybeT TurtleState ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TurtleData -> Picture
T.drawTurtle)

-- | Turn a turtle right by the given degrees amount.

right :: Float -- ^ Rotation amount to apply to turtle.

      -> TurtleCommand ()
right :: Float -> TurtleCommand ()
right = Bool -> Float -> TurtleCommand ()
rotateTo_ Bool
True

-- | Shorthand for `right`.

rt :: Float -> TurtleCommand ()
rt :: Float -> TurtleCommand ()
rt = Float -> TurtleCommand ()
right

-- | Turn a turtle left by the given degrees amount.

left :: Float -- ^ Rotation amount to apply to turtle.

     -> TurtleCommand ()
left :: Float -> TurtleCommand ()
left = Bool -> Float -> TurtleCommand ()
rotateTo_ Bool
False

-- | Shorthand for `left`.

lt :: Float -> TurtleCommand ()
lt :: Float -> TurtleCommand ()
lt = Float -> TurtleCommand ()
left

rotateTo_ :: Bool -- ^ Bias decides in which direction rotation happens.

          -> Float -- ^ Amount to rotate by

          -> TurtleCommand ()
rotateTo_ :: Bool -> Float -> TurtleCommand ()
rotateTo_  !Bool
rightBias !Float
r = (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> MaybeT TurtleState ()) -> TurtleCommand ())
-> (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a b. (a -> b) -> a -> b
$ \ Turtle
turtle -> do
    !TurtleData
t <- Turtle -> SequenceCommand TurtleData
tData_ Turtle
turtle
    let !r' :: Float
r' = Float -> Float
P.normalizeHeading Float
r
    Float
-> Float
-> (Float -> MaybeT TurtleState ())
-> MaybeT TurtleState ()
forall a.
Float -> Float -> (Float -> SequenceCommand a) -> SequenceCommand a
animate' (Float -> Float
P.degToRad Float
r') (TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.rotationSpeed) ((Float -> MaybeT TurtleState ()) -> MaybeT TurtleState ())
-> (Float -> MaybeT TurtleState ()) -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ \Float
q -> do
      let h :: Float
h = TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.heading
      let newHeading :: Float
newHeading = Float -> Float
P.normalizeHeading (Float -> Float) -> Float -> Float
forall a b. (a -> b) -> a -> b
$ if Bool
rightBias then Float
h Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
q Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
r'
                                                          else Float
h Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
q Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
r'
      --  Get new heading via percentage

      Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
turtle ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Float -> Identity Float) -> TurtleData -> Identity TurtleData)
-> (Float -> Identity Float)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Float -> Identity Float) -> TurtleData -> Identity TurtleData
Lens' TurtleData Float
T.heading ((Float -> Identity Float) -> TSC -> Identity TSC)
-> Float -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Float
newHeading

-- | Draw a circle with a given @radius@. The center is @radius@ units left of 

--   the @turtle@ if positive. Otherwise  @radius@ units right of the @turtle@ 

--   if negative.

--

--   The circle is drawn in an anticlockwise direction if the radius is 

--   positive, otherwise, it is drawn in a clockwise direction.

--

--   Circle is an alias for @circle r = arc r 360@.

circle :: Float -- ^ Radius of the circle.

       -> TurtleCommand ()
circle :: Float -> TurtleCommand ()
circle Float
radius = Float -> Float -> TurtleCommand ()
Graphics.WorldTurtle.Commands.arc Float
radius Float
360

-- | Draws an arc starting from a given starting point on the edge of the

--   circle.

drawCircle_ :: P.Point -- ^ Point on edge of circle to start from

            -> Float -- ^ Radius of circle

            -> Float -- ^ Absolute starting angle in degrees

            -> Float -- ^ Rotation amount about radius in degrees

            -> Float -- ^ Line thickness (penSize)

            -> Color -- ^ Color of circle 

            -> Picture -- ^ Resulting circle

drawCircle_ :: Point -> Float -> Float -> Float -> Float -> Color -> Picture
drawCircle_ !Point
p !Float
radius !Float
startAngle !Float
endAngle !Float
pSize !Color
pColor = 
 (Float -> Float -> Picture -> Picture)
-> Point -> Picture -> Picture
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Float -> Float -> Picture -> Picture
translate Point
p (Picture -> Picture) -> Picture -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Picture -> Picture
rotate (Float
180 Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
startAngle)
                     (Picture -> Picture) -> Picture -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Picture -> Picture
translate (-Float
radius) Float
0
                     (Picture -> Picture) -> Picture -> Picture
forall a b. (a -> b) -> a -> b
$ Color -> Picture -> Picture
color Color
pColor
                     (Picture -> Picture) -> Picture -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Picture -> Picture
scale (if Float
radius Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0 then Float
1 else -Float
1) Float
1
                     (Picture -> Picture) -> Picture -> Picture
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float -> Float -> Picture
thickArc Float
0 Float
endAngle (Float -> Float
forall a. Num a => a -> a
abs Float
radius) Float
pSize

-- Calculates the next position of a turtle on a circle.

calculateNewPointC_ :: P.Point -- ^ Point on edge of circle

                    -> Float -- ^ Radius of circle

                    -> Float -- ^ Absolute starting angle in degrees

                    -> Float -- ^ Rotation amount about radius in degrees

                    -> P.Point -- ^ Resulting new point

calculateNewPointC_ :: Point -> Float -> Float -> Float -> Point
calculateNewPointC_ !Point
p !Float
radius !Float
startAngle !Float
angle = 
  let !px :: Float
px = Point -> Float
forall a b. (a, b) -> a
fst Point
p Float -> Float -> Float
forall a. Num a => a -> a -> a
- (Float
radius Float -> Float -> Float
forall a. Num a => a -> a -> a
* (Float -> Float
forall a. Floating a => a -> a
cos Float
a Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float -> Float
forall a. Floating a => a -> a
cos Float
s))
      !py :: Float
py = Point -> Float
forall a b. (a, b) -> b
snd Point
p Float -> Float -> Float
forall a. Num a => a -> a -> a
- (Float
radius Float -> Float -> Float
forall a. Num a => a -> a -> a
* (Float -> Float
forall a. Floating a => a -> a
sin Float
a Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float -> Float
forall a. Floating a => a -> a
sin Float
s))
      !s :: Float
s = Float -> Float
P.degToRad Float
startAngle
      !a :: Float
a = Float -> Float
P.degToRad (Float -> Float) -> Float -> Float
forall a b. (a -> b) -> a -> b
$ if Float
radius Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0 then Float
startAngle Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
angle
                                       else Float
startAngle Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
angle
   in (Float
px, Float
py)

-- | Draw an arc with a given @radius@. The center is @radius@ units left of the

--   @turtle@ if positive. Otherwise  @radius@ units right of the @turtle@ if 

--   negative.

--

--   The arc is drawn in an anticlockwise direction if the radius is positive,

--   otherwise, it is drawn in a clockwise direction.

arc  :: Float -- ^ Radius of the circle.

     -> Float -- ^ Angle to travel in degrees. 

              -- For example: @360@ for a full circle or @180@ for a 

              -- semicircle.

     -> TurtleCommand ()
arc :: Float -> Float -> TurtleCommand ()
arc !Float
radius !Float
r = (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> MaybeT TurtleState ()) -> TurtleCommand ())
-> (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a b. (a -> b) -> a -> b
$ \Turtle
turtle -> do
  !TurtleData
t <- Turtle -> SequenceCommand TurtleData
tData_ Turtle
turtle
  let !r' :: Float
r' = Float -> Float
P.normalizeHeading Float
r
  Float
-> Float
-> (Float -> MaybeT TurtleState ())
-> MaybeT TurtleState ()
forall a.
Float -> Float -> (Float -> SequenceCommand a) -> SequenceCommand a
animate' (Float -> Float
forall a. Num a => a -> a
abs Float
radius Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float
P.degToRad Float
r') (TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.speed) ((Float -> MaybeT TurtleState ()) -> MaybeT TurtleState ())
-> (Float -> MaybeT TurtleState ()) -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ \ Float
q -> do
    let !startAngle :: Float
startAngle = TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.heading Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
90
    let !p :: Point
p = TurtleData
t TurtleData -> Getting Point TurtleData Point -> Point
forall s a. s -> Getting a s a -> a
^. Getting Point TurtleData Point
Lens' TurtleData Point
T.position
    let !angle :: Float
angle = Float
r' Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
q
    -- don't draw if pen isn't in down state

    Bool -> MaybeT TurtleState () -> MaybeT TurtleState ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (TurtleData
t TurtleData -> Getting Bool TurtleData Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool TurtleData Bool
Lens' TurtleData Bool
T.penDown) (MaybeT TurtleState () -> MaybeT TurtleState ())
-> MaybeT TurtleState () -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ 
      Picture -> MaybeT TurtleState ()
addPicture (Picture -> MaybeT TurtleState ())
-> Picture -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ Point -> Float -> Float -> Float -> Float -> Color -> Picture
drawCircle_ Point
p Float
radius Float
startAngle Float
angle 
                               (TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.penSize) (TurtleData
t TurtleData -> Getting Color TurtleData Color -> Color
forall s a. s -> Getting a s a -> a
^. Getting Color TurtleData Color
Lens' TurtleData Color
T.penColor)

    -- Update the turtle with the new values.

    let ts :: (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts = Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
turtle
    (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Float -> Identity Float) -> TurtleData -> Identity TurtleData)
-> (Float -> Identity Float)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Float -> Identity Float) -> TurtleData -> Identity TurtleData
Lens' TurtleData Float
T.heading ((Float -> Identity Float) -> TSC -> Identity TSC)
-> Float -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Float -> Float
P.normalizeHeading (if Float
radius Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0
                                          then Float
startAngle Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
90 Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
angle
                                          else Float
startAngle Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
90 Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
angle)

    let !p' :: Point
p' = Point -> Float -> Float -> Float -> Point
calculateNewPointC_ Point
p Float
radius Float
startAngle Float
angle
    (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Point -> Identity Point) -> TurtleData -> Identity TurtleData)
-> (Point -> Identity Point)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point -> Identity Point) -> TurtleData -> Identity TurtleData
Lens' TurtleData Point
T.position ((Point -> Identity Point) -> TSC -> Identity TSC)
-> Point -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Point
p'

-- | Returns the turtle's current position.

--   Default (starting) position is @(0, 0)@.

position :: TurtleCommand P.Point -- ^ Returned current point.

position :: TurtleCommand Point
position = Point -> Lens' TurtleData Point -> TurtleCommand Point
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ (Float
0, Float
0) Lens' TurtleData Point
T.position

-- | Warps the turtle to its starting position @(0, 0)@ and resets the

--   orientation to `north` (@90@ degrees). No line is drawn moving the turtle.

home :: TurtleCommand ()
home :: TurtleCommand ()
home = (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> MaybeT TurtleState ()) -> TurtleCommand ())
-> (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a b. (a -> b) -> a -> b
$ \ Turtle
turtle -> do
  let ts :: (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts = Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
turtle
  (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Point -> Identity Point) -> TurtleData -> Identity TurtleData)
-> (Point -> Identity Point)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point -> Identity Point) -> TurtleData -> Identity TurtleData
Lens' TurtleData Point
T.position       ((Point -> Identity Point) -> TSC -> Identity TSC)
-> Point -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= (Float
0, Float
0)
  (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
ts ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Float -> Identity Float) -> TurtleData -> Identity TurtleData)
-> (Float -> Identity Float)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Float -> Identity Float) -> TurtleData -> Identity TurtleData
Lens' TurtleData Float
T.heading        ((Float -> Identity Float) -> TSC -> Identity TSC)
-> Float -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Float
90

-- | Warps the turtle to a new position.

--   The turtle jumps to this new position with no animation. If the pen is down

--   then a line is drawn.

--   

--   This does not affect the turtle's heading.

goto :: P.Point -- ^ Position to warp to.

     -> TurtleCommand ()
goto :: Point -> TurtleCommand ()
goto Point
point = (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> MaybeT TurtleState ()) -> TurtleCommand ())
-> (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a b. (a -> b) -> a -> b
$ \ Turtle
turtle -> do
  !TurtleData
t <- Turtle -> SequenceCommand TurtleData
tData_ Turtle
turtle
  let !startP :: Point
startP = TurtleData
t TurtleData -> Getting Point TurtleData Point -> Point
forall s a. s -> Getting a s a -> a
^. Getting Point TurtleData Point
Lens' TurtleData Point
T.position
  Bool -> MaybeT TurtleState () -> MaybeT TurtleState ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (TurtleData
t TurtleData -> Getting Bool TurtleData Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool TurtleData Bool
Lens' TurtleData Bool
T.penDown) (MaybeT TurtleState () -> MaybeT TurtleState ())
-> MaybeT TurtleState () -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ Picture -> MaybeT TurtleState ()
addPicture 
                        (Picture -> MaybeT TurtleState ())
-> Picture -> MaybeT TurtleState ()
forall a b. (a -> b) -> a -> b
$ Color -> Picture -> Picture
color (TurtleData
t TurtleData -> Getting Color TurtleData Color -> Color
forall s a. s -> Getting a s a -> a
^. Getting Color TurtleData Color
Lens' TurtleData Color
T.penColor) 
                        (Picture -> Picture) -> Picture -> Picture
forall a b. (a -> b) -> a -> b
$ Point -> Point -> Float -> Picture
thickLine Point
startP Point
point (TurtleData
t TurtleData -> Getting Float TurtleData Float -> Float
forall s a. s -> Getting a s a -> a
^. Getting Float TurtleData Float
Lens' TurtleData Float
T.penSize)
  Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
turtle ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((Point -> Identity Point) -> TurtleData -> Identity TurtleData)
-> (Point -> Identity Point)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point -> Identity Point) -> TurtleData -> Identity TurtleData
Lens' TurtleData Point
T.position ((Point -> Identity Point) -> TSC -> Identity TSC)
-> Point -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Point
point

-- | Alias of `goto`.

setPosition :: P.Point -> TurtleCommand ()
setPosition :: Point -> TurtleCommand ()
setPosition = Point -> TurtleCommand ()
goto

-- | Returns the turtle's heading.

--   

--   @0@ is along the positive x-axis, going anticlockwise. So:

--

--   * East is @0@ degrees.

--   * North is @90@ degrees.

--   * West is @180@ degrees.

--   * South is @270@ degrees.

--

--   The default heading is North (@90@ degrees).

heading :: TurtleCommand Float -- ^ Returned heading as angle in degrees.

heading :: TurtleCommand Float
heading = Float -> Lens' TurtleData Float -> TurtleCommand Float
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Float
0 Lens' TurtleData Float
T.heading

-- | Sets the turtle's heading. See `heading`.

setHeading :: Float -- ^ Heading to apply. 

           -> TurtleCommand ()
setHeading :: Float -> TurtleCommand ()
setHeading = Lens' TurtleData Float -> Float -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Float
T.heading

-- | Returns the turtle's pen color.

--   The color of the turtle's pen.The default color is @black@.

penColor :: TurtleCommand Color -- ^ Returned current pen color.

penColor :: TurtleCommand Color
penColor = Color -> Lens' TurtleData Color -> TurtleCommand Color
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Color
black Lens' TurtleData Color
T.penColor

-- | Set the turtle's pen color.

--  See `penColor`.

setPenColor :: Color -- ^ New pen color to apply

            -> TurtleCommand ()
setPenColor :: Color -> TurtleCommand ()
setPenColor = Lens' TurtleData Color -> Color -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Color
T.penColor

-- | Returns whether the turtle's pen is down.

--   When the turtle's pen is down it will draw a line when it moves.

--   The default value is @True@.

penDown :: TurtleCommand Bool -- ^ True if pen is down, false if not.

penDown :: TurtleCommand Bool
penDown = Bool -> Lens' TurtleData Bool -> TurtleCommand Bool
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Bool
False Lens' TurtleData Bool
T.penDown

-- | Sets the turtle's pen to down or up.

--   See `penDown`.

setPenDown :: Bool -- ^ New state for pen flag. True for down. False for up.

           -> TurtleCommand ()
setPenDown :: Bool -> TurtleCommand ()
setPenDown = Lens' TurtleData Bool -> Bool -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Bool
T.penDown

-- | Returns the turtle's pen size.

--   Defaults to @2@.

penSize :: TurtleCommand Float -- ^ Size of turtle's pen.

penSize :: TurtleCommand Float
penSize = Float -> Lens' TurtleData Float -> TurtleCommand Float
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Float
0 Lens' TurtleData Float
T.penSize

-- | Sets the turtle's pen size.

--   See `penSize`.

setPenSize :: Float -- ^ New size for turtle's pen.

           -> TurtleCommand ()
setPenSize :: Float -> TurtleCommand ()
setPenSize = Lens' TurtleData Float -> Float -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Float
T.penSize

-- | Returns whether the turtle is visible.

--   The default value is @True@.

visible :: TurtleCommand Bool -- ^ @True@ if turtle is visible, @False@ if not.

visible :: TurtleCommand Bool
visible = Bool -> Lens' TurtleData Bool -> TurtleCommand Bool
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Bool
False Lens' TurtleData Bool
T.visible

-- | Sets the turtle's visibility.

--   See `visible`.

setVisible :: Bool -- ^ New state for visible flag.

           -> TurtleCommand ()
setVisible :: Bool -> TurtleCommand ()
setVisible = Lens' TurtleData Bool -> Bool -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Bool
T.visible

-- | Returns the turtle's current speed.

--   Speed is is @distance@ per second.

--   A speed of @0@ is equivalent to no animation being performed and instant 

--   movement.

-- The default value is @200@.

speed :: TurtleCommand Float -- ^ Speed of turtle.

speed :: TurtleCommand Float
speed = Float -> Lens' TurtleData Float -> TurtleCommand Float
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Float
0 Lens' TurtleData Float
T.speed

-- | Sets the turtle's speed.

--   See `speed`.

setSpeed :: Float -- ^ New speed.

         -> TurtleCommand ()
setSpeed :: Float -> TurtleCommand ()
setSpeed = Lens' TurtleData Float -> Float -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Float
T.speed

-- | Returns the turtle's current rotation speed.

--   Rotation speed is is the speed in seconds it takes to do a full revolution.

--   A speed of @0@ is equivalent to no animation being performed and instant 

--   rotation.

-- The default value is @20@.

rotationSpeed :: TurtleCommand Float -- ^ Rotation speed of turtle.

rotationSpeed :: TurtleCommand Float
rotationSpeed = Float -> Lens' TurtleData Float -> TurtleCommand Float
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Float
0 Lens' TurtleData Float
T.rotationSpeed

-- | Sets the turtle's rotation speed.

--   See `rotationSpeed`.

setRotationSpeed :: Float -- ^ New rotation speed.

                 -> TurtleCommand ()
setRotationSpeed :: Float -> TurtleCommand ()
setRotationSpeed = Lens' TurtleData Float -> Float -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Float
T.rotationSpeed

-- | Gets the turtle's representation as a `Picture`.

representation :: TurtleCommand Picture
representation :: TurtleCommand Picture
representation = Picture -> Lens' TurtleData Picture -> TurtleCommand Picture
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ Picture
blank Lens' TurtleData Picture
T.representation

{- | Sets the turtle's representation to a `Picture`.
   See `representation`.
   For example, to set the turtle as a red circle:
   
   
  > import Graphics.WorldTurtle
  > import qualified Graphics.Gloss.Data.Picture as G
  >
  >  myCommand :: TurtleCommand ()
  >  myCommand = do
  >    setPenColor red
  >    setRepresentation (G.color red $ G.circleSolid 10)
  >    forward 90
-}
setRepresentation :: Picture -- ^ Picture to apply.

                  -> TurtleCommand ()
setRepresentation :: Picture -> TurtleCommand ()
setRepresentation = Lens' TurtleData Picture -> Picture -> TurtleCommand ()
forall b. Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData Picture
T.representation

-- | Clears all drawings form the canvas. Does not alter any turtle's state.

clear :: WorldCommand ()
clear :: WorldCommand ()
clear = MaybeT TurtleState () -> WorldCommand ()
forall a. SequenceCommand a -> WorldCommand a
WorldCommand (MaybeT TurtleState () -> WorldCommand ())
-> MaybeT TurtleState () -> WorldCommand ()
forall a b. (a -> b) -> a -> b
$ ([Picture] -> Identity [Picture]) -> TSC -> Identity TSC
Lens' TSC [Picture]
pics (([Picture] -> Identity [Picture]) -> TSC -> Identity TSC)
-> [Picture] -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [Picture]
forall a. Monoid a => a
mempty

-- | Sleep for a given amount of time in seconds. When sleeping no animation 

--   runs. A negative value will be clamped to @0@.

sleep :: Float -> WorldCommand ()
sleep :: Float -> WorldCommand ()
sleep = MaybeT TurtleState () -> WorldCommand ()
forall a. SequenceCommand a -> WorldCommand a
WorldCommand (MaybeT TurtleState () -> WorldCommand ())
-> (Float -> MaybeT TurtleState ()) -> Float -> WorldCommand ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> MaybeT TurtleState ()
decrementSimTime (Float -> MaybeT TurtleState ())
-> (Float -> Float) -> Float -> MaybeT TurtleState ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Float -> Float
forall a. Ord a => a -> a -> a
max Float
0

-- | Given a command, runs the command, then resets the turtle's state back to

--   what the state was before the command was run.

branch :: TurtleCommand a -> TurtleCommand a
branch :: TurtleCommand a -> TurtleCommand a
branch (TurtleCommand Turtle -> WorldCommand a
p ) = (Turtle -> SequenceCommand a) -> TurtleCommand a
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> SequenceCommand a) -> TurtleCommand a)
-> (Turtle -> SequenceCommand a) -> TurtleCommand a
forall a b. (a -> b) -> a -> b
$ \ Turtle
turtle -> do
  !TurtleData
t <- Turtle -> SequenceCommand TurtleData
tData_ Turtle
turtle
  a
output <- WorldCommand a -> SequenceCommand a
forall a. WorldCommand a -> SequenceCommand a
seqW (WorldCommand a -> SequenceCommand a)
-> WorldCommand a -> SequenceCommand a
forall a b. (a -> b) -> a -> b
$ Turtle -> WorldCommand a
p Turtle
turtle
  Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
turtle ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> TurtleData -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= TurtleData
t
  a -> SequenceCommand a
forall (m :: * -> *) a. Monad m => a -> m a
return a
output

-- | @90@ degrees.

north :: Float
north :: Float
north = Float
90

-- | @0@ degrees.

east :: Float
east :: Float
east = Float
0

-- | @180@ degrees.

west :: Float 
west :: Float
west = Float
180

-- | @270@ degrees.

south :: Float
south :: Float
south = Float
270

{-
   Here be dirty helper functions:
-}

-- | Looks up the turtle data for the given turtle in the state monad.

-- This type signature comes form GHC...my prism-foo is not good enough to sugar

-- it.

turtLens_ :: Applicative f 
          => Turtle 
          -> (T.TurtleData -> f T.TurtleData) 
          -> TSC
          -> f TSC 
turtLens_ :: Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
t = (Map Turtle TurtleData -> f (Map Turtle TurtleData))
-> TSC -> f TSC
Lens' TSC (Map Turtle TurtleData)
turtles ((Map Turtle TurtleData -> f (Map Turtle TurtleData))
 -> TSC -> f TSC)
-> ((TurtleData -> f TurtleData)
    -> Map Turtle TurtleData -> f (Map Turtle TurtleData))
-> (TurtleData -> f TurtleData)
-> TSC
-> f TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map Turtle TurtleData)
-> Traversal'
     (Map Turtle TurtleData) (IxValue (Map Turtle TurtleData))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index (Map Turtle TurtleData)
Turtle
t
{-# INLINE turtLens_ #-}

-- | This is a helper function for our getter commands.

--   It takes a default value, the lense to compose, and the turtle to inspect.

getter_ :: a -> Lens' T.TurtleData a -> TurtleCommand a
getter_ :: a -> Lens' TurtleData a -> TurtleCommand a
getter_ a
def Lens' TurtleData a
l = (Turtle -> SequenceCommand a) -> TurtleCommand a
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> SequenceCommand a) -> TurtleCommand a)
-> (Turtle -> SequenceCommand a) -> TurtleCommand a
forall a b. (a -> b) -> a -> b
$ \ Turtle
t -> a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
def (Maybe a -> a) -> MaybeT TurtleState (Maybe a) -> SequenceCommand a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (First a) TSC a -> MaybeT TurtleState (Maybe a)
forall s (m :: * -> *) a.
MonadState s m =>
Getting (First a) s a -> m (Maybe a)
preuse (Turtle
-> (TurtleData -> Const (First a) TurtleData)
-> TSC
-> Const (First a) TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
t ((TurtleData -> Const (First a) TurtleData)
 -> TSC -> Const (First a) TSC)
-> ((a -> Const (First a) a)
    -> TurtleData -> Const (First a) TurtleData)
-> Getting (First a) TSC a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const (First a) a)
-> TurtleData -> Const (First a) TurtleData
Lens' TurtleData a
l)
{-# INLINE getter_ #-}

-- | This is a helper function that extracts the turtle data for a given turtle.

tData_ :: Turtle -> SequenceCommand T.TurtleData
tData_ :: Turtle -> SequenceCommand TurtleData
tData_ Turtle
t = WorldCommand TurtleData -> SequenceCommand TurtleData
forall a. WorldCommand a -> SequenceCommand a
seqW (WorldCommand TurtleData -> SequenceCommand TurtleData)
-> WorldCommand TurtleData -> SequenceCommand TurtleData
forall a b. (a -> b) -> a -> b
$ TurtleCommand TurtleData -> Turtle -> WorldCommand TurtleData
forall a. TurtleCommand a -> Turtle -> WorldCommand a
seqT (TurtleData
-> Lens' TurtleData TurtleData -> TurtleCommand TurtleData
forall a. a -> Lens' TurtleData a -> TurtleCommand a
getter_ TurtleData
T.defaultTurtle forall a. a -> a
Lens' TurtleData TurtleData
id) Turtle
t
{-# INLINE tData_ #-}

-- | This is a helper function for our setter commands

-- It takes a lens, the value to apply, and the turtle to modify.

setter_ :: Lens' T.TurtleData b -> b -> TurtleCommand ()
setter_ :: Lens' TurtleData b -> b -> TurtleCommand ()
setter_ Lens' TurtleData b
l b
val = (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a. (Turtle -> SequenceCommand a) -> TurtleCommand a
seqToT ((Turtle -> MaybeT TurtleState ()) -> TurtleCommand ())
-> (Turtle -> MaybeT TurtleState ()) -> TurtleCommand ()
forall a b. (a -> b) -> a -> b
$ \ Turtle
t -> Turtle
-> (TurtleData -> Identity TurtleData) -> TSC -> Identity TSC
forall (f :: * -> *).
Applicative f =>
Turtle -> (TurtleData -> f TurtleData) -> TSC -> f TSC
turtLens_ Turtle
t ((TurtleData -> Identity TurtleData) -> TSC -> Identity TSC)
-> ((b -> Identity b) -> TurtleData -> Identity TurtleData)
-> (b -> Identity b)
-> TSC
-> Identity TSC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b -> Identity b) -> TurtleData -> Identity TurtleData
Lens' TurtleData b
l ((b -> Identity b) -> TSC -> Identity TSC)
-> b -> MaybeT TurtleState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= b
val
{-# INLINE setter_ #-}