Skip to content

Instantly share code, notes, and snippets.

@ajnsit
Last active June 6, 2020 19:37
Show Gist options
  • Save ajnsit/c3637f0be0e8857c4c118ae6a35c3663 to your computer and use it in GitHub Desktop.
Save ajnsit/c3637f0be0e8857c4c118ae6a35c3663 to your computer and use it in GitHub Desktop.
module Main where
import Prelude
import Concur.Core (Widget)
import Concur.React (HTML)
import Concur.React.Props (ReactProps, height, stroke, strokeWidth, unsafeMkProp, viewBox, width)
import Concur.React.Run (runWidgetInDom)
import Concur.React.SVG (line, svg)
import Control.Alt ((<|>))
import Control.MultiAlternative (orr)
import Data.Array (reverse, (:))
import Data.Foldable (foldl)
import Data.Time.Duration (Milliseconds(..))
import Data.Tuple (snd)
import Data.Tuple.Nested ((/\), type (/\))
import Effect (Effect)
import Effect.Aff (delay)
import Effect.Aff.Class (liftAff)
main :: Effect Unit
main = runWidgetInDom "main" do
svg
[ width "500"
, height "500"
, viewBox "0 0 500 500"
] [growingDragonCurve newModel]
---------------
-- RENDERING --
---------------
-- Draw one section, wait, recurse to draw the next sections, uptil 10 iterations
growingDragonCurve :: forall a. Model -> Widget HTML a
growingDragonCurve model
| model.iteration > 10 = renderLines model
| otherwise = do
renderLines model <|> do
liftAff (delay $ Milliseconds 1000.0)
growingDragonCurve (step model)
type Coord = Int /\ Int
-- Render the lines for a section of the dragon curve
renderLines :: forall a. Model -> Widget HTML a
renderLines = orr <<< snd <<< foldl renderLine ((120 /\ 120) /\ []) <<< _.dirs
renderLine
:: forall a
. Coord /\ Array (Widget HTML a)
-> Dir
-> Coord /\ Array (Widget HTML a)
renderLine (coord /\ lines) dir = newCoord /\ newLine : lines
where
newCoord = move coord dir
newLine = makeLine coord newCoord
stepSize = 10
move (x /\ y) = case _ of
Up -> x /\ (y - stepSize)
Down -> x /\ (y + stepSize)
Left -> (x - stepSize) /\ y
Right -> (x + stepSize) /\ y
makeLine (xa /\ ya) (xb /\ yb) = line
[ x1 xa
, x2 xb
, y1 ya
, y2 yb
, strokeWidth 2
, stroke "#000000"
] []
-----------
-- MODEL --
-----------
data Dir = Up | Down | Left | Right
type Model =
{ dirs :: Array Dir
, iteration :: Int
}
newModel :: Model
newModel = { dirs: [], iteration: 0 }
step :: Model -> Model
step model = model
{ dirs = unfold model.dirs
, iteration = model.iteration + 1
}
where
unfold = case _ of
[] -> [ Down ]
dirs -> dirs <> (rotate <$> reverse dirs)
rotate = case _ of
Right -> Up
Up -> Left
Left -> Down
Down -> Right
-------------
-- UTILITY --
-------------
x1 :: forall a. Int -> ReactProps a
x1 = unsafeMkProp "x1" <<< show
x2 :: forall a. Int -> ReactProps a
x2 = unsafeMkProp "x2" <<< show
y1 :: forall a. Int -> ReactProps a
y1 = unsafeMkProp "y1" <<< show
y2 :: forall a. Int -> ReactProps a
y2 = unsafeMkProp "y2" <<< show
@ajnsit
Copy link
Author

ajnsit commented Jun 6, 2020

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment