{- ORMOLU_DISABLE -}
-- Copyright 2016, Julia Longtin (julial@turinglace.com)
-- Implicit CAD. Copyright (C) 2011, Christopher Olah (chris@colah.ca)
-- Released under the GNU AGPLV3+, see LICENSE

-- Allow our DiscreteAproxable class to handle multiple parameters.
{-# LANGUAGE MultiParamTypeClasses #-}

-- For the instance declaration of DiscreteAproxable SymbolicObj2 [Polyline]
{-# LANGUAGE FlexibleInstances #-}

-- | A module for retrieving approximate represententations of objects.
module Graphics.Implicit.Export.DiscreteAproxable (DiscreteAproxable, discreteAprox) where

import Prelude(pure, (-), (/), ($), (<), round, (+), maximum, abs, (*), fromIntegral, max, realToFrac, Int)

-- Definitions for our number system, objects, and the things we can use to approximately represent objects.
import Graphics.Implicit.Definitions (defaultObjectContext, , ℝ2, SymbolicObj2, SymbolicObj3, Polyline, TriangleMesh(getTriangles), NormedTriangleMesh(NormedTriangleMesh))

import Graphics.Implicit.ObjectUtil (getBox2, getBox3)

import Graphics.Implicit.Export.SymbolicObj3 (symbolicGetMesh)

import Graphics.Implicit.Export.SymbolicObj2 (symbolicGetContour)

import Graphics.Implicit.Export.Util (normTriangle)

-- We are the only ones that use this.
import Graphics.Implicit.Export.RayTrace (Color(Color), Camera(Camera), Light(Light), Scene(Scene), average, traceRay, cameraRay)

import Codec.Picture (DynamicImage(ImageRGBA8), PixelRGBA8(PixelRGBA8), generateImage)

import Control.Parallel.Strategies (using, rdeepseq, parBuffer)

import Linear ( V3(V3), V2(V2), (*^), (^/) )
import Linear.Affine ( Affine((.+^), (.-^)) )
import Graphics.Implicit.Primitives (getImplicit)

default ()

-- | There is a discrete way to aproximate this object.
--   eg. Aproximating a 3D object with a triangle mesh
--       would be DiscreteApproxable Obj3 TriangleMesh
class DiscreteAproxable obj aprox where
    discreteAprox ::  -> obj -> aprox

instance DiscreteAproxable SymbolicObj3 TriangleMesh where
    discreteAprox :: ℝ -> SymbolicObj3 -> TriangleMesh
discreteAprox = ℝ -> SymbolicObj3 -> TriangleMesh
symbolicGetMesh

-- FIXME: number of CPUs hardcoded here.
instance DiscreteAproxable SymbolicObj3 NormedTriangleMesh where
    discreteAprox :: ℝ -> SymbolicObj3 -> NormedTriangleMesh
discreteAprox res SymbolicObj3
obj = [NormedTriangle] -> NormedTriangleMesh
NormedTriangleMesh
        ([ ℝ -> Obj3 -> Triangle -> NormedTriangle
normTriangle res (forall obj (f :: * -> *) a. Object obj f a => obj -> f a -> a
getImplicit SymbolicObj3
obj) Triangle
rawMesh
            | Triangle
rawMesh <- TriangleMesh -> [Triangle]
getTriangles forall a b. (a -> b) -> a -> b
$ ℝ -> SymbolicObj3 -> TriangleMesh
symbolicGetMesh res SymbolicObj3
obj
         ] forall a. a -> Strategy a -> a
`using` forall a. Int -> Strategy a -> Strategy [a]
parBuffer Int
32 forall a. NFData a => Strategy a
rdeepseq)

-- FIXME: way too many magic numbers.
-- FIXME: adjustable resolution!
instance DiscreteAproxable SymbolicObj3 DynamicImage where
    discreteAprox :: ℝ -> SymbolicObj3 -> DynamicImage
discreteAprox _ SymbolicObj3
symbObj = Image PixelRGBA8 -> DynamicImage
ImageRGBA8 forall a b. (a -> b) -> a -> b
$ forall px. Pixel px => (Int -> Int -> px) -> Int -> Int -> Image px
generateImage Int -> Int -> PixelRGBA8
pixelRenderer (forall a b. (RealFrac a, Integral b) => a -> b
round w) (forall a b. (RealFrac a, Integral b) => a -> b
round h)
        where
            -- Size of the image to produce.
            (V2 w h) = forall a. a -> a -> V2 a
V2 150 150 :: ℝ2
            obj :: Obj3
obj = forall obj (f :: * -> *) a. Object obj f a => obj -> f a -> a
getImplicit SymbolicObj3
symbObj
            box :: Box3
box@(V3 x1 y1 z1, V3 _ y2 z2) = SymbolicObj3 -> Box3
getBox3 SymbolicObj3
symbObj
            av ::  ->  -> 
            av :: ℝ -> ℝ -> ℝ
av a b = (aforall a. Num a => a -> a -> a
+b)forall a. Fractional a => a -> a -> a
/2
            avY :: ℝ
avY = ℝ -> ℝ -> ℝ
av y1 y2
            avZ :: ℝ
avZ = ℝ -> ℝ -> ℝ
av z1 z2
            deviation :: ℝ
deviation = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [forall a. Num a => a -> a
abs forall a b. (a -> b) -> a -> b
$ y1 forall a. Num a => a -> a -> a
- avY, forall a. Num a => a -> a
abs forall a b. (a -> b) -> a -> b
$ y2 forall a. Num a => a -> a -> a
- avY, forall a. Num a => a -> a
abs forall a b. (a -> b) -> a -> b
$ z1 forall a. Num a => a -> a -> a
- avZ, forall a. Num a => a -> a
abs forall a b. (a -> b) -> a -> b
$ z2 forall a. Num a => a -> a -> a
- avZ]
            camera :: Camera
camera = V3 ℝ -> V3 ℝ -> V3 ℝ -> ℝ -> Camera
Camera (forall a. a -> a -> a -> V3 a
V3 (x1forall a. Num a => a -> a -> a
-deviationforall a. Num a => a -> a -> a
*2.2) avY avZ) (forall a. a -> a -> a -> V3 a
V3 0 (-1) 0) (forall a. a -> a -> a -> V3 a
V3 0 0 (-1)) 1.0
            lights :: [Light]
lights = [V3 ℝ -> ℝ -> Light
Light (forall a. a -> a -> a -> V3 a
V3 (x1forall a. Num a => a -> a -> a
-deviationforall a. Num a => a -> a -> a
*1.5) (y1 forall a. Num a => a -> a -> a
- 0.4forall a. Num a => a -> a -> a
*(y2forall a. Num a => a -> a -> a
-y1)) avZ) (0.03forall a. Num a => a -> a -> a
*deviation) ]
            scene :: Scene
scene = Obj3 -> Color -> [Light] -> Color -> Scene
Scene Obj3
obj (Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> Color
Color Pixel8
200 Pixel8
200 Pixel8
230 Pixel8
255) [Light]
lights (Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> Color
Color Pixel8
255 Pixel8
255 Pixel8
255 Pixel8
0)
            -- passed to generateImage, it's external, and determines this type.
            pixelRenderer :: Int -> Int -> PixelRGBA8
            pixelRenderer :: Int -> Int -> PixelRGBA8
pixelRenderer Int
a Int
b = ℝ -> ℝ -> PixelRGBA8
renderScreen
                (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
aforall a. Fractional a => a -> a -> a
/w forall a. Num a => a -> a -> a
- 0.5) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bforall a. Fractional a => a -> a -> a
/h forall a. Num a => a -> a -> a
- 0.5)
            renderScreen ::  ->  -> PixelRGBA8
            renderScreen :: ℝ -> ℝ -> PixelRGBA8
renderScreen a b =
                Color -> PixelRGBA8
colorToPixelRGBA8 forall a b. (a -> b) -> a -> b
$
                    [Color] -> Color
average [
                        Ray -> ℝ -> Box3 -> Scene -> Color
traceRay
                            (Camera -> ℝ2 -> Ray
cameraRay Camera
camera (forall a. a -> a -> V2 a
V2 a b forall a. Num a => a -> a -> a
+ forall a. a -> a -> V2 a
V2 ( 0.25forall a. Fractional a => a -> a -> a
/w) (0.25forall a. Fractional a => a -> a -> a
/h)))
                            2 Box3
box Scene
scene,
                        Ray -> ℝ -> Box3 -> Scene -> Color
traceRay
                            (Camera -> ℝ2 -> Ray
cameraRay Camera
camera (forall a. a -> a -> V2 a
V2 a b forall a. Num a => a -> a -> a
+ forall a. a -> a -> V2 a
V2 (-0.25forall a. Fractional a => a -> a -> a
/w) (0.25forall a. Fractional a => a -> a -> a
/h)))
                            0.5 Box3
box Scene
scene,
                        Ray -> ℝ -> Box3 -> Scene -> Color
traceRay
                            (Camera -> ℝ2 -> Ray
cameraRay Camera
camera (forall a. a -> a -> V2 a
V2 a b forall a. Num a => a -> a -> a
+ forall a. a -> a -> V2 a
V2 (0.25forall a. Fractional a => a -> a -> a
/w) (-0.25forall a. Fractional a => a -> a -> a
/h)))
                            0.5 Box3
box Scene
scene,
                        Ray -> ℝ -> Box3 -> Scene -> Color
traceRay
                            (Camera -> ℝ2 -> Ray
cameraRay Camera
camera (forall a. a -> a -> V2 a
V2 a b forall a. Num a => a -> a -> a
+ forall a. a -> a -> V2 a
V2 (-0.25forall a. Fractional a => a -> a -> a
/w) (-0.25forall a. Fractional a => a -> a -> a
/h)))
                            0.5 Box3
box Scene
scene
                        ]
                    where
                      colorToPixelRGBA8 :: Color -> PixelRGBA8
                      colorToPixelRGBA8 :: Color -> PixelRGBA8
colorToPixelRGBA8 (Color Pixel8
rr Pixel8
gg Pixel8
bb Pixel8
aa) = Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> PixelRGBA8
PixelRGBA8 Pixel8
rr Pixel8
gg Pixel8
bb Pixel8
aa

instance DiscreteAproxable SymbolicObj2 [Polyline] where
    discreteAprox :: ℝ -> SymbolicObj2 -> [Polyline]
discreteAprox res = ℝ -> ObjectContext -> SymbolicObj2 -> [Polyline]
symbolicGetContour res ObjectContext
defaultObjectContext

-- FIXME: way too many magic numbers.
-- FIXME: adjustable resolution?
instance DiscreteAproxable SymbolicObj2 DynamicImage where
    discreteAprox :: ℝ -> SymbolicObj2 -> DynamicImage
discreteAprox _ SymbolicObj2
symbObj = Image PixelRGBA8 -> DynamicImage
ImageRGBA8 forall a b. (a -> b) -> a -> b
$ forall px. Pixel px => (Int -> Int -> px) -> Int -> Int -> Image px
generateImage Int -> Int -> PixelRGBA8
pixelRenderer (forall a b. (RealFrac a, Integral b) => a -> b
round w) (forall a b. (RealFrac a, Integral b) => a -> b
round h)
        where
            -- Size of the image to produce.
            V2 w h = forall (f :: * -> *) a. Applicative f => a -> f a
pure 150 :: ℝ2
            obj :: ℝ2 -> ℝ
obj = forall obj (f :: * -> *) a. Object obj f a => obj -> f a -> a
getImplicit SymbolicObj2
symbObj
            (p1 :: ℝ2
p1@(V2 x1 _), p2 :: ℝ2
p2@(V2 _ y2)) = SymbolicObj2 -> (ℝ2, ℝ2)
getBox2 SymbolicObj2
symbObj
            V2 dx dy = ℝ2
p2 forall a. Num a => a -> a -> a
- ℝ2
p1
            dxy :: ℝ
dxy = forall a. Ord a => a -> a -> a
max dx dy
            -- passed to generateImage, it's external, and determines this type.
            pixelRenderer :: Int -> Int -> PixelRGBA8
            pixelRenderer :: Int -> Int -> PixelRGBA8
pixelRenderer Int
mya Int
myb = PixelRGBA8
mycolor
                where
                    xy :: ℝ -> ℝ -> ℝ2
xy a b = (forall a. a -> a -> V2 a
V2 x1 y2 forall (p :: * -> *) a. (Affine p, Num a) => p a -> Diff p a -> p a
.-^ forall a. a -> a -> V2 a
V2 (dxyforall a. Num a => a -> a -> a
-dx) (dyforall a. Num a => a -> a -> a
-dxy) forall (f :: * -> *) a.
(Functor f, Fractional a) =>
f a -> a -> f a
^/2) forall (p :: * -> *) a. (Affine p, Num a) => p a -> Diff p a -> p a
.+^ dxy forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^ forall a. a -> a -> V2 a
V2 (aforall a. Fractional a => a -> a -> a
/w) (-bforall a. Fractional a => a -> a -> a
/h)
                    s :: ℝ
s = 0.25 :: 
                    V2 a' b' = forall a. a -> a -> V2 a
V2 (forall a b. (Real a, Fractional b) => a -> b
realToFrac Int
mya) (forall a b. (Real a, Fractional b) => a -> b
realToFrac Int
myb) :: ℝ2
                    mycolor :: PixelRGBA8
mycolor = Color -> PixelRGBA8
colorToPixelRGBA8 forall a b. (a -> b) -> a -> b
$ [Color] -> Color
average [ℝ2 -> Color
objColor forall a b. (a -> b) -> a -> b
$ ℝ -> ℝ -> ℝ2
xy a' b', ℝ2 -> Color
objColor forall a b. (a -> b) -> a -> b
$ ℝ -> ℝ -> ℝ2
xy a' b',
                        ℝ2 -> Color
objColor forall a b. (a -> b) -> a -> b
$ ℝ -> ℝ -> ℝ2
xy (a'forall a. Num a => a -> a -> a
+s) (b'forall a. Num a => a -> a -> a
+s),
                        ℝ2 -> Color
objColor forall a b. (a -> b) -> a -> b
$ ℝ -> ℝ -> ℝ2
xy (a'forall a. Num a => a -> a -> a
-s) (b'forall a. Num a => a -> a -> a
-s),
                        ℝ2 -> Color
objColor forall a b. (a -> b) -> a -> b
$ ℝ -> ℝ -> ℝ2
xy (a'forall a. Num a => a -> a -> a
+s) (b'forall a. Num a => a -> a -> a
+s),
                        ℝ2 -> Color
objColor forall a b. (a -> b) -> a -> b
$ ℝ -> ℝ -> ℝ2
xy (a'forall a. Num a => a -> a -> a
-s) (b'forall a. Num a => a -> a -> a
-s)]
                    colorToPixelRGBA8 :: Color -> PixelRGBA8
                    colorToPixelRGBA8 :: Color -> PixelRGBA8
colorToPixelRGBA8 (Color Pixel8
rr Pixel8
gg Pixel8
bb Pixel8
aa) = Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> PixelRGBA8
PixelRGBA8 Pixel8
rr Pixel8
gg Pixel8
bb Pixel8
aa
            objColor :: ℝ2 -> Color
objColor ℝ2
p = if ℝ2 -> ℝ
obj ℝ2
p forall a. Ord a => a -> a -> Bool
< 0 then Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> Color
Color Pixel8
150 Pixel8
150 Pixel8
160 Pixel8
255 else Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> Color
Color Pixel8
255 Pixel8
255 Pixel8
255 Pixel8
0