module System.Console.Shell.Commands
( File (..)
, Username (..)
, Completable (..)
, Completion (..)
, showShellHelp
, showCmdHelp
, helpCommand
, exitCommand
, toggle
, cmd
, CommandFunction
, maybePrefix
, getShellCommands
, commandsRegex
) where
import System.Console.Shell.Types
import System.Console.Shell.PPrint
import System.Console.Shell.Regex
import System.Console.Shell.ShellMonad
maybePrefix :: ShellDescription st -> String
maybePrefix desc = case commandStyle desc of CharPrefixCommands x -> [x]; _ -> ""
getShellCommands :: ShellDescription st -> [(String,CommandParser st,Doc,Doc)]
getShellCommands desc = map ($ desc) (shellCommands desc)
newtype File = File String
newtype Username = Username String
newtype Completable compl = Completable String
class Completion compl st | compl -> st where
  
  
  complete :: compl -> (st -> String -> IO [String])
  
  completableLabel :: compl -> String
showShellHelp :: ShellDescription st -> String
showShellHelp desc = show (commandHelpDoc desc (getShellCommands desc)) ++ "\n"
showCmdHelp :: ShellDescription st -> String -> String
showCmdHelp desc cmd =
  case cmds of
     [_] -> show (commandHelpDoc desc cmds) ++ "\n"
     _   -> show (text "bad command name: " <> squotes (text cmd)) ++ "\n"
 where cmds = filter (\ (n,_,_,_) -> n == cmd) (getShellCommands desc)
commandHelpDoc :: ShellDescription st ->  [(String,CommandParser st,Doc,Doc)] -> Doc
commandHelpDoc desc cmds =
   vcat [ (fillBreak 20 syn) <+> msg | (_,_,syn,msg) <- cmds ]
exitCommand :: String            
            -> ShellCommand st
exitCommand name desc = ( name
                        , \_ -> [CompleteParse (shellSpecial ShellExit)]
                        , text (maybePrefix desc) <> text name
                        , text "Exit the shell"
                        )
helpCommand :: String           
            -> ShellCommand st
helpCommand name desc = ( name
                        , \_ -> [CompleteParse (shellSpecial (ShellHelp Nothing))]
                        , text (maybePrefix desc) <> text name
                        , text "Display the shell command help"
                        )
toggle :: String                
       -> String                
       -> (st -> Bool)          
       -> (Bool -> st -> st)    
       -> ShellCommand st
toggle name helpMsg getter setter desc =
     ( name
     , \_ -> [CompleteParse doToggle]
     , text (maybePrefix desc) <> text name
     , text helpMsg
     )
  where doToggle = do
          st <- getShellSt
          if getter st
             then shellPutInfoLn (name++" off") >> putShellSt (setter False st)
             else shellPutInfoLn (name++" on")  >> putShellSt (setter True  st)
cmd :: CommandFunction f st
    => String           
    -> f                
                        
    -> String           
    -> ShellCommand st
cmd name f helpMsg desc =
      ( name
      , parseCommand (wordBreakChars desc) f
      , text (maybePrefix desc) <> text name <+> hsep (commandSyntax f)
      , text helpMsg
      )
class CommandFunction f st | f -> st where
  parseCommand  :: String -> f -> CommandParser st
  commandSyntax :: f -> [Doc]
instance CommandFunction (Sh st ()) st where
  parseCommand wbc m str =
         do (x,[]) <- runRegex (maybeSpaceBefore (Epsilon (CompleteParse m))) str
            return x
  commandSyntax _ = []
instance CommandFunction r st
      => CommandFunction (Int -> r) st where
  parseCommand = doParseCommand Nothing intRegex id
  commandSyntax f = text (show intRegex) : commandSyntax (f undefined)
instance CommandFunction r st
      => CommandFunction (Integer -> r) st where
  parseCommand = doParseCommand Nothing intRegex id
  commandSyntax f =  text (show intRegex) : commandSyntax (f undefined)
instance CommandFunction r st
      => CommandFunction (Float -> r) st where
  parseCommand = doParseCommand Nothing floatRegex id
  commandSyntax f = text (show floatRegex) : commandSyntax (f undefined)
instance CommandFunction r st
      => CommandFunction (Double -> r) st where
  parseCommand = doParseCommand Nothing floatRegex id
  commandSyntax f = text (show floatRegex) : commandSyntax (f undefined)
instance CommandFunction r st
      => CommandFunction (String -> r) st where
  parseCommand wbc = doParseCommand Nothing (wordRegex wbc) id wbc
  commandSyntax f = text (show (wordRegex "")) : commandSyntax (f undefined)
instance CommandFunction r st
      => CommandFunction (File -> r) st where
  parseCommand wbc = doParseCommand
                        (Just FilenameCompleter)
                        (wordRegex wbc)
                        File
                        wbc
  commandSyntax f = text "<file>" : commandSyntax (f undefined)
instance CommandFunction r st
      => CommandFunction (Username -> r) st where
  parseCommand wbc = doParseCommand
                        (Just UsernameCompleter)
                        (wordRegex wbc)
                        Username
                        wbc
  commandSyntax f = text "<username>" : commandSyntax (f undefined)
instance (CommandFunction r st,Completion compl st)
      => CommandFunction (Completable compl -> r) st where
  parseCommand wbc =
     ( doParseCommand
          (Just (OtherCompleter (complete (undefined::compl))))
          (wordRegex wbc)
          Completable
          wbc
     ) :: (Completable compl -> r) -> CommandParser st
  commandSyntax (f:: (Completable compl -> r)) =
     text (completableLabel (undefined::compl)) : commandSyntax (f undefined)
doParseCommand compl re proj wbc f []  = return (IncompleteParse compl)
doParseCommand compl re proj wbc f str =
  let xs = runRegex (maybeSpaceBefore (maybeSpaceAfter re)) str
  in case xs of
        [] -> return (IncompleteParse compl)
        _  -> do (x,str') <- xs; parseCommand wbc (f (proj x)) str'
commandsRegex :: ShellDescription st -> Regex Char (String,CommandParser st,Doc,Doc)
commandsRegex desc =
   case commandStyle desc of
      CharPrefixCommands ch -> prefixCommandsRegex ch (getShellCommands desc)
      OnlyCommands          -> onlyCommandsRegex      (getShellCommands desc)
      SingleCharCommands    -> singleCharCommandRegex (getShellCommands desc)
onlyCommandsRegex :: [(String,CommandParser st,Doc,Doc)] -> Regex Char (String,CommandParser st,Doc,Doc)
onlyCommandsRegex xs =
    Concat (\_ x -> x) maybeSpaceRegex $
    Concat (\x _ -> x) (anyOfRegex (map (\ (x,y,z,w) -> (x,(x,y,z,w))) xs)) $
                       spaceRegex
prefixCommandsRegex :: Char -> [(String,CommandParser st,Doc,Doc)] -> Regex Char (String,CommandParser st,Doc,Doc)
prefixCommandsRegex ch xs =
    Concat (\_ x -> x) maybeSpaceRegex $
    Concat (\_ x -> x) (strTerminal ch) $
    Concat (\x _ -> x) (anyOfRegex (map (\ (x,y,z,w) -> (x,(x,y,z,w))) xs)) $
                       spaceRegex
singleCharCommandRegex :: [(String,CommandParser st,Doc,Doc)] -> Regex Char (String,CommandParser st,Doc,Doc)
singleCharCommandRegex xs =
    altProj
       (anyOfRegex (map (\ (x,y,z,w) -> ([head x],(x,y,z,w))) xs))
       (Epsilon ("",\_ -> [CompleteParse (shellSpecial ShellNothing)],empty,empty))