Skip to content

Commit

Permalink
Added a version of the turtle example from Seth Tisue's talk on lenses.
Browse files Browse the repository at this point in the history
  • Loading branch information
ekmett committed Nov 20, 2012
1 parent 0c727bb commit a65cb2a
Showing 1 changed file with 65 additions and 0 deletions.
65 changes: 65 additions & 0 deletions examples/Turtle.hs
@@ -0,0 +1,65 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveDataTypeable #-}
-- | A simple Turtle-graphics demonstration for modeling the location of a turtle.
--
-- This is based on the code presented by Seth Tisue at the Boston Area Scala
-- Enthusiasts meeting during his lens talk.
--
-- Usage:
--
-- > def & forward 10 & down & color .~ red % turn (pi/2) & forward 5
module Turtle where

import Control.Lens hiding (up, down)
import Data.Default

data Point = Point
{ _x, _y :: Double
} deriving (Eq,Show)

makeClassy ''Point

instance Default Point where
def = Point def def

data Color = Color
{ _r, _g, _b :: Int
} deriving (Eq,Show)

makeClassy ''Color

red :: Color
red = Color 255 0 0

instance Default Color where
def = Color def def def

data Turtle = Turtle
{ _tPoint :: Point
, _tColor :: Color
, _heading :: Double
, _penDown :: Bool
} deriving (Eq,Show)

makeClassy ''Turtle

instance Default Turtle where
def = Turtle def def def False

instance HasPoint Turtle where
point = tPoint

instance HasColor Turtle where
color = tColor

forward :: Double -> Turtle -> Turtle
forward d t =
t & y +~ d * cos (t^.heading)
& x +~ d * sin (t^.heading)

turn :: Double -> Turtle -> Turtle
turn d = heading +~ d

up, down :: Turtle -> Turtle
up = penDown .~ False
down = penDown .~ True

0 comments on commit a65cb2a

Please sign in to comment.