evac/Groups.hs

77 lines
2.5 KiB
Haskell
Raw Normal View History

2019-05-18 23:56:48 -04:00
module Groups where
import Util
import Types
-- Each characters default adjacents
defFrens :: MainCharacter -> [MainCharacter]
defFrens Asuka = [Rei, Shinji, Misato]
defFrens Shinji = [Rei, Gendo, Ritsuko, Misato, Asuka]
defFrens Rei = [Gendo, Shinji, Asuka]
defFrens Misato = [Asuka, Shinji, Ritsuko]
defFrens Ritsuko = [Misato, Shinji, Gendo]
defFrens Gendo = [Rei, Shinji, Ritsuko]
2019-05-19 00:55:53 -04:00
-- Return true if charater is downed
isDowned :: MainCharacter -> Downed -> Bool
isDowned c d = c `elem` d
-- Return true if character is not grouped
isAlone :: MainCharacter -> Groups -> Bool
isAlone c g = curFrens c g == []
-- Return true if X is adjacent to Y
isAdjacent :: MainCharacter -> MainCharacter -> Groups -> Bool
2019-05-19 02:11:40 -04:00
isAdjacent x y g = y `elem` (getAdj x g)
2019-05-19 00:55:53 -04:00
-- All characters a X is adjacent to
getAdj :: MainCharacter -> Groups -> [MainCharacter]
getAdj x g = curFrens x g ++ (foldr (++) [] (adjGroups x g))
2019-05-18 23:56:48 -04:00
-- The characters currently grouped with x
2019-05-19 00:55:53 -04:00
curFrens :: MainCharacter -> Groups -> [MainCharacter]
curFrens x g = filter (/= x) $ charsGroup x g
2019-05-18 23:56:48 -04:00
2019-05-19 00:55:53 -04:00
-- The group that character x belongs to
charsGroup :: MainCharacter -> Groups -> Group
charsGroup x g = head $ filter (\y -> x `elem` y) g
2019-05-18 23:56:48 -04:00
-- The groups a character isnt in
2019-05-19 00:55:53 -04:00
otherGroups :: MainCharacter -> Groups -> Groups
otherGroups x g = filter (\y -> not $ x `elem` y) g
2019-05-18 23:56:48 -04:00
2019-05-19 00:55:53 -04:00
-- The groups a character is adaject to
adjGroups :: MainCharacter -> Groups -> Groups
adjGroups x g = filter (\y -> any (\z -> z `elem` adjFrens) y) (otherGroups x g)
where
adjFrens = uniq $ foldr (++) [] (map defFrens $ charsGroup x g)
-- The groups a group is adjacent to
neighborGroups :: Group -> Groups -> Groups
neighborGroups g gs = uniq . concat $ map (\x -> adjGroups x gs) g
2019-05-19 00:55:53 -04:00
-- Return the groups with C removed from its current group
removeFromGroup :: MainCharacter -> Groups -> Groups
2019-05-19 02:11:40 -04:00
removeFromGroup c g = ( [c] : (groupMinusChar c) : (otherGroups c g) )
where
groupMinusChar x = curFrens x g
2019-05-18 23:56:48 -04:00
2019-05-19 02:11:40 -04:00
-- Return the groups with X grouped with Y
joinGroups :: MainCharacter -> MainCharacter -> Groups -> Groups
joinGroups x y g
| x `elem` curFrens y g = g
| otherwise = (groupX ++ groupY) : (otherGroups x . otherGroups y) g
2019-05-18 23:56:48 -04:00
where
2019-05-19 02:11:40 -04:00
groupX = charsGroup x g
groupY = charsGroup y g
-- Return the Downed with the new character
downChar :: MainCharacter -> Downed -> Downed
downChar c d
| c `elem` d = d
| otherwise = (c : d)
2019-05-18 23:56:48 -04:00
2019-05-19 02:11:40 -04:00
-- Return the Downed minus the chosen character
readyChar :: MainCharacter -> Downed -> Downed
readyChar c d = filter (/= c) d