--[[-- Mandulia -- Mandelbrot/Julia explorer Copyright (C) 2010 Claude Heiland-Allen This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . --]]-- require("defaults") require("transition") require("distance") do -- frame count without interaction local mode = "interact" local unattended = 0 local attentionSpan = 25 * 60 -- frame counts for recording local frames = 0 local frameLimit = 0 -- magic numbers math.randomseed(os.time()) local phi = (math.sqrt(5) + 1) / 2 local phi1 = (math.sqrt(5) - 1) / 2 -- animation parameters local defaultSpeed = 0.125 local defaultWeight = 8 local speed = defaultSpeed local weight = defaultWeight -- view bounds local minimum = { x = -4, y = -4, z = 0 } local maximum = { x = 4, y = 4, z = 42 } local function clamp(x, mi, ma) return math.min(math.max(x, mi), ma) end -- attract mode for interesting behaviour when unattended local attract = { } do local function walk(x, mi, ma, d) local p = (x - mi) / (ma - mi) local s = math.random() return x + d * (s - p) end -- default view local function zero() return { x = 0, y = 0, z = minimum.z } end -- animation variables local source = zero() local target = zero() local t = 0 local s = 0 local f = function(t) return zero() end local dz = minimum.z local history = { } for i = 1,48 do history[i] = { x = 0, y = 0 } end local historyptr = 1 attract.enter = function() mode = "attract" target.x = mandulia.view.x target.y = mandulia.view.y target.z = mandulia.view.z t = 0 s = 0 end attract.render = function() t = t + speed * (phi1 ^ dz) if t > s then -- we reached the target, new target needed t = t - s source.x = target.x source.y = target.y source.z = target.z local interesting local x, y, e, v, d2, dx, dy local r = 25 * phi1 ^ dz e = exteriordistance(source.x, source.y, 1000, 1000) interesting = e ~= nil and e < 0.00001 if interesting then interesting = false while not interesting do x = source.x + r * (2 * math.random() - 1) y = source.y + r * (2 * math.random() - 1) e = exteriordistance(x, y, 1000, 1000) if e ~= nil and e < 0.00001 then v = false for i,p in ipairs(history) do dx = x - p.x dy = y - p.y d2 = dx * dx + dy * dy v = v or d2 < 0.01 end if v then r = r * 1.1 end interesting = not v end end else interesting = false while not interesting do x = math.random() * (maximum.x - minimum.x) + minimum.x y = math.random() * (maximum.y - minimum.y) + minimum.y e = exteriordistance(x, y, 1000, 1000) interesting = e ~= nil and e < 0.00001 end end target.x = clamp(x, minimum.x, maximum.x) target.y = clamp(y, minimum.y, maximum.y) target.z = walk(source.z, minimum.z, maximum.z, 3) history[historyptr].x = target.x history[historyptr].y = target.y historyptr = historyptr + 1 if historyptr > #history then historyptr = 1 end s, f = transition(source, target, weight, phi) end mandulia.view = f(t) mandulia.view.z = clamp(mandulia.view.z, minimum.z, maximum.z) dz = mandulia.view.z end -- render end -- attract -- interact mode for engagement and control local interact = { } do local delta = { x = 0, y = 0, z = 0 } interact.enter = function() mode = "interact" unattended = 0 end interact.render = function() local x = mandulia.view.x + speed * delta.x * phi1 ^ mandulia.view.z local y = mandulia.view.y + speed * delta.y * phi1 ^ mandulia.view.z local z = mandulia.view.z + speed * delta.z mandulia.view.x = clamp(x, minimum.x, maximum.x) mandulia.view.y = clamp(y, minimum.y, maximum.y) mandulia.view.z = clamp(z, minimum.z, maximum.z) end local keys = { Right = function() delta.x = delta.x + 1 end , Left = function() delta.x = delta.x - 1 end , Up = function() delta.y = delta.y + 1 end , Down = function() delta.y = delta.y - 1 end , PageUp = function() delta.z = delta.z + 1 end , PageDown = function() delta.z = delta.z - 1 end , End = function() delta = { x = 0, y = 0, z = 0 } end , Home = function() delta = { x = 0, y = 0, z = 0 } mandulia.view = { x = 0, y = 0, z = 0 } end , ["["] = function() speed = speed * 0.95 end , ["]"] = function() speed = speed / 0.95 end , ["#"] = function() speed = defaultSpeed end , ["{"] = function() weight = weight * 0.95 end , ["}"] = function() weight = weight / 0.95 end , ["~"] = function() weight = defaultWeight end } interact.keyboard = function(key) if type(keys[key]) == "function" then keys[key]() end end end -- interact local screenshot = { } local record = { } do local recording = false screenshot.enter = function() frames = 0 frameLimit = 1 frameStep = 1 recording = true end record.enter = function() frames = 0 frameLimit = 25 * 60 * 10 frameStep = 1 recording = true end record.render = function() if recording then mandulia.record = (frames % frameStep) == 0 and frames < frameLimit frames = frames + 1 end end end -- screenshot/record function mandulia.render() if mode == "interact" then interact.render() unattended = unattended + 1 if unattended >= attentionSpan then attract.enter() end elseif mode == "attract" then attract.render() end record.render() end function mandulia.keyboard(key) if key == "Escape" then mandulia.quit() elseif key == "F11" then mandulia.fullscreen = not mandulia.fullscreen elseif key == "a" then attract.enter() elseif key == "r" then record.enter() elseif key == "s" then screenshot.enter() else interact.enter() interact.keyboard(key) end end end pcall(function() require("config") end)