module View ( Location(..), zoom, translate, defLocation , Viewport(..), rotate, defViewport , Window(..), windowSize, defWindow , Colours(..), defColours, Colour(..) , Label(..), Line(..) , Image(..), defImage , BufferSize(..), bufferSize , pixelLocation, delta, tileSize, locationPixel , visibleQuads, originQuad ) where import Control.Monad (guard) import Data.Bits (bit) import Data.Ratio ((%)) import Fractal.RUFF.Types.Complex (Complex((:+)), magnitude) import Fractal.GRUFF import QuadTree (Quad(..), Child(..), child, Square(..), square) import Tile (rootSquare) pixelLocation :: Window -> Viewport -> Location -> Double -> Double -> Complex Rational pixelLocation w v l = let f = fromScreenCoords w v l in \x y -> f (x :+ y) locationPixel :: Window -> Viewport -> Location -> Complex Rational -> (Double, Double) locationPixel w v l = let f = toScreenCoords w v l in \c -> let (x :+ y) = f c in (x, y) zoom :: Double -> Location -> Location zoom f l = l{ radius = radius l * f} translate :: Complex Rational -> Location -> Location translate u l = l{ center = center l + u } rotate :: Double -> Viewport -> Viewport rotate a v = v{ orient = orient v + a } windowSize :: Window -> Int windowSize w = ceiling . sqrt . (fromIntegral :: Int -> Double) . diagonal2 $ w diagonal2 :: Window -> Int diagonal2 w = width w * width w + height w * height w data BufferSize = BufferSize { texels :: !Int -- power of two } deriving (Read, Show, Eq) bufferSize :: Int -> Window -> BufferSize bufferSize o w = BufferSize{ texels = roundUp2 . ceiling . ((2::Double) ^^ o *) . sqrt . fromIntegral . diagonal2 $ w } roundUp2 :: Int -> Int -- fails for too small and too large inputs roundUp2 x = head . dropWhile (x >=) . iterate (2 *) $ 1 level :: Location -> Int level = floor . negate . logBase 2 . radius radius' :: Location -> Double radius' l = 0.5 ** fromIntegral (level l) delta :: Location -> Double -- in [0,1) delta l = logBase 2 $ radius' l / radius l tileSize :: Int tileSize = 256 tileLevel :: Location -> BufferSize -> Int tileLevel l b = level l + (floor . logBase (2 :: Double) . fromIntegral) (texels b `div` tileSize) tileOrigin :: Complex Rational tileOrigin = negate $ 4 :+ 4 tileOriginRadius :: Complex Rational tileOriginRadius = 8 bufferOrigin :: Location -> Quad -> Maybe (Complex Int) bufferOrigin l Quad{ quadLevel = ql, quadWest = qw, quadNorth = qn } = do guard $ ql >= 0 let qd = bit ql qc = (qw % qd) :+ (qn % qd) tx :+ ty = fromIntegral tileSize * fromIntegral qd * (qc - (center l - tileOrigin) / tileOriginRadius) return (floor tx :+ floor ty) originQuad :: Location -> BufferSize -> Maybe Quad originQuad l b = let cx :+ cy = center l ql = tileLevel l b qs = bit ql % 1 qw = floor $ (cx + 4) / 8 * qs qn = floor $ (cy + 4) / 8 * qs in if ql <= 0 then Nothing else Just Quad{ quadLevel = ql, quadWest = qw, quadNorth = qn } bufferQuads :: Location -> BufferSize -> Maybe [(Complex Int, Quad)] bufferQuads l b = do q0 <- originQuad l b i0 :+ j0 <- bufferOrigin l q0 let m = texels b u = fromIntegral $ (m `div` 2) `div` tileSize v = fromIntegral $ (m `div` 2) `div` tileSize return [ (i :+ j, q0{ quadWest = w, quadNorth = n }) | (i, w) <- takeWhile ((< m) . fst) $ [ i0, i0 + tileSize .. ] `zip` [ quadWest q0 - u .. ] , (j, n) <- takeWhile ((< m) . fst) $ [ j0, j0 + tileSize .. ] `zip` [ quadNorth q0 - v .. ] ] childQuads :: (Complex Int, Quad) -> [(Complex Int, Quad)] childQuads (i :+ j, q) = let i0 = 2 * i j0 = 2 * j i1 = i0 + tileSize j1 = j0 + tileSize in [ (i0 :+ j0, NorthWest `child` q) , (i0 :+ j1, SouthWest `child` q) , (i1 :+ j0, NorthEast `child` q) , (i1 :+ j1, SouthEast `child` q) ] visibleQuads :: Window -> Viewport -> Location -> Int -> Maybe ([(Complex Int, Quad)], [(Complex Int, Quad)]) visibleQuads w v l o = do let b = bufferSize o w x0 = 0 y0 = 0 x1 = fromIntegral (width w) y1 = fromIntegral (height w) toScreen = toScreenCoords w v l visible (_, q) = let s = square rootSquare q d = squareSize s / 2 r = magnitude $ p - p0 c0 = squareWest s :+ squareNorth s c = (squareWest s + d) :+ (squareNorth s + d) p0 = toScreen c0 p@(x :+ y) = toScreen c in not $ x < x0 - r || y < y0 - r || x1 + r < x || y1 + r < y qs0 <- bufferQuads l b let qs0' = filter visible qs0 qs1 = concatMap childQuads qs0' qs1' = filter visible qs1 return (qs0', qs1') defImage :: Image defImage = Image { imageWindow = defWindow , imageViewport = defViewport , imageLocation = defLocation , imageColours = defColours , imageLabels = [] , imageLines = [] } defColours :: Colours defColours = Colours { colourInterior = Colour 1 0 0 , colourBoundary = Colour 0 0 0 , colourExterior = Colour 1 1 1 } defLocation :: Location defLocation = Location{ center = 0, radius = 2 } defWindow :: Window defWindow = Window{ width = 512, height = 288, supersamples = 1 } defViewport :: Viewport defViewport = Viewport{ aspect = 16/9, orient = 0 }