{-
    Copyright 2012-2019 Vidar Holen

    This file is part of ShellCheck.
    https://www.shellcheck.net

    ShellCheck is free software: you can redistribute it and/or modify
    it under the terms of the GNU General Public License as published by
    the Free Software Foundation, either version 3 of the License, or
    (at your option) any later version.

    ShellCheck 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 General Public License for more details.

    You should have received a copy of the GNU General Public License
    along with this program.  If not, see <https://www.gnu.org/licenses/>.
-}
module ShellCheck.Formatter.CheckStyle (format) where

import ShellCheck.Interface
import ShellCheck.Formatter.Format

import Data.Char
import Data.List
import GHC.Exts
import System.IO

format :: IO Formatter
format :: IO Formatter
format = Formatter -> IO Formatter
forall (m :: * -> *) a. Monad m => a -> m a
return Formatter :: IO ()
-> (CheckResult -> SystemInterface IO -> IO ())
-> (FilePath -> FilePath -> IO ())
-> IO ()
-> Formatter
Formatter {
    header :: IO ()
header = do
        FilePath -> IO ()
putStrLn FilePath
"<?xml version='1.0' encoding='UTF-8'?>"
        FilePath -> IO ()
putStrLn FilePath
"<checkstyle version='4.3'>",

    onFailure :: FilePath -> FilePath -> IO ()
onFailure = FilePath -> FilePath -> IO ()
outputError,
    onResult :: CheckResult -> SystemInterface IO -> IO ()
onResult = CheckResult -> SystemInterface IO -> IO ()
outputResults,

    footer :: IO ()
footer = FilePath -> IO ()
putStrLn FilePath
"</checkstyle>"
}

outputResults :: CheckResult -> SystemInterface IO -> IO ()
outputResults CheckResult
cr SystemInterface IO
sys =
    if [PositionedComment] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PositionedComment]
comments
    then FilePath -> FilePath -> [PositionedComment] -> IO ()
outputFile (CheckResult -> FilePath
crFilename CheckResult
cr) FilePath
"" []
    else ([PositionedComment] -> IO ()) -> [[PositionedComment]] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ [PositionedComment] -> IO ()
outputGroup [[PositionedComment]]
fileGroups
  where
    comments :: [PositionedComment]
comments = CheckResult -> [PositionedComment]
crComments CheckResult
cr
    fileGroups :: [[PositionedComment]]
fileGroups = (PositionedComment -> FilePath)
-> [PositionedComment] -> [[PositionedComment]]
forall b a. Ord b => (a -> b) -> [a] -> [[a]]
groupWith PositionedComment -> FilePath
sourceFile [PositionedComment]
comments
    outputGroup :: [PositionedComment] -> IO ()
outputGroup [PositionedComment]
group = do
        let filename :: FilePath
filename = PositionedComment -> FilePath
sourceFile ([PositionedComment] -> PositionedComment
forall a. [a] -> a
head [PositionedComment]
group)
        Either FilePath FilePath
result <- SystemInterface IO
-> Maybe Bool -> FilePath -> IO (Either FilePath FilePath)
forall (m :: * -> *).
SystemInterface m
-> Maybe Bool -> FilePath -> m (Either FilePath FilePath)
siReadFile SystemInterface IO
sys (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True) FilePath
filename
        let contents :: FilePath
contents = (FilePath -> FilePath)
-> (FilePath -> FilePath) -> Either FilePath FilePath -> FilePath
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (FilePath -> FilePath -> FilePath
forall a b. a -> b -> a
const FilePath
"") FilePath -> FilePath
forall a. a -> a
id Either FilePath FilePath
result
        FilePath -> FilePath -> [PositionedComment] -> IO ()
outputFile FilePath
filename FilePath
contents [PositionedComment]
group

outputFile :: FilePath -> FilePath -> [PositionedComment] -> IO ()
outputFile FilePath
filename FilePath
contents [PositionedComment]
warnings = do
    let comments :: [PositionedComment]
comments = [PositionedComment] -> FilePath -> [PositionedComment]
makeNonVirtual [PositionedComment]
warnings FilePath
contents
    FilePath -> IO ()
putStrLn (FilePath -> IO ())
-> ([PositionedComment] -> FilePath)
-> [PositionedComment]
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [PositionedComment] -> FilePath
forall (t :: * -> *).
Foldable t =>
FilePath -> t PositionedComment -> FilePath
formatFile FilePath
filename ([PositionedComment] -> IO ()) -> [PositionedComment] -> IO ()
forall a b. (a -> b) -> a -> b
$ [PositionedComment]
comments

formatFile :: FilePath -> t PositionedComment -> FilePath
formatFile FilePath
name t PositionedComment
comments = [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
    FilePath
"<file ", FilePath -> FilePath -> FilePath
attr FilePath
"name" FilePath
name, FilePath
">\n",
        (PositionedComment -> FilePath) -> t PositionedComment -> FilePath
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PositionedComment -> FilePath
formatComment t PositionedComment
comments,
    FilePath
"</file>"
    ]

formatComment :: PositionedComment -> FilePath
formatComment PositionedComment
c = [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
    FilePath
"<error ",
    FilePath -> FilePath -> FilePath
attr FilePath
"line" (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show (Integer -> FilePath)
-> (PositionedComment -> Integer) -> PositionedComment -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionedComment -> Integer
lineNo (PositionedComment -> FilePath) -> PositionedComment -> FilePath
forall a b. (a -> b) -> a -> b
$ PositionedComment
c,
    FilePath -> FilePath -> FilePath
attr FilePath
"column" (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show (Integer -> FilePath)
-> (PositionedComment -> Integer) -> PositionedComment -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionedComment -> Integer
colNo (PositionedComment -> FilePath) -> PositionedComment -> FilePath
forall a b. (a -> b) -> a -> b
$ PositionedComment
c,
    FilePath -> FilePath -> FilePath
attr FilePath
"severity" (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
severity (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ PositionedComment -> FilePath
severityText PositionedComment
c,
    FilePath -> FilePath -> FilePath
attr FilePath
"message" (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ PositionedComment -> FilePath
messageText PositionedComment
c,
    FilePath -> FilePath -> FilePath
attr FilePath
"source" (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"ShellCheck.SC" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Integer -> FilePath
forall a. Show a => a -> FilePath
show (PositionedComment -> Integer
codeNo PositionedComment
c),
    FilePath
"/>\n"
    ]

outputError :: FilePath -> FilePath -> IO ()
outputError FilePath
file FilePath
error = FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
    FilePath
"<file ", FilePath -> FilePath -> FilePath
attr FilePath
"name" FilePath
file, FilePath
">\n",
    FilePath
"<error ",
        FilePath -> FilePath -> FilePath
attr FilePath
"line" FilePath
"1",
        FilePath -> FilePath -> FilePath
attr FilePath
"column" FilePath
"1",
        FilePath -> FilePath -> FilePath
attr FilePath
"severity" FilePath
"error",
        FilePath -> FilePath -> FilePath
attr FilePath
"message" FilePath
error,
        FilePath -> FilePath -> FilePath
attr FilePath
"source" FilePath
"ShellCheck",
    FilePath
"/>\n",
    FilePath
"</file>"
    ]


attr :: FilePath -> FilePath -> FilePath
attr FilePath
s FilePath
v = [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ FilePath
s, FilePath
"='", FilePath -> FilePath
escape FilePath
v, FilePath
"' " ]
escape :: FilePath -> FilePath
escape = (Char -> FilePath) -> FilePath -> FilePath
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Char -> FilePath
escape'
escape' :: Char -> FilePath
escape' Char
c = if Char -> Bool
isOk Char
c then [Char
c] else FilePath
"&#" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show (Char -> Int
ord Char
c) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
";"
isOk :: Char -> Bool
isOk Char
x = ((Char -> Bool) -> Bool) -> [Char -> Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Char -> Bool) -> Char -> Bool
forall a b. (a -> b) -> a -> b
$Char
x) [Char -> Bool
isAsciiUpper, Char -> Bool
isAsciiLower, Char -> Bool
isDigit, (Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
" ./")]

severity :: FilePath -> FilePath
severity FilePath
"error" = FilePath
"error"
severity FilePath
"warning" = FilePath
"warning"
severity FilePath
_ = FilePath
"info"