Skip to content

Commit

Permalink
ilerp experiment
Browse files Browse the repository at this point in the history
  • Loading branch information
sorki committed Aug 16, 2022
1 parent 8025785 commit 1c8f288
Showing 1 changed file with 52 additions and 2 deletions.
54 changes: 52 additions & 2 deletions example-haskell/SomeModule.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,64 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module SomeModule where

import Control.Applicative
import Linear
import Graphics.Implicit
import Graphics.Implicit.Primitives
--import Graphics.Implicit.ObjectUtil.GetBoxShared

import SomeOtherModule

res = 2
--res = 0.016
res = 0.5

obj = union $ [
ilerp
:: forall obj f . (Object obj (f ), Applicative f, Semigroup obj)
=>
-> obj
-> obj
-> obj
ilerp s a b = implicit
(\i ->
(1 - s) * getImplicit a i
+ s * getImplicit b i
)
$ --(getBox a) <> (getBox b)
getBox $
(scale :: f -> obj -> obj) (pure (1-s)) a
<> (scale :: f -> obj -> obj) (pure s) b
-- <> b

ilerp'
:: forall obj f . (Object obj (f ), Applicative f, Semigroup obj)
=>
-> obj
-> obj
-> obj
ilerp' s a b = implicit
(\i ->
(1 - s) * getImplicit a i
+ s * getImplicit b i
)
$ --(getBox a) <> (getBox b)
let (a1 :: f , b1) = getBox a
(a2 :: f , b2) = getBox a
sa1 = liftA2 (*) (pure $ 1 - s) a1
sb1 = liftA2 (*) (pure $ 1 - s) b1
sa2 = liftA2 (*) (pure s) a2
sb2 = liftA2 (*) (pure s) b2
in pointsBox [sa1, sb1, sa2, sb2]

pointsBox :: (Applicative f, Ord a, Num a) => [f a] -> (f a, f a)
pointsBox [] = (pure 0, pure 0)
pointsBox (a : as) = (foldr (liftA2 min) a as, foldr (liftA2 max) a as)

obj = ilerp' 1.0 (cube False (pure 3)) (cylinder2 7 5 6)
--obj = cube False (V3 3 0.095 0.045)

objz = union $ [
cube False (V3 20 20 14)
, translate (V3 20 20 20) (sphere 15)
, translate (V3 30 20 20) (sphere 5)
Expand Down

0 comments on commit 1c8f288

Please sign in to comment.