module Language.Docker.Parser.Arguments
  ( arguments,
  )
where

import qualified Data.Text as T
import Language.Docker.Parser.Prelude
import Language.Docker.Syntax

-- Parse arguments of a command in the exec form
argumentsExec :: (?esc :: Char) => Parser (Arguments Text)
argumentsExec :: Parser (Arguments Text)
argumentsExec = do
  [Text]
args <- Parser [Text] -> Parser [Text]
forall a. (?esc::Char) => Parser a -> Parser a
brackets (Parser [Text] -> Parser [Text]) -> Parser [Text] -> Parser [Text]
forall a b. (a -> b) -> a -> b
$ Parser Text -> Parser [Text]
forall a. (?esc::Char) => Parser a -> Parser [a]
commaSep Parser Text
stringLiteral
  Arguments Text -> Parser (Arguments Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Arguments Text -> Parser (Arguments Text))
-> Arguments Text -> Parser (Arguments Text)
forall a b. (a -> b) -> a -> b
$ Text -> Arguments Text
forall args. args -> Arguments args
ArgumentsList ([Text] -> Text
T.unwords [Text]
args)

-- Parse arguments of a command in the shell form
argumentsShell :: (?esc :: Char) => Parser (Arguments Text)
argumentsShell :: Parser (Arguments Text)
argumentsShell = Text -> Arguments Text
forall args. args -> Arguments args
ArgumentsText (Text -> Arguments Text) -> Parser Text -> Parser (Arguments Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text
toEnd
  where
    toEnd :: Parser Text
toEnd = (?esc::Char) => String -> Parser Text
String -> Parser Text
untilEol String
"the shell arguments"

arguments :: (?esc :: Char) => Parser (Arguments Text)
arguments :: Parser (Arguments Text)
arguments = Parser (Arguments Text) -> Parser (Arguments Text)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser (Arguments Text)
(?esc::Char) => Parser (Arguments Text)
argumentsExec Parser (Arguments Text)
-> Parser (Arguments Text) -> Parser (Arguments Text)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser (Arguments Text) -> Parser (Arguments Text)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser (Arguments Text)
(?esc::Char) => Parser (Arguments Text)
argumentsShell