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 :: (?esc::Char) => 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

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

portspec :: (?esc :: Char) => Parser PortSpec
portspec :: (?esc::Char) => Parser PortSpec
portspec =
  ( Parser PortSpec -> Parser PortSpec
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser PortSpec
(?esc::Char) => Parser PortSpec
parsePortRangeSpec Parser PortSpec -> String -> Parser PortSpec
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"A range of ports optionally followed by the protocol" )
    Parser PortSpec -> Parser PortSpec -> Parser PortSpec
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ( Parser PortSpec
(?esc::Char) => Parser PortSpec
parsePortSpec Parser PortSpec -> String -> Parser PortSpec
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"A port optionally followed by the protocol" )

parsePortRangeSpec :: (?esc :: Char) => Parser PortSpec
parsePortRangeSpec :: (?esc::Char) => Parser PortSpec
parsePortRangeSpec = PortRange -> PortSpec
PortRangeSpec (PortRange -> PortSpec)
-> ParsecT DockerfileError Text Identity PortRange
-> Parser PortSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT DockerfileError Text Identity PortRange
(?esc::Char) => ParsecT DockerfileError Text Identity PortRange
portRange

parsePortSpec :: (?esc :: Char) => Parser PortSpec
parsePortSpec :: (?esc::Char) => Parser PortSpec
parsePortSpec = Port -> PortSpec
PortSpec (Port -> PortSpec)
-> ParsecT DockerfileError Text Identity Port -> Parser PortSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT DockerfileError Text Identity Port
(?esc::Char) => ParsecT DockerfileError Text Identity Port
port

port :: (?esc :: Char) => Parser Port
port :: (?esc::Char) => ParsecT DockerfileError Text Identity Port
port = (ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT DockerfileError Text Identity Port
(?esc::Char) => ParsecT DockerfileError Text Identity Port
portVariable ParsecT DockerfileError Text Identity Port
-> String -> ParsecT DockerfileError Text Identity Port
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"a variable")
    ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT DockerfileError Text Identity Port
portWithProtocol ParsecT DockerfileError Text Identity Port
-> String -> ParsecT DockerfileError Text Identity Port
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"a port with its protocol (udp/tcp)")
    ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ParsecT DockerfileError Text Identity Port
portInt ParsecT DockerfileError Text Identity Port
-> String -> ParsecT DockerfileError Text Identity Port
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"a valid port number")

portRangeLimit :: (?esc :: Char) => Parser Port
portRangeLimit :: (?esc::Char) => ParsecT DockerfileError Text Identity Port
portRangeLimit = ParsecT DockerfileError Text Identity Port
number ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT DockerfileError Text Identity Port
variable
  where
    number :: ParsecT DockerfileError Text Identity Port
number = do
      Integer
num <- Parser Integer
natural
      Port -> ParsecT DockerfileError Text Identity Port
forall a. a -> ParsecT DockerfileError Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Port -> ParsecT DockerfileError Text Identity Port)
-> Port -> ParsecT DockerfileError Text Identity 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
num) Protocol
TCP

    variable :: ParsecT DockerfileError Text Identity Port
variable = 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
var <- (?esc::Char) => String -> (Char -> Bool) -> Parser Text
String -> (Char -> Bool) -> Parser Text
someUnless String
"the variable name" (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/')
      Port -> ParsecT DockerfileError Text Identity Port
forall a. a -> ParsecT DockerfileError Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Port -> ParsecT DockerfileError Text Identity Port)
-> Port -> ParsecT DockerfileError Text Identity Port
forall a b. (a -> b) -> a -> b
$ Text -> Port
PortStr (Text -> Text -> Text
T.append Text
"$" Text
var)

portRange :: (?esc :: Char) => Parser PortRange
portRange :: (?esc::Char) => ParsecT DockerfileError Text Identity PortRange
portRange = do
  Port
start <- ParsecT DockerfileError Text Identity Port
(?esc::Char) => ParsecT DockerfileError Text Identity Port
portRangeLimit
  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
'-'
  Port
finish <- ParsecT DockerfileError Text Identity Port
-> ParsecT DockerfileError Text Identity Port
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT DockerfileError Text Identity Port
(?esc::Char) => ParsecT DockerfileError Text Identity Port
portRangeLimit
  Protocol
proto <- ParsecT DockerfileError Text Identity Protocol
-> ParsecT DockerfileError Text Identity Protocol
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
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 a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Protocol -> ParsecT DockerfileError Text Identity Protocol
forall a. a -> ParsecT DockerfileError Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return Protocol
TCP
  PortRange -> ParsecT DockerfileError Text Identity PortRange
forall a. a -> ParsecT DockerfileError Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (PortRange -> ParsecT DockerfileError Text Identity PortRange)
-> PortRange -> ParsecT DockerfileError Text Identity PortRange
forall a b. (a -> b) -> a -> b
$ Port -> Port -> PortRange
PortRange (Port -> Protocol -> Port
setProto Port
start Protocol
proto) (Port -> Protocol -> Port
setProto Port
finish Protocol
proto)
  where
    setProto :: Port -> Protocol -> Port
    setProto :: Port -> Protocol -> Port
setProto (Port Int
p Protocol
_) Protocol
prot = Int -> Protocol -> Port
Port Int
p Protocol
prot
    setProto (PortStr Text
s) Protocol
_ = Text -> Port
PortStr Text
s

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 a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
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 a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
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 a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String -> ParsecT DockerfileError Text Identity Protocol
forall a. String -> ParsecT DockerfileError Text Identity a
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 a b.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity b
-> ParsecT DockerfileError Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Protocol -> ParsecT DockerfileError Text Identity Protocol
forall a. a -> ParsecT DockerfileError Text Identity a
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 a b.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity b
-> ParsecT DockerfileError Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Protocol -> ParsecT DockerfileError Text Identity Protocol
forall a. a -> ParsecT DockerfileError Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return Protocol
UDP

portInt :: Parser Port
portInt :: ParsecT DockerfileError Text Identity Port
portInt = do
  Integer
portNumber <- Parser Integer
natural
  ParsecT DockerfileError Text Identity (Tokens Text) -> Parser ()
forall a. ParsecT DockerfileError Text Identity a -> 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
"/" ParsecT DockerfileError Text Identity (Tokens Text)
-> ParsecT DockerfileError Text Identity (Tokens Text)
-> ParsecT DockerfileError Text Identity (Tokens Text)
forall a.
ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
-> ParsecT DockerfileError Text Identity a
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 -> ParsecT DockerfileError Text Identity Port
forall a. a -> ParsecT DockerfileError Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Port -> ParsecT DockerfileError Text Identity Port)
-> Port -> ParsecT DockerfileError Text Identity 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 :: ParsecT DockerfileError Text Identity 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
-> ParsecT DockerfileError Text Identity 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 :: (?esc::Char) => ParsecT DockerfileError Text Identity 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 -> ParsecT DockerfileError Text Identity Port
forall a. a -> ParsecT DockerfileError Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Port -> ParsecT DockerfileError Text Identity Port)
-> Port -> ParsecT DockerfileError Text Identity Port
forall a b. (a -> b) -> a -> b
$ Text -> Port
PortStr (Text -> Text -> Text
T.append Text
"$" Text
variable)