module Language.Docker.Parser.Expose
  ( parseExpose,
  )
where

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

parseExpose :: (?esc :: Char) => Parser (Instruction Text)
parseExpose :: Parser (Instruction Text)
parseExpose = do
  (?esc::Char) => Text -> Parser ()
Text -> Parser ()
reserved Text
"EXPOSE"
  Ports -> Instruction Text
forall args. Ports -> Instruction args
Expose (Ports -> Instruction Text)
-> ParsecT DockerfileError Text Identity Ports
-> Parser (Instruction Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT DockerfileError Text Identity Ports
(?esc::Char) => ParsecT DockerfileError Text Identity Ports
ports

port :: (?esc :: Char) => Parser Port
port :: Parser Port
port = (Parser Port -> Parser Port
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser Port
(?esc::Char) => Parser Port
portVariable Parser Port -> String -> Parser Port
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"a variable")
    Parser Port -> Parser Port -> Parser Port
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Port -> Parser Port
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser Port
portRange Parser Port -> String -> Parser Port
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"a port range optionally followed by the protocol (udp/tcp)") -- There a many valid representations of ports
    Parser Port -> Parser Port -> Parser Port
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Port -> Parser Port
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser Port
portWithProtocol Parser Port -> String -> Parser Port
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"a port with its protocol (udp/tcp)")
    Parser Port -> Parser Port -> Parser Port
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Port
portInt Parser Port -> String -> Parser Port
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"a valid port number")

ports :: (?esc :: Char) => Parser Ports
ports :: ParsecT DockerfileError Text Identity Ports
ports = [Port] -> Ports
Ports ([Port] -> Ports)
-> ParsecT DockerfileError Text Identity [Port]
-> ParsecT DockerfileError Text Identity Ports
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Port
(?esc::Char) => Parser Port
port Parser Port
-> Parser () -> ParsecT DockerfileError Text Identity [Port]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepEndBy` Parser ()
(?esc::Char) => Parser ()
requiredWhitespace

portRange :: Parser Port
portRange :: Parser Port
portRange = do
  Integer
start <- Parser Integer
natural
  ParsecT DockerfileError Text Identity Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT DockerfileError Text Identity Char -> Parser ())
-> ParsecT DockerfileError Text Identity Char -> Parser ()
forall a b. (a -> b) -> a -> b
$ Token Text -> ParsecT DockerfileError Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'-'
  Integer
finish <- Parser Integer -> Parser Integer
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser Integer
natural
  Protocol
proto <- ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT DockerfileError Text Identity Protocol
protocol ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Protocol -> ParsecT DockerfileError Text Identity Protocol
forall (m :: * -> *) a. Monad m => a -> m a
return Protocol
TCP
  Port -> Parser Port
forall (m :: * -> *) a. Monad m => a -> m a
return (Port -> Parser Port) -> Port -> Parser Port
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Protocol -> Port
PortRange (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
start) (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
finish) Protocol
proto

protocol :: Parser Protocol
protocol :: ParsecT DockerfileError Text Identity Protocol
protocol = do
  ParsecT DockerfileError Text Identity Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Token Text -> ParsecT DockerfileError Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'/')
  ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT DockerfileError Text Identity Protocol
tcp ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT DockerfileError Text Identity Protocol
udp) ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String -> ParsecT DockerfileError Text Identity Protocol
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"invalid protocol"
  where
    tcp :: ParsecT DockerfileError Text Identity Protocol
tcp = Text -> Parser Text
caseInsensitiveString Text
"tcp" Parser Text
-> ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Protocol -> ParsecT DockerfileError Text Identity Protocol
forall (m :: * -> *) a. Monad m => a -> m a
return Protocol
TCP
    udp :: ParsecT DockerfileError Text Identity Protocol
udp = Text -> Parser Text
caseInsensitiveString Text
"udp" Parser Text
-> ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Protocol -> ParsecT DockerfileError Text Identity Protocol
forall (m :: * -> *) a. Monad m => a -> m a
return Protocol
UDP

portInt :: Parser Port
portInt :: Parser Port
portInt = do
  Integer
portNumber <- Parser Integer
natural
  Parser Text -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Tokens Text -> ParsecT DockerfileError Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"/" Parser Text -> Parser Text -> Parser Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Tokens Text -> ParsecT DockerfileError Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"-")
  Port -> Parser Port
forall (m :: * -> *) a. Monad m => a -> m a
return (Port -> Parser Port) -> Port -> Parser Port
forall a b. (a -> b) -> a -> b
$ Int -> Protocol -> Port
Port (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
portNumber) Protocol
TCP

portWithProtocol :: Parser Port
portWithProtocol :: Parser Port
portWithProtocol = do
  Integer
portNumber <- Parser Integer
natural
  Int -> Protocol -> Port
Port (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
portNumber) (Protocol -> Port)
-> ParsecT DockerfileError Text Identity Protocol -> Parser Port
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT DockerfileError Text Identity Protocol
protocol

portVariable :: (?esc :: Char) => Parser Port
portVariable :: Parser Port
portVariable = do
  ParsecT DockerfileError Text Identity Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Token Text -> ParsecT DockerfileError Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'$')
  Text
variable <- (?esc::Char) => String -> (Char -> Bool) -> Parser Text
String -> (Char -> Bool) -> Parser Text
someUnless String
"the variable name" (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'$')
  Port -> Parser Port
forall (m :: * -> *) a. Monad m => a -> m a
return (Port -> Parser Port) -> Port -> Parser Port
forall a b. (a -> b) -> a -> b
$ Text -> Port
PortStr (Text -> Text -> Text
T.append Text
"$" Text
variable)