Shell-like syntax for interactive mode

This commit is contained in:
Nikolay Yakimov
2015-12-20 06:05:43 +03:00
parent 6d9ed9a255
commit feae07da5b
6 changed files with 126 additions and 63 deletions

View File

@@ -27,6 +27,7 @@ import Control.Arrow
import GHCMod.Options.Commands
import GHCMod.Version
import GHCMod.Options.DocUtils
import GHCMod.Options.ShellEscape
parseArgs :: IO (Options, GhcModCommands)
parseArgs =
@@ -36,9 +37,9 @@ parseArgs =
$$ fullDesc
<=> header "ghc-mod: Happy Haskell Programming"
parseArgsInteractive :: [String] -> Maybe (GhcModCommands, [String])
parseArgsInteractive :: String -> Maybe (GhcModCommands, [String])
parseArgsInteractive args =
getParseResult $ execParserPure (prefs idm) opts args
getParseResult $ execParserPure (prefs idm) opts $ parseCmdLine args
where
opts = info interactiveCommandsSpec $$ fullDesc

View File

@@ -13,8 +13,6 @@
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
{-# LANGUAGE TupleSections #-}
module GHCMod.Options.Commands where
import Options.Applicative

View File

@@ -0,0 +1,55 @@
-- ghc-mod: Making Haskell development *more* fun
-- Copyright (C) 2015 Nikolay Yakimov <root@livid.pp.ru>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
module GHCMod.Options.ShellEscape (parseCmdLine) where
import Data.Char
import Data.Maybe
isQuote :: Char -> Bool
isQuote = (`elem` "\"'")
isEscapeChar :: Char -> Bool
isEscapeChar = (==) '\\'
isEscapable :: Char -> Bool
isEscapable c = any ($ c) [isSpace, isQuote, isEscapeChar]
go :: String -> String -> [String] -> Maybe Char -> [String]
-- result
go [] curarg accargs _ = reverse $ reverse curarg : accargs
-- escaped character
go (esc:c:cl) curarg accargs quote
| isEscapeChar esc
= if isEscapable c
then go cl (c:curarg) accargs quote
else go (c:cl) ('\\':curarg) accargs quote
-- quote character -- opens quotes
go (c:cl) curarg accargs Nothing
| isQuote c = go cl curarg accargs (Just c)
-- close quotes
go (c:cl) curarg accargs (Just q)
| c == q = go cl curarg accargs Nothing
go (c:cl) curarg accargs quotes
-- space separates argumetns outside quotes
| isSpace c && isNothing quotes
= if null curarg
then go cl curarg accargs quotes
else go cl [] (reverse curarg : accargs) quotes
-- general character
| otherwise = go cl (c:curarg) accargs quotes
parseCmdLine :: String -> [String]
parseCmdLine comline = go comline [] [] Nothing