Created
October 30, 2025 17:05
-
-
Save aavogt/251bce22b770262a289809b300d7d123 to your computer and use it in GitHub Desktop.
right-angle diverging duct as a sequence of lofts
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| {-# LANGUAGE FlexibleContexts #-} | |
| -- # LANGUAGE NamedFieldPuns #-} | |
| -- # LANGUAGE OverloadedRecordDot #-} | |
| -- import Reinsch | |
| import Control.Lens | |
| import Data.List | |
| import qualified Data.Vector.Storable as V | |
| import Linear | |
| import Waterfall | |
| n = 4 -- number of profiles to interpolate into | |
| inch = 25.4 | |
| -- vent area | |
| vw = 3.5 * inch | |
| vh = 10 | |
| -- vent distance from the bottom back left corner | |
| vy = 10 -- | |
| vx = cw / 2 - 0.5 * inch | |
| t = 5 -- thickness | |
| cw = 14 * inch | |
| ch = 20 | |
| -- middle section | |
| mx = vx - 80 | |
| mw = vw * 1.8 | |
| mh = min fz (vh * 1.5) | |
| -- fan area | |
| fz = 37 -- fan plane height off the table | |
| fd = 116 -- duct diameter | |
| screwOd = 5 -- hole is 4 mm | |
| fwh = 119 -- outer square width | |
| fcc = 115 -- bolt square width | |
| fy = 40 | |
| -- sequence of lofts | |
| -- the vents are xy plane, the | |
| rect2 x y w h = | |
| (rect2i x y w h, rect2o t x y w h) | |
| & each %~ \(x : xs) -> x : (xs :> x) | |
| where | |
| rect2i x y w h = [V2 x y, V2 (x + w) y, V2 (x + w) (y + h), V2 x (y + h)] | |
| rect2o o x y w h = [V2 (x - o) (y - o), V2 (x + w + o) (y - o), V2 (x + w + o) (y + h + o), V2 (x - o) (y + h + o)] | |
| -- The vent v is in the xy plane, the middle is in a parallel plane, fan is in xz | |
| v = rect2 vx vy vw vh & each . traversed %~ \(V2 x y) -> V3 x y 0 | |
| m = | |
| rect2 mx vy mw mh | |
| & each . traversed %~ (\(V2 x y) -> V3 x y (fy * 7 / 10)) | |
| f = | |
| rect2 (-fd / 2) fy fd fd | |
| & each . traversed %~ (\(V2 x y) -> V3 x fz y) | |
| -- | same as 'loft' except the inner lists (cross sections) are rotated to | |
| -- minimize the volume of each intermediate loft. | |
| loft2 :: [[V3 Double]] -> Solid | |
| loft2 = loft . map section . loftsort | |
| loftsort :: [[V3 Double]] -> [[V3 Double]] | |
| loftsort (x : y0 : xs) = x : loftsort (ynew : xs) | |
| where | |
| yrots = init $ zipWith (++) (tails y0) (inits y0) | |
| ynew = maximumOn f yrots | |
| f y = volume $ loft [section x, section y] | |
| loftsort xs = xs | |
| maximumOn f xs = last $ sortOn f xs | |
| section :: [V3 Double] -> Path | |
| section ps = closeLoop3D $ mconcat $ zipWith line3D ps (drop 1 ps) | |
| -- vent-mid-fan | |
| -- vento-mido-fano | |
| main = do | |
| (vmfi, vmfo) <- [v, m, f] & unzip & each %%~ fmap loft2 . mapM fit3path_ | |
| writeSolid 0.1 "vmf.step" $ difference vmfo vmfi | |
| fit3path_ = return | |
| {- | |
| -- | interpolate x,y,z independently via htpl Reinsch.fit | |
| fit3path :: Range -> [V3 Double] -> IO [V3 Double] | |
| fit3path tout ps = zipWith3 V3 <$> f _x <*> f _y <*> f _z | |
| where | |
| n = length ps | |
| ts = V.generate n (\i -> fromIntegral i / fromIntegral n) | |
| f coord = map realToFrac . V.toList . snd <$> fit {tout}.call ts xs | |
| where | |
| xs = V.fromListN n (ps ^.. traversed . cloneLens coord . to realToFrac) | |
| -} |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment