{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}

-- |
-- Module      : Error.Diagnose.Diagnostic.Internal
-- Description : Internal workings for diagnostic definitions and pretty printing.
-- Copyright   : (c) Mesabloo, 2021-2022
-- License     : BSD3
-- Stability   : experimental
-- Portability : Portable
--
-- /Warning/: The API of this module can break between two releases, therefore you should not rely on it.
--            It is also highly undocumented.
--
--            Please limit yourself to the "Error.Diagnose.Diagnostic" module, which exports some of the useful functions defined here.
module Error.Diagnose.Diagnostic.Internal (module Error.Diagnose.Diagnostic.Internal, def) where

import Control.Monad.IO.Class (MonadIO, liftIO)
#ifdef USE_AESON
import Data.Aeson (ToJSON(..), encode, object, (.=))
import Data.ByteString.Lazy (ByteString)
#endif
import Data.Default (Default, def)
import Data.Foldable (fold)
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap
import Data.List (intersperse)
import Error.Diagnose.Report (Report)
import Error.Diagnose.Report.Internal (prettyReport)
import Error.Diagnose.Style (Annotation, Style)
import Prettyprinter (Doc, Pretty, hardline, unAnnotate)
import Prettyprinter.Render.Terminal (hPutDoc)
import System.IO (Handle)

-- | The data type for diagnostic containing messages of an abstract type.
--
--   The constructors are private, but users can use 'def' from the 'Default' typeclass
--   to create a new empty diagnostic, and 'addFile' and 'addReport' to alter its internal state.
data Diagnostic msg
  = Diagnostic
      [Report msg]
      -- ^ All the reports contained in a diagnostic.
      --
      --   Reports are output one by one, without connections in between.
      (HashMap FilePath [String])
      -- ^ A map associating files with their content as lists of lines.

instance Default (Diagnostic msg) where
  def :: Diagnostic msg
def = [Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
forall msg.
[Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
Diagnostic [Report msg]
forall a. Monoid a => a
mempty HashMap FilePath [FilePath]
forall a. Monoid a => a
mempty

instance Semigroup (Diagnostic msg) where
  Diagnostic [Report msg]
rs1 HashMap FilePath [FilePath]
file <> :: Diagnostic msg -> Diagnostic msg -> Diagnostic msg
<> Diagnostic [Report msg]
rs2 HashMap FilePath [FilePath]
_ = [Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
forall msg.
[Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
Diagnostic ([Report msg]
rs1 [Report msg] -> [Report msg] -> [Report msg]
forall a. Semigroup a => a -> a -> a
<> [Report msg]
rs2) HashMap FilePath [FilePath]
file

#ifdef USE_AESON
instance ToJSON msg => ToJSON (Diagnostic msg) where
  toJSON (Diagnostic reports files) =
    object [ "files" .= fmap toJSONFile (HashMap.toList files)
           , "reports" .= reports
           ]
    where
      toJSONFile (path, content) =
        object [ "name" .= path
               , "content" .= content
               ]
#endif

-- | Pretty prints a 'Diagnostic' into a 'Doc'ument that can be output using 'hPutDoc'.
--
--   Colors are put by default.
--   If you do not want these, just 'unAnnotate' the resulting document like so:
--
--   >>> let doc = unAnnotate (prettyDiagnostic withUnicode tabSize diagnostic)
--
--   Changing the style is also rather easy:
--
--   >>> let myCustomStyle :: Style = _
--   >>> let doc = myCustomStyle (prettyDiagnostic withUnicode tabSize diagnostic)
prettyDiagnostic ::
  Pretty msg =>
  -- | Should we use unicode when printing paths?
  Bool ->
  -- | The number of spaces each TAB character will span.
  Int ->
  -- | The diagnostic to print.
  Diagnostic msg ->
  Doc Annotation
prettyDiagnostic :: Bool -> Int -> Diagnostic msg -> Doc Annotation
prettyDiagnostic Bool
withUnicode Int
tabSize (Diagnostic [Report msg]
reports HashMap FilePath [FilePath]
file) =
  [Doc Annotation] -> Doc Annotation
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Doc Annotation] -> Doc Annotation)
-> ([Doc Annotation] -> [Doc Annotation])
-> [Doc Annotation]
-> Doc Annotation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Annotation -> [Doc Annotation] -> [Doc Annotation]
forall a. a -> [a] -> [a]
intersperse Doc Annotation
forall ann. Doc ann
hardline ([Doc Annotation] -> Doc Annotation)
-> [Doc Annotation] -> Doc Annotation
forall a b. (a -> b) -> a -> b
$ HashMap FilePath [FilePath]
-> Bool -> Int -> Report msg -> Doc Annotation
forall msg.
Pretty msg =>
HashMap FilePath [FilePath]
-> Bool -> Int -> Report msg -> Doc Annotation
prettyReport HashMap FilePath [FilePath]
file Bool
withUnicode Int
tabSize (Report msg -> Doc Annotation) -> [Report msg] -> [Doc Annotation]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Report msg]
reports
{-# INLINE prettyDiagnostic #-}

-- | Prints a 'Diagnostic' onto a specific 'Handle'.
printDiagnostic ::
  (MonadIO m, Pretty msg) =>
  -- | The handle onto which to output the diagnostic.
  Handle ->
  -- | Should we print with unicode characters?
  Bool ->
  -- | 'False' to disable colors.
  Bool ->
  -- | The number of spaces each TAB character will span.
  Int ->
  -- | The style in which to output the diagnostic.
  Style ->
  -- | The diagnostic to output.
  Diagnostic msg ->
  m ()
printDiagnostic :: Handle -> Bool -> Bool -> Int -> Style -> Diagnostic msg -> m ()
printDiagnostic Handle
handle Bool
withUnicode Bool
withColors Int
tabSize Style
style Diagnostic msg
diag =
  IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Handle -> Doc AnsiStyle -> IO ()
hPutDoc Handle
handle ((if Bool
withColors then Style
style else Style
forall ann xxx. Doc ann -> Doc xxx
unAnnotate) Style -> Style
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> Diagnostic msg -> Doc Annotation
forall msg.
Pretty msg =>
Bool -> Int -> Diagnostic msg -> Doc Annotation
prettyDiagnostic Bool
withUnicode Int
tabSize Diagnostic msg
diag)
{-# INLINE printDiagnostic #-}

-- | Inserts a new referenceable file within the diagnostic.
addFile ::
  Diagnostic msg ->
  -- | The path to the file.
  FilePath ->
  -- | The content of the file as a single string, where lines are ended by @\\n@.
  String ->
  Diagnostic msg
addFile :: Diagnostic msg -> FilePath -> FilePath -> Diagnostic msg
addFile (Diagnostic [Report msg]
reports HashMap FilePath [FilePath]
files) FilePath
path FilePath
content =
  [Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
forall msg.
[Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
Diagnostic [Report msg]
reports (FilePath
-> [FilePath]
-> HashMap FilePath [FilePath]
-> HashMap FilePath [FilePath]
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert FilePath
path (FilePath -> [FilePath]
lines FilePath
content) HashMap FilePath [FilePath]
files)
{-# INLINE addFile #-}

-- | Inserts a new report into a diagnostic.
addReport ::
  Diagnostic msg ->
  -- | The new report to add to the diagnostic.
  Report msg ->
  Diagnostic msg
addReport :: Diagnostic msg -> Report msg -> Diagnostic msg
addReport (Diagnostic [Report msg]
reports HashMap FilePath [FilePath]
files) Report msg
report =
  [Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
forall msg.
[Report msg] -> HashMap FilePath [FilePath] -> Diagnostic msg
Diagnostic ([Report msg]
reports [Report msg] -> [Report msg] -> [Report msg]
forall a. Semigroup a => a -> a -> a
<> [Report msg
report]) HashMap FilePath [FilePath]
files
{-# INLINE addReport #-}

#ifdef USE_AESON
-- | Creates a JSON object from a diagnostic, containing those fields (only types are indicated):
--
--   > { files:
--   >     { name: string
--   >     , content: string[]
--   >     }[]
--   > , reports:
--   >     { kind: 'error' | 'warning'
--   >     , code: T?
--   >     , message: T
--   >     , markers:
--   >         { kind: 'this' | 'where' | 'maybe'
--   >         , position:
--   >             { beginning: { line: int, column: int }
--   >             , end: { line: int, column: int }
--   >             , file: string
--   >             }
--   >         , message: T
--   >         }[]
--   >     , hints: ({ note: T } | { hint: T })[]
--   >     }[]
--   > }
--
--   where @T@ is the type of the JSON representation for the @msg@ type variable.
diagnosticToJson :: ToJSON msg => Diagnostic msg -> ByteString
diagnosticToJson = encode
#endif