Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- type Dockerfile = [InstructionPos Text]
- parseText :: Text -> Either Error Dockerfile
- parseFile :: FilePath -> IO (Either Error Dockerfile)
- parseStdin :: IO (Either Error Dockerfile)
- parseErrorPretty :: (VisualStream s, ShowErrorComponent e) => ParseError s e -> String
- errorBundlePretty :: (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- prettyPrint :: Dockerfile -> Text
- prettyPrintDockerfile :: [InstructionPos Text] -> Doc ann
- data Instruction args
- = From !BaseImage
- | Add !AddArgs !AddFlags
- | User !Text
- | Label !Pairs
- | Stopsignal !Text
- | Copy !CopyArgs !CopyFlags
- | Run !(RunArgs args)
- | Cmd !(Arguments args)
- | Shell !(Arguments args)
- | Workdir !Directory
- | Expose !Ports
- | Volume !Text
- | Entrypoint !(Arguments args)
- | Maintainer !Text
- | Env !Pairs
- | Arg !Text !(Maybe Text)
- | Healthcheck !(Check args)
- | Pragma !PragmaDirective
- | Comment !Text
- | OnBuild !(Instruction args)
- data InstructionPos args = InstructionPos {
- instruction :: !(Instruction args)
- sourcename :: !Filename
- lineNumber :: !Linenumber
- data BaseImage = BaseImage {}
- newtype SourcePath = SourcePath {
- unSourcePath :: Text
- newtype TargetPath = TargetPath {
- unTargetPath :: Text
- data Chown
- data CopySource
- = CopySource !Text
- | NoSource
- data CopyArgs = CopyArgs {}
- data AddArgs = AddArgs {}
- data Check args
- data CheckArgs args = CheckArgs {}
- data Image = Image {
- registryName :: !(Maybe Registry)
- imageName :: !Text
- newtype Registry = Registry {
- unRegistry :: Text
- newtype ImageAlias = ImageAlias {
- unImageAlias :: Text
- newtype Tag = Tag {}
- newtype Digest = Digest {}
- data Ports
- type Directory = Text
- data Arguments args
- type Pairs = [(Text, Text)]
- type Filename = Text
- type Platform = Text
- type Linenumber = Int
Documentation
type Dockerfile = [InstructionPos Text] Source #
Type of the Dockerfile AST
Parsing Dockerfiles (Language.Docker.Syntax
and Language.Docker.Parser
)
parseStdin :: IO (Either Error Dockerfile) Source #
Reads the standard input until the end and parses the contents as a Dockerfile
Re-exports from megaparsec
:: (VisualStream s, ShowErrorComponent e) | |
=> ParseError s e | Parse error to render |
-> String | Result of rendering |
Pretty-print a ParseError
. The rendered String
always ends with a
newline.
Since: megaparsec-5.0.0
:: (VisualStream s, TraversableStream s, ShowErrorComponent e) | |
=> ParseErrorBundle s e | Parse error bundle to display |
-> String | Textual rendition of the bundle |
Pretty-print a ParseErrorBundle
. All ParseError
s in the bundle will
be pretty-printed in order together with the corresponding offending
lines by doing a single pass over the input stream. The rendered String
always ends with a newline.
Since: megaparsec-7.0.0
Pretty-printing Dockerfiles (Language.Docker.PrettyPrint
)
prettyPrint :: Dockerfile -> Text Source #
Pretty print a Dockerfile
to a Text
prettyPrintDockerfile :: [InstructionPos Text] -> Doc ann Source #
Types (Language.Docker.Syntax
)
data Instruction args Source #
All commands available in Dockerfiles
From !BaseImage | |
Add !AddArgs !AddFlags | |
User !Text | |
Label !Pairs | |
Stopsignal !Text | |
Copy !CopyArgs !CopyFlags | |
Run !(RunArgs args) | |
Cmd !(Arguments args) | |
Shell !(Arguments args) | |
Workdir !Directory | |
Expose !Ports | |
Volume !Text | |
Entrypoint !(Arguments args) | |
Maintainer !Text | |
Env !Pairs | |
Arg !Text !(Maybe Text) | |
Healthcheck !(Check args) | |
Pragma !PragmaDirective | |
Comment !Text | |
OnBuild !(Instruction args) |
Instances
data InstructionPos args Source #
Instruction
with additional location information required for creating
good check messages
InstructionPos | |
|
Instances
newtype SourcePath Source #
Instances
IsString SourcePath Source # | |
Defined in Language.Docker.Syntax fromString :: String -> SourcePath # | |
Show SourcePath Source # | |
Defined in Language.Docker.Syntax showsPrec :: Int -> SourcePath -> ShowS # show :: SourcePath -> String # showList :: [SourcePath] -> ShowS # | |
Eq SourcePath Source # | |
Defined in Language.Docker.Syntax (==) :: SourcePath -> SourcePath -> Bool # (/=) :: SourcePath -> SourcePath -> Bool # | |
Ord SourcePath Source # | |
Defined in Language.Docker.Syntax compare :: SourcePath -> SourcePath -> Ordering # (<) :: SourcePath -> SourcePath -> Bool # (<=) :: SourcePath -> SourcePath -> Bool # (>) :: SourcePath -> SourcePath -> Bool # (>=) :: SourcePath -> SourcePath -> Bool # max :: SourcePath -> SourcePath -> SourcePath # min :: SourcePath -> SourcePath -> SourcePath # |
newtype TargetPath Source #
Instances
IsString TargetPath Source # | |
Defined in Language.Docker.Syntax fromString :: String -> TargetPath # | |
Show TargetPath Source # | |
Defined in Language.Docker.Syntax showsPrec :: Int -> TargetPath -> ShowS # show :: TargetPath -> String # showList :: [TargetPath] -> ShowS # | |
Eq TargetPath Source # | |
Defined in Language.Docker.Syntax (==) :: TargetPath -> TargetPath -> Bool # (/=) :: TargetPath -> TargetPath -> Bool # | |
Ord TargetPath Source # | |
Defined in Language.Docker.Syntax compare :: TargetPath -> TargetPath -> Ordering # (<) :: TargetPath -> TargetPath -> Bool # (<=) :: TargetPath -> TargetPath -> Bool # (>) :: TargetPath -> TargetPath -> Bool # (>=) :: TargetPath -> TargetPath -> Bool # max :: TargetPath -> TargetPath -> TargetPath # min :: TargetPath -> TargetPath -> TargetPath # |
data CopySource Source #
Instances
IsString CopySource Source # | |
Defined in Language.Docker.Syntax fromString :: String -> CopySource # | |
Show CopySource Source # | |
Defined in Language.Docker.Syntax showsPrec :: Int -> CopySource -> ShowS # show :: CopySource -> String # showList :: [CopySource] -> ShowS # | |
Eq CopySource Source # | |
Defined in Language.Docker.Syntax (==) :: CopySource -> CopySource -> Bool # (/=) :: CopySource -> CopySource -> Bool # | |
Ord CopySource Source # | |
Defined in Language.Docker.Syntax compare :: CopySource -> CopySource -> Ordering # (<) :: CopySource -> CopySource -> Bool # (<=) :: CopySource -> CopySource -> Bool # (>) :: CopySource -> CopySource -> Bool # (>=) :: CopySource -> CopySource -> Bool # max :: CopySource -> CopySource -> CopySource # min :: CopySource -> CopySource -> CopySource # |
Instances
Functor Check Source # | |
Show args => Show (Check args) Source # | |
Eq args => Eq (Check args) Source # | |
Ord args => Ord (Check args) Source # | |
Instances
Functor CheckArgs Source # | |
Show args => Show (CheckArgs args) Source # | |
Eq args => Eq (CheckArgs args) Source # | |
Ord args => Ord (CheckArgs args) Source # | |
Defined in Language.Docker.Syntax compare :: CheckArgs args -> CheckArgs args -> Ordering # (<) :: CheckArgs args -> CheckArgs args -> Bool # (<=) :: CheckArgs args -> CheckArgs args -> Bool # (>) :: CheckArgs args -> CheckArgs args -> Bool # (>=) :: CheckArgs args -> CheckArgs args -> Bool # |
newtype ImageAlias Source #
Instances
IsString ImageAlias Source # | |
Defined in Language.Docker.Syntax fromString :: String -> ImageAlias # | |
Show ImageAlias Source # | |
Defined in Language.Docker.Syntax showsPrec :: Int -> ImageAlias -> ShowS # show :: ImageAlias -> String # showList :: [ImageAlias] -> ShowS # | |
Eq ImageAlias Source # | |
Defined in Language.Docker.Syntax (==) :: ImageAlias -> ImageAlias -> Bool # (/=) :: ImageAlias -> ImageAlias -> Bool # | |
Ord ImageAlias Source # | |
Defined in Language.Docker.Syntax compare :: ImageAlias -> ImageAlias -> Ordering # (<) :: ImageAlias -> ImageAlias -> Bool # (<=) :: ImageAlias -> ImageAlias -> Bool # (>) :: ImageAlias -> ImageAlias -> Bool # (>=) :: ImageAlias -> ImageAlias -> Bool # max :: ImageAlias -> ImageAlias -> ImageAlias # min :: ImageAlias -> ImageAlias -> ImageAlias # |
Instances
Functor Arguments Source # | |
IsString (Arguments Text) Source # | |
Defined in Language.Docker.Syntax fromString :: String -> Arguments Text # | |
IsList (Arguments Text) Source # | |
Show args => Show (Arguments args) Source # | |
Eq args => Eq (Arguments args) Source # | |
Ord args => Ord (Arguments args) Source # | |
Defined in Language.Docker.Syntax compare :: Arguments args -> Arguments args -> Ordering # (<) :: Arguments args -> Arguments args -> Bool # (<=) :: Arguments args -> Arguments args -> Bool # (>) :: Arguments args -> Arguments args -> Bool # (>=) :: Arguments args -> Arguments args -> Bool # | |
type Item (Arguments Text) Source # | |
Defined in Language.Docker.Syntax |
type Linenumber = Int Source #