module Invert where import Types -- Inverting back to front. class Invertable a where invert :: a -> a instance Invertable Direction where invert DLeft = DRight invert DRight = DLeft invert DUp = DDown invert DDown = DUp invert DDive =DDive instance Invertable Segment where invert s = s { segmentDirection = invert (segmentDirection s) } -- Head moves to the position of the last tail segment, which moves to the -- position of the head. The body is reversed. -- -- If the final tail segment is inside the scroll, avoid putting the head -- there. In this case, the worm technically gets 1 segment shorter, -- but it's one that cannot be seen. instance Invertable Player where invert p = go $ reverse $ map invert $ playerBody p where go [] = p go (t:bs) | segmentSide t == InSide = go bs | otherwise = repoint $ p { playerHead = getPos t , playerBody = bs ++ [t { segmentPos = playerHead p }] } -- Ensures that each segment after the last consistently points to -- the next segment (assuming the next segment is actually touching it; -- segments may somehow be off elsewhere in the map. The first segment -- is repointed at the head. repoint :: Player -> Player repoint p = p { playerBody = map go (zip (playerBody p) (playerHead p : map getPos (playerBody p))) } where go (s, nextpos) = case finddir (getPos s) nextpos of Nothing -> s Just d -> s { segmentDirection = d } finddir from to = case filter (\d -> offsetPos (directionOffset d) from == to) [minBound..maxBound] of [] -> Nothing (d:_) -> Just d