From 0ee05c63d5c022acb50065d6333fe56069be4d03 Mon Sep 17 00:00:00 2001 From: Andrew Cady Date: Fri, 15 Mar 2019 16:58:54 -0400 Subject: fill out stubbed code based on existing code also removed the unused definition --- shelves.hs | 113 +++++++++++++++++++++---------------------------------------- 1 file changed, 38 insertions(+), 75 deletions(-) diff --git a/shelves.hs b/shelves.hs index 6ed051a..0ea28ee 100644 --- a/shelves.hs +++ b/shelves.hs @@ -1,93 +1,56 @@ +{-# LANGUAGE RecordWildCards #-} import Control.Lens import Graphics.OpenSCAD import Linear.V3 genscad :: [(V3 Double, V3 Double)] -> String -genscad = render . union . map transBox - where - transBox :: (V3 Double, V3 Double) -> Model3d - transBox (V3 x1 y1 z1, V3 x2 y2 z2) = translate (x1,y1,z1) $ box x2 y2 z2 - -data Shelf - -myShelf :: Shelf -myShelf = undefined - -modelShelf :: Shelf -> Model3d -modelShelf = undefined - -main :: IO () -main = draw $ modelShelf myShelf - -shelf_thickness :: Double -shelf_thickness = 0.5 -shelf_width :: Double -shelf_width = 8 -shelf_length :: Double -shelf_length = 36 * 2 -shelf_dim :: V3 Double -shelf_dim = V3 shelf_length shelf_width shelf_thickness - -shelf_heights :: [Double] -shelf_heights = [12, 10, 8, 8, 8, 8, 8] - --- working algorithm doing the same as `scanl (+) 0 shelf_heights` ---acc [] = [0] ---acc xs = acc(init xs) ++ [sum xs] - -shelf_height :: Double -shelf_height = (sum shelf_heights) + (shelf_dim ^. _z * (fromIntegral (length shelf_heights) + 1)) +genscad = render . transBoxes -side_dim :: V3 Double -side_dim = V3 0.5 shelf_width shelf_height +transBoxes :: [(V3 Double, V3 Double)] -> Model Vector3d +transBoxes = union . map transBox ---shelf_y_poss = scanl (+) 0 shelf_heights -shelf_y_poss :: [Double] -shelf_y_poss = scanl (+) 0 [h+shelf_thickness| h <- shelf_heights] -shelves_pos :: [V3 Double] -shelves_pos = [V3 (side_dim ^. _x) 0 y | y <- shelf_y_poss] -shelves :: [(V3 Double, V3 Double)] -shelves = [(p, shelf_dim) | p <- shelves_pos] +transBox :: (V3 Double, V3 Double) -> Model3d +transBox (V3 x1 y1 z1, V3 x2 y2 z2) = translate (x1,y1,z1) $ box x2 y2 z2 ---sides = [(V3 0 0 0, side_dim), (V3 (side_dim ^. _x + shelf_length) 0 0, side_dim)] -sides_pos :: [V3 Double] -sides_pos = [V3 0 0 0, V3 (side_dim ^. _x + shelf_length) 0 0] -sides :: [(V3 Double, V3 Double)] -sides = [(p, side_dim) | p <- sides_pos] +type Inches = Double ---V3_to_string v = drop 3 (show v) +data Shelf = Shelf { + shelfThickness :: Inches, + shelfWidth :: Inches, + shelfLength :: Inches, + shelfHeights :: [Inches], + shelfSideDimX :: Inches +} ---scad_place (p,d) = "translate([ " ++ _V32s(p) ++ " ]) { cube([ " ++ _V32s(d) ++ " ]);}" ---genscad objs = concat $ map (++ "\n") $ map scad_place objs +shelfDim :: Shelf -> V3 Inches +shelfDim Shelf{..} = V3 shelfLength shelfWidth shelfThickness -scadshelf :: String -scadshelf = genscad $ shelves ++ sides - ---gen_shelf :: [Fractional] -> Fractional -> Fractional -> [Char] ---gen_shelf shelf_heights depth length = - - - --- main :: IO () --- main = do putStrLn scadshelf - - - ---main = map (putStrLn) ["one", "two"] - ---genshelf = genscad $ shelves ++ sides +shelves' :: Shelf -> [(V3 Double, V3 Double)] +shelves' s@Shelf{..} = [(p, shelfDim s) | p <- shelvesPos] + where + shelfHeight = (sum shelfHeights) + (shelfDim s ^. _z * (fromIntegral (length shelfHeights) + 1)) ---main = map print $ gen_scad $ shelves ++ sides + shelfSideDim :: V3 Inches + shelfSideDim = V3 shelfSideDimX shelfWidth shelfHeight ---scad_place_sides = map (scad_place_board) [[[V3 0 0 0], side_dim], [[V3 side_dim ^. _x, 0, 0], side_dim]] + shelfYPos :: [Inches] + shelfYPos = scanl (+) 0 [h+shelfThickness| h <- shelfHeights] ---scad_place_shelf vpos = scad_place_board show([0, vpos, 0]) show(shelfd) + shelvesPos :: [V3 Double] + shelvesPos = [V3 (shelfSideDim ^. _x) 0 y | y <- shelfYPos] +myShelf :: Shelf +myShelf = Shelf { + shelfThickness = 0.5, + shelfWidth = 8, + shelfLength = 36 * 2, + shelfHeights = [12, 10, 8, 8, 8, 8, 8], + shelfSideDimX = 0.5 +} ---genscad shelves ++ sides +modelShelf :: Shelf -> Model3d +modelShelf = transBoxes . shelves' ---gen_openscad = map (scad_place_piece +main :: IO () +main = draw $ modelShelf myShelf ---accu [x] = x ---accu xs = sum(xs) ++ accu(tail xs) --- OUTPUT: [0,5,8,10] -- cgit v1.2.3