about summary refs log tree commit diff
path: root/src/Xanthous/Command.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Xanthous/Command.hs')
-rw-r--r--src/Xanthous/Command.hs39
1 files changed, 24 insertions, 15 deletions
diff --git a/src/Xanthous/Command.hs b/src/Xanthous/Command.hs
index 94c8075b34..19c5e17e0a 100644
--- a/src/Xanthous/Command.hs
+++ b/src/Xanthous/Command.hs
@@ -1,30 +1,39 @@
+{-# LANGUAGE ViewPatterns #-}
+--------------------------------------------------------------------------------
 module Xanthous.Command where
-
-import Graphics.Vty.Input (Key(..), Modifier(..))
-
+--------------------------------------------------------------------------------
 import Xanthous.Prelude hiding (Left, Right, Down)
+--------------------------------------------------------------------------------
+import Graphics.Vty.Input (Key(..), Modifier(..))
+--------------------------------------------------------------------------------
 import Xanthous.Data (Direction(..))
+--------------------------------------------------------------------------------
 
 data Command
   = Quit
   | Move Direction
   | PreviousMessage
   | PickUp
+  | Open
 
 commandFromKey :: Key -> [Modifier] -> Maybe Command
 commandFromKey (KChar 'q') [] = Just Quit
-
-commandFromKey (KChar 'h') [] = Just $ Move Left
-commandFromKey (KChar 'j') [] = Just $ Move Down
-commandFromKey (KChar 'k') [] = Just $ Move Up
-commandFromKey (KChar 'l') [] = Just $ Move Right
-commandFromKey (KChar 'y') [] = Just $ Move UpLeft
-commandFromKey (KChar 'u') [] = Just $ Move UpRight
-commandFromKey (KChar 'b') [] = Just $ Move DownLeft
-commandFromKey (KChar 'n') [] = Just $ Move DownRight
-
+commandFromKey (KChar (directionFromChar -> Just dir)) [] = Just $ Move dir
 commandFromKey (KChar 'p') [MCtrl] = Just PreviousMessage
-
 commandFromKey (KChar ',') [] = Just PickUp
-
+commandFromKey (KChar 'o') [] = Just Open
 commandFromKey _ _ = Nothing
+
+--------------------------------------------------------------------------------
+
+directionFromChar :: Char -> Maybe Direction
+directionFromChar 'h' = Just Left
+directionFromChar 'j' = Just Down
+directionFromChar 'k' = Just Up
+directionFromChar 'l' = Just Right
+directionFromChar 'y' = Just UpLeft
+directionFromChar 'u' = Just UpRight
+directionFromChar 'b' = Just DownLeft
+directionFromChar 'n' = Just DownRight
+directionFromChar '.' = Just Here
+directionFromChar _   = Nothing