Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
54 changes: 6 additions & 48 deletions exec-src/coon_rendering.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ import Graphics.Rasterific.Linear( (^+^), (^*) )
import Graphics.Rasterific.Immediate
import Graphics.Rasterific.Patch
import Graphics.Rasterific.MeshPatch
import Graphics.Rasterific

import Criterion
import Criterion.Main
Expand All @@ -23,22 +22,15 @@ import Codec.Picture

import qualified Data.Vector as V

background, blue, black, yellow, red, green, orange, white :: PixelRGBA8
background = PixelRGBA8 128 128 128 255
blue, black, yellow, red, green, orange, white :: PixelRGBA8
blue = PixelRGBA8 0 020 150 255
red = PixelRGBA8 255 0 0 255
green = PixelRGBA8 0 255 0 255
black = PixelRGBA8 0 0 0 255
{-grey = PixelRGBA8 128 128 128 255-}
orange = PixelRGBA8 255 0xA5 0 255
yellow = PixelRGBA8 255 255 0 255
{-brightblue = PixelRGBA8 0 255 255 255-}
white = PixelRGBA8 255 255 255 255

biColor, triColor :: Gradient PixelRGBA8
biColor = [ (0.0, black) , (1.0, yellow) ]
triColor = [ (0.0, blue), (0.5, white) , (1.0, red) ]

frontColor, accentColor, accent2Color :: PixelRGBA8
frontColor = PixelRGBA8 0 0x86 0xc1 255
accentColor = PixelRGBA8 0xff 0xf4 0xc1 255
Expand Down Expand Up @@ -72,31 +64,26 @@ drawPure path w h act = do

coonTest :: IO ()
coonTest = do
drawing "coon_img/single_patch.png" defaultDebug 400 440 patch [patch]
drawing "coon_img/single_patch_subdiv.png" defaultDebug 400 410 patch [n, e, w, s]
drawing "coon_img/single_patch.png" 400 440 patch [patch]
drawing "coon_img/single_patch_subdiv.png" 400 410 patch [north, east, west, south]
putStrLn "coon_img/subdiv.gif"
case imgAtSubdiv of
Left _ -> return ()
Right f -> f
where
draw path p = do
putStrLn $ "Rendering " ++ path
writePng path . renderDrawing 800 800 (PixelRGBA8 255 255 255 255) $
withTexture (uniformTexture (PixelRGBA8 0 0 0 255)) p

drawing :: FilePath -> DebugOption -> Int -> Int
drawing :: FilePath -> Int -> Int
-> CoonPatch (ParametricValues PixelRGBA8)
-> [CoonPatch (ParametricValues a)]
-> IO ()
drawing path opt w h rootPatch patches = do
drawing path w h rootPatch patches = do
putStrLn $ "Rendering " ++ path
writePng path $ runST $ runDrawContext w h white $ do
rasterizeCoonPatch rootPatch
forM_ patches $ \p ->
mapM_ fillOrder $ drawOrdersOfDrawing w h 96 white $
debugDrawCoonPatch defaultDebug p { _coonValues = colors }

Subdivided n e w s = subdividePatch patch { _coonValues = parametricBase }
Subdivided north east west south = subdividePatch patch { _coonValues = parametricBase }

imgAtSubdiv = writeGifImages "coon_img/subdiv.gif" LoopingForever images
where
Expand Down Expand Up @@ -237,13 +224,6 @@ toCoon st values = build . go st where

toAbsolute p = fmap (p ^+^)

drawVertex :: Point -> Drawing PixelRGBA8 ()
drawVertex p = stroke 2 JoinRound (CapRound, CapRound) $ circle p 4

drawBetweenPoint :: Point -> Point -> Drawing PixelRGBA8 ()
drawBetweenPoint p1 p2 =
stroke 1.5 JoinRound (CapRound, CapRound) $ line p1 p2

jitPoints :: Transformable a => Float -> a -> a
jitPoints force e = evalState (transformM jit e) jitter where
jitter = cycle $ (^* force) <$> [ V2 1 0.5, V2 0.5 1 , V2 (-0.5) (-1)
Expand Down Expand Up @@ -327,28 +307,6 @@ debugCubic = do
mesh3 =
generateLinearGrid 9 9 (V2 10 10) (V2 100 100) . V.fromListN (10 * 10) $ cycle colorBase

colors2 = V.fromListN (4 * 4)
[ px 255 179 47
, px 255 242 34
, px 61 227 206
, px 90 255 0

, px 255 242 34
, px 61 227 206
, px 103 157 255
, px 255 179 47

, px 255 74 74
, px 90 255 0
, px 255 179 47
, px 61 227 206

, px 103 157 255
, px 61 227 206
, px 255 242 34
, px 103 157 255
]

colors = V.fromListN (5 * 5) colorBase

colorBase =
Expand Down
12 changes: 0 additions & 12 deletions src/Graphics/Rasterific/Patch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,18 +85,6 @@ import Codec.Picture.Types( PixelRGBA8( .. ) )
-- @


-- TODO: find a new way to calculate that...
maxColorDeepness :: forall px. InterpolablePixel px => ParametricValues px -> Int
maxColorDeepness values = ceiling $ log (maxDelta * range) / log 2 where
range = maxRepresentable (Proxy :: Proxy px)
maxDelta =
maximum [ maxDistance north east
, maxDistance east south
, maxDistance south west
, maxDistance west north]
ParametricValues { _westValue = west, _northValue = north
, _southValue = south, _eastValue = east } = values

estimateCoonSubdivision :: CoonPatch px -> Int
estimateCoonSubdivision CoonPatch { .. } = min 8 $
maximum $ estimateFDStepCount <$> [_north, _west, _south, _east]
Expand Down