module Tile where import Terminal.Game data Tile = Tile { tType :: TileType, tAnimation :: Animation } deriving (Show, Eq) -- Keep then in alphabetical order. Complete every function in this -- module. data TileType = Background | ColRed | ColGreen | ColYellow | ColBlue | ColPurple | ColCerulean | Floor | Heaven | Invisible | Ladder | Prop | Solid | Slow | Spike | Thick | Transparent | Water deriving (Eq, Show) tilePlane :: Tile -> Plane tilePlane t = fetchFrame . tAnimation $ t charTile :: Char -> Maybe Tile charTile '.' = creaSipTile Background (cell '.') charTile 'R' = creaSipTile ColRed (cell '.' # color Red Vivid) charTile 'G' = creaSipTile ColGreen (cell '.' # color Green Vivid) charTile 'Y' = creaSipTile ColYellow (cell '.' # color Yellow Vivid) charTile 'B' = creaSipTile ColBlue (cell '.' # color Blue Vivid) charTile 'P' = creaSipTile ColPurple (cell '.' # color Magenta Vivid) charTile 'C' = creaSipTile ColCerulean (cell '.' # color Cyan Vivid) charTile '-' = creaSipTile Floor (cell '-' # bold) charTile 'i' = creaSipTile Invisible (cell ' ') charTile '|' = creaSipTile Ladder (cell '|') charTile 'S' = creaSipTile Slow (cell '.') charTile ':' = creaSipTile Solid (cell ':') charTile 'A' = creaSipTile Spike (cell 'A' # color Cyan Vivid # bold) charTile '=' = creaSipTile Thick (cell '=') charTile 'x' = creaSipTile Transparent (cell ' ') -- no prop, since there is no single char charTile 'w' = creaSipTile Water (cell '~' # color Blue Dull) charTile '~' = let n = 5 ha = creaLoopAnimation [(n*3, cell '~' # color Black Dull), (n , cell '~' # color Blue Vivid), (n , cell '~' # color Yellow Vivid), (n*3, cell '~' # color White Vivid), (n , cell '~' # color Yellow Vivid), (n , cell '~' # color Blue Vivid)] in Just $ Tile Heaven ha -- prop plus charTile 'q' = Just $ creaPropPlus 'a' (color Red Vivid) charTile 'h' = Just $ creaPropPlus 'f' (\p -> p # color Green Dull # bold # invert) charTile _ = Nothing creaProp :: Char -> Tile creaProp c = Tile Prop (creaStaticAnimation $ cell c) type Colour = Plane -> Plane creaPropPlus :: Char -> Colour -> Tile creaPropPlus k c = Tile Prop (creaStaticAnimation $ cell k # c) creaSipTile :: TileType -> Plane -> Maybe Tile creaSipTile tt p = Just $ Tile tt (creaStaticAnimation p) tickTile :: Tile -> Tile tickTile (Tile tt a) = Tile tt (tick a) ---------------- -- PROPERTIES -- ---------------- isSolid :: TileType -> Bool isSolid Floor = True isSolid Heaven = True isSolid Invisible = True isSolid Solid = True isSolid Thick = True isSolid _ = False isGround :: TileType -> Bool isGround Floor = True isGround Ladder = True isGround t = isSolid t