aboutsummaryrefslogtreecommitdiffstats
path: root/src/Main.hs
blob: b674eb681b4881bcaf48f8893893db590912381f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
module Main where

import           Data.Bifunctor       (Bifunctor, bimap)
import qualified Data.ByteString      as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text            as T
import           Data.Word            (Word8)
import           PFM
import           Vec

clamp :: PFMColour -> PPMColour
clamp (PFMColour ri gi bi) =
  PPMColour (f ri) (f gi) (f bi)
  where
    v s = s * 255.0
    f s = if v s > 255.0 then 255 else fromInteger (round (v s))
clamp _ = undefined

clampImage :: PFMImage -> PPMImage
clampImage (PFMImage w h c) =
  PPMImage w h $ fmap clamp <$> c

bmap :: (Bifunctor f) => (a -> b) -> f a a -> f b b
bmap f = bimap f f

uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 f (a, b, c) = f a b c

colourCorrect :: Double -> Double
colourCorrect = (+0.5) . (/2)

toCircle :: ((Int, Int) -> Vec Double) -> Int -> [[(Int, Int)]] -> [[PFMColour]]
toCircle f v m =
  fmap toCol <$> m
  where
    toCol val = if dist val <= v ^ (2 :: Int)
      then uncurry3 PFMColour (unVec $ realToFrac . colourCorrect <$> f val)
      else PFMColour 0 0 0--0.5 0.5 1.0
    dist = add . bmap ((^(2 :: Int)) . (v-))
    add (an, bn) = an + bn

circleImage :: ((Int, Int) -> Vec Double) -> Int -> PFMImage
circleImage f s = PFMImage s s $ toCircle f ((s - 1) `div` 2)
  [ [ (y, x) | x <- [0..s-1] ] | y <- reverse [0..s-1] ]

revColour :: PFMImage -> PFMImage
revColour (PFMImage w h i) =
  PFMImage w h $ reverse i

main :: IO ()
main = do
  let i = circleImage (normalise 511) 511
  BL.writeFile "normal.ppm" . encodePPM . clampImage $ i
  BL.writeFile "normal.pfm" . encode . revColour $ i
  let r = circleImage (reflect 511 (Vec (0, 0, 1))) 511
  BL.writeFile "reflect.ppm" . encodePPM . clampImage $ r
  BL.writeFile "reflect.pfm" . encode . revColour $ r