module Utils where import Debug.Trace debug = False debugLineSearch = False debugObj = False -- turn on/off output in obj fn or constraint -- used when sampling the inital state, make sure sizes satisfy subset constraints subsetSizeDiff :: Floating a => a subsetSizeDiff = 10.0 epsd :: Floating a => a -- to prevent 1/0 (infinity). put it in the denominator epsd = 10 ** (-10) halfDiagonal :: (Floating a) => a -> a halfDiagonal side = 0.5 * dist (0, 0) (side, side) labelName :: String -> String labelName name = "Label_" ++ name -- Some debugging functions. @@@ debugF :: (Show a) => a -> a debugF x = if debug then traceShowId x else x debugXY x1 x2 y1 y2 = if debug then trace (show x1 ++ " " ++ show x2 ++ " " ++ show y1 ++ " " ++ show y2 ++ "\n") else id -- To send output to a file, do ./EXECUTABLE 2> FILE.txt tr :: Show a => String -> a -> a tr s x = if debug then trace "---" $ trace s $ traceShowId x else x -- prints in left to right order trRaw :: Show a => String -> a -> a trRaw s x = if debug then trace "---" $ trace s $ trace (show x ++ "\n") x else x-- prints in left to right order trStr :: String -> a -> a trStr s x = if debug then trace "---" $ trace s x else x -- prints in left to right order tr' :: Show a => String -> a -> a tr' s x = if debugLineSearch then trace "---" $ trace s $ traceShowId x else x -- prints in left to right order tro :: Show a => String -> a -> a tro s x = if debugObj then trace "---" $ trace s $ traceShowId x else x -- prints in left to right order ---- Lists-as-vectors utility functions, TODO split out of file -- define operator precedence: higher precedence = evaluated earlier infixl 6 +., -. infixl 7 *. -- .*, /. -- assumes lists are of the same length dotL :: Floating a => [a] -> [a] -> a dotL u v = if not $ length u == length v then error $ "can't dot-prod different-len lists: " ++ (show $ length u) ++ " " ++ (show $ length v) else sum $ zipWith (*) u v (+.) :: Floating a => [a] -> [a] -> [a] -- add two vectors (+.) u v = if not $ length u == length v then error $ "can't add different-len lists: " ++ (show $ length u) ++ " " ++ (show $ length v) else zipWith (+) u v (-.) :: Floating a => [a] -> [a] -> [a] -- subtract two vectors (-.) u v = if not $ length u == length v then error $ "can't subtract different-len lists: " ++ (show $ length u) ++ " " ++ (show $ length v) else zipWith (-) u v negL :: Floating a => [a] -> [a] negL = map negate (*.) :: Floating a => a -> [a] -> [a] -- multiply by a constant (*.) c v = map ((*) c) v norm :: Floating a => [a] -> a norm = sqrt . sum . map (^ 2) normsq :: Floating a => [a] -> a normsq = sum . map (^ 2) normalize :: Floating a => [a] -> [a] normalize v = (1 / norm v) *. v -- Find the angle between x-axis and a line passing points, reporting in radians findAngle :: Floating a => (a, a) -> (a, a) -> a findAngle (x1, y1) (x2, y2) = atan $ (y2 - y1) / (x2 - x1) midpoint :: Floating a => (a, a) -> (a, a) -> (a, a) -- mid point midpoint (x1, y1) (x2, y2) = ((x1 + x2) / 2, (y1 + y2) / 2) dist :: Floating a => (a, a) -> (a, a) -> a -- distance dist (x1, y1) (x2, y2) = sqrt ((x1 - x2)^2 + (y1 - y2)^2) distsq :: Floating a => (a, a) -> (a, a) -> a -- distance distsq (x1, y1) (x2, y2) = (x1 - x2)^2 + (y1 - y2)^2