2018-06-23 22:41:51 +00:00
|
|
|
module MindMap where
|
|
|
|
|
|
|
|
import Affection as A
|
|
|
|
|
|
|
|
import Algebra.Graph as AG
|
|
|
|
|
|
|
|
import System.Random (randomRIO)
|
|
|
|
|
|
|
|
import Control.Monad (foldM)
|
|
|
|
|
|
|
|
import Linear
|
|
|
|
|
|
|
|
import qualified Data.Matrix as M
|
|
|
|
import Data.Maybe (fromJust)
|
|
|
|
import Data.List (find)
|
|
|
|
|
|
|
|
-- internal imports
|
|
|
|
|
|
|
|
import Types
|
|
|
|
|
2018-06-24 10:59:24 +00:00
|
|
|
friction :: Double
|
2018-06-25 21:46:17 +00:00
|
|
|
friction = 0.1
|
2018-06-24 10:59:24 +00:00
|
|
|
l0 :: Double
|
|
|
|
l0 = 1
|
|
|
|
springKonst :: Double
|
2018-06-23 22:41:51 +00:00
|
|
|
springKonst = 0.8 -- N/m
|
|
|
|
|
|
|
|
buildMindMap :: Int -> Word -> IO (AG.Graph MMNode)
|
|
|
|
buildMindMap num difficulty = do
|
|
|
|
mainPath <- (return . path . (MMNode (V2 0 0) 0 :)) =<< foldM
|
|
|
|
makeVert
|
|
|
|
[MMNode (V2 10 10) (-1)]
|
|
|
|
[1 .. (1 + fromIntegral difficulty)]
|
2018-06-24 10:59:24 +00:00
|
|
|
aux <- randomRIO (0, floor (fromIntegral num * 5 / 8 :: Double)) :: IO Int
|
2018-06-23 22:41:51 +00:00
|
|
|
auxPaths <- mapM (\_ -> do
|
2018-08-18 03:01:52 +00:00
|
|
|
ln <- randomRIO (0, num `div` 10)
|
2018-09-02 08:44:33 +00:00
|
|
|
path . (MMNode (V2 0 0) 0 :) <$> foldM makeVert [] [1 .. ln]
|
2018-06-23 22:41:51 +00:00
|
|
|
)
|
|
|
|
[0 .. aux]
|
|
|
|
return $ overlays (mainPath : auxPaths)
|
|
|
|
where
|
|
|
|
makeVert :: [MMNode] -> Int -> IO [MMNode]
|
|
|
|
makeVert acc a = do
|
|
|
|
vert <- randomRIO (1, num)
|
|
|
|
x <- randomRIO (4.5, 5.5) :: IO Double
|
|
|
|
y <- randomRIO (4.5, 5.5) :: IO Double
|
2018-07-19 02:51:07 +00:00
|
|
|
-- A.logIO A.Debug ("pos: " ++ show (x, y))
|
2018-06-23 22:41:51 +00:00
|
|
|
let node = MMNode (V2 x y) vert
|
|
|
|
if node `elem` acc
|
|
|
|
then makeVert acc a
|
|
|
|
else return (node : acc)
|
|
|
|
|
|
|
|
springField :: AG.Graph MMNode -> AG.Graph MMNode
|
2018-07-03 14:19:27 +00:00
|
|
|
springField =
|
|
|
|
calcul
|
2018-06-23 22:41:51 +00:00
|
|
|
where
|
|
|
|
calcul graph =
|
2018-07-19 02:51:07 +00:00
|
|
|
let deltas = calculDelta2 graph
|
2018-07-08 05:55:44 +00:00
|
|
|
in if any (\(_, v) -> len v > 1)
|
2018-07-19 02:51:07 +00:00
|
|
|
-- (A.log A.Debug ("deltas: " ++ show deltas) deltas)
|
|
|
|
deltas
|
2018-06-23 22:41:51 +00:00
|
|
|
then
|
|
|
|
let deltaNodes = map
|
|
|
|
(\n -> n { mmPos = mmPos n + snd (fromJust (find ((== mmId n) . fst) deltas))})
|
|
|
|
(vertexList graph)
|
|
|
|
ngraph = fmap (\n -> fromJust (find ((== mmId n) . mmId) deltaNodes)) graph
|
|
|
|
in -- A.log A.Debug "\n\nRECURSING\n"
|
2018-09-02 08:44:33 +00:00
|
|
|
calcul ngraph
|
2018-06-23 22:41:51 +00:00
|
|
|
else graph
|
2018-07-19 02:51:07 +00:00
|
|
|
|
|
|
|
len :: (Floating a, Metric f) => f a -> a
|
|
|
|
len v = sqrt (v `dot` v)
|
2018-07-08 05:55:44 +00:00
|
|
|
|
|
|
|
normv :: (Eq a, Floating a) => V2 a -> V2 a
|
|
|
|
normv v@(V2 0 0) = v
|
|
|
|
normv v = signorm v
|
2018-06-23 22:41:51 +00:00
|
|
|
|
2018-06-28 19:07:58 +00:00
|
|
|
buildFloorMap :: AG.Graph MMNode -> (M.Matrix Int, AG.Graph MMNode)
|
2018-06-23 22:41:51 +00:00
|
|
|
buildFloorMap inGraph =
|
2018-06-28 19:07:58 +00:00
|
|
|
( foldl
|
|
|
|
(\amat (MMNode (V2 r c) i) -> M.setElem (if i == 0 then -2 else i)
|
|
|
|
(floor r + 2, floor c + 2) amat
|
|
|
|
)
|
|
|
|
emptyFloor
|
2019-01-06 02:52:43 +00:00
|
|
|
(vertexList floorGraph)
|
2018-06-28 19:07:58 +00:00
|
|
|
, fmap (\n -> n { mmPos = (+ 2) <$> mmPos n} ) floorGraph
|
|
|
|
)
|
2018-06-23 22:41:51 +00:00
|
|
|
where
|
|
|
|
normGraph =
|
|
|
|
let minVert = V2
|
|
|
|
( minimum $ map ((\(V2 r _) -> r) . mmPos) (vertexList inGraph))
|
|
|
|
( minimum $ map ((\(V2 _ c) -> c) . mmPos) (vertexList inGraph))
|
|
|
|
maxVert = V2
|
|
|
|
( maximum $ map ((\(V2 r _) -> r) . mmPos) (vertexList redGraph))
|
|
|
|
( maximum $ map ((\(V2 _ c) -> c) . mmPos) (vertexList redGraph))
|
|
|
|
redGraph = fmap (\n -> n { mmPos = mmPos n - minVert }) inGraph
|
|
|
|
in fmap (\n -> n { mmPos = mmPos n / maxVert }) redGraph
|
2018-07-19 02:51:07 +00:00
|
|
|
floorGraph = fmap (\n -> n { mmPos = (* 45) <$> mmPos n }) normGraph
|
2018-06-23 22:41:51 +00:00
|
|
|
emptyFloor = M.matrix 50 50 (const 0)
|
2018-06-28 19:07:58 +00:00
|
|
|
|
|
|
|
manhattan :: AG.Graph MMNode -> M.Matrix Int -> M.Matrix TileState
|
|
|
|
manhattan graph input =
|
|
|
|
walls intermediate
|
|
|
|
where
|
2018-07-03 14:19:27 +00:00
|
|
|
mandistance :: (Int, Int) -> (Int, Int) -> Int
|
|
|
|
mandistance (r1, c1) (r2, c2) = abs (r1 - r2) + abs (c1 - c2)
|
2018-06-28 19:07:58 +00:00
|
|
|
dmin = M.nrows input + M.ncols input
|
2018-07-03 14:19:27 +00:00
|
|
|
calculate (r, c) = foldl (\acc@(accdmin, _) (MMNode (V2 vr vc) ind) ->
|
|
|
|
let d = mandistance (r, c) (floor vr, floor vc)
|
2018-06-28 19:07:58 +00:00
|
|
|
in if d < accdmin
|
|
|
|
then (d, ind)
|
|
|
|
else acc
|
2018-07-03 14:19:27 +00:00
|
|
|
) (dmin, 0) verts
|
|
|
|
verts = vertexList graph
|
2018-06-28 19:07:58 +00:00
|
|
|
coords = (,) <$> [1 .. M.nrows input] <*> [1 .. M.ncols input]
|
|
|
|
intermediate = M.matrix (M.nrows input) (M.ncols input) (snd . calculate)
|
|
|
|
walls inter = foldl (\accmat (r, c) ->
|
2018-07-03 14:19:27 +00:00
|
|
|
wallnotwall inter accmat r c
|
2018-06-28 19:07:58 +00:00
|
|
|
) emptyMM coords
|
|
|
|
emptyMM = M.matrix (M.nrows input) (M.ncols input) (const Offi)
|
|
|
|
wallnotwall inter mat r c
|
|
|
|
| M.safeGet (r - 1) (c - 1) mat /= Just Wall &&
|
|
|
|
M.safeGet r (c - 1) mat == Just Wall &&
|
|
|
|
M.safeGet (r - 1) c mat == Just Wall = M.setElem Wall (r, c) mat
|
|
|
|
| (M.safeGet r (c - 1) inter /= M.safeGet r c inter) &&
|
|
|
|
(M.safeGet r (c - 1) mat /= Just Wall) = M.setElem Wall (r, c) mat
|
|
|
|
| (M.safeGet (r - 1) c inter /= M.safeGet r c inter) &&
|
|
|
|
(M.safeGet (r - 1) c mat /= Just Wall) = M.setElem Wall (r, c) mat
|
|
|
|
| (M.safeGet r (c + 1) inter /= M.safeGet r c inter) &&
|
|
|
|
(M.safeGet r (c + 1) mat /= Just Wall) = M.setElem Wall (r, c) mat
|
|
|
|
| (M.safeGet (r + 1) c inter /= M.safeGet r c inter) &&
|
|
|
|
(M.safeGet (r + 1) c mat /= Just Wall) = M.setElem Wall (r, c) mat
|
|
|
|
| otherwise = mat
|
2018-07-08 05:55:44 +00:00
|
|
|
|
|
|
|
calculDelta2 :: AG.Graph MMNode -> [(Int, V2 Double)]
|
|
|
|
calculDelta2 graph =
|
|
|
|
let accel2 = sproing2 (zip (vertexList graph) (repeat $ V2 0 0))
|
|
|
|
sproing2 [] = []
|
|
|
|
sproing2 ((cnode, cacc):nodeaccs) =
|
|
|
|
( mmId cnode
|
2018-09-02 08:44:33 +00:00
|
|
|
, if len (V2 100 100 * normv deltasum) < len deltasum
|
2018-07-08 05:55:44 +00:00
|
|
|
then V2 100 100 * normv deltasum
|
|
|
|
else deltasum
|
|
|
|
) : sproing2 dnodeaccs
|
|
|
|
where
|
|
|
|
deltasum = cacc + sum deltas
|
2018-09-02 08:44:33 +00:00
|
|
|
deltas = map (fmap (* friction) . doForce) (map fst nodeaccs)
|
2018-07-08 05:55:44 +00:00
|
|
|
doForce n
|
|
|
|
-- are the nodes identic? (unlikely)
|
|
|
|
| mmId cnode == mmId n =
|
|
|
|
V2 0 0
|
|
|
|
-- Is the cnode pointing to the currently mapped node?
|
|
|
|
| n `elem` map snd (filter ((== cnode) . fst) $ edgeList graph) =
|
|
|
|
fmap (* (springKonst * (distance (mmPos n) (mmPos cnode) - l0)))
|
|
|
|
(normv (mmPos n - mmPos cnode))
|
|
|
|
-- Is the cnode being pointed to from the currently mapped node?
|
|
|
|
| cnode `elem` map snd (filter ((== n) . fst) $ edgeList graph) =
|
|
|
|
- fmap (* (springKonst * (distance (mmPos n) (mmPos cnode) - l0)))
|
|
|
|
(normv (mmPos cnode - mmPos n))
|
|
|
|
-- Do gravitational push in all other cases
|
|
|
|
| otherwise =
|
2018-09-02 08:44:33 +00:00
|
|
|
- fmap (* (1000 / (distance (mmPos cnode) (mmPos n)) ^ (2 :: Int)))
|
2018-07-08 05:55:44 +00:00
|
|
|
(normv (mmPos n - mmPos cnode))
|
|
|
|
dnodeaccs = zipWith (\(n, a) d -> (n, a - d)) nodeaccs deltas
|
|
|
|
in accel2
|