{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}

-- | This module contains the implementation of the @dhall format@ subcommand

module Dhall.Format
    ( -- * Format
      Format(..)
    , format
    ) where

import Data.Foldable      (for_)
import Data.List.NonEmpty (NonEmpty)
import Data.Maybe         (fromMaybe)
import Dhall.Pretty       (CharacterSet, annToAnsiStyle, detectCharacterSet)
import Dhall.Util
    ( Censor
    , CheckFailed (..)
    , Header (..)
    , Input (..)
    , OutputMode (..)
    , Transitivity (..)
    , handleMultipleChecksFailed
    )

import qualified Data.Text.IO
import qualified Dhall.Import
import qualified Dhall.Pretty
import qualified Dhall.Util
import qualified Prettyprinter                      as Pretty
import qualified Prettyprinter.Render.Terminal      as Pretty.Terminal
import qualified Prettyprinter.Render.Text          as Pretty.Text
import qualified System.AtomicWrite.Writer.LazyText as AtomicWrite.LazyText
import qualified System.Console.ANSI
import qualified System.FilePath
import qualified System.IO

-- | Arguments to the `format` subcommand
data Format = Format
    { Format -> Maybe CharacterSet
chosenCharacterSet :: Maybe CharacterSet
    , Format -> Censor
censor             :: Censor
    , Format -> Transitivity
transitivity       :: Transitivity
    , Format -> NonEmpty Input
inputs             :: NonEmpty Input
    , Format -> OutputMode
outputMode         :: OutputMode
    }

-- | Implementation of the @dhall format@ subcommand
format :: Format -> IO ()
format :: Format -> IO ()
format (Format { inputs :: Format -> NonEmpty Input
inputs = NonEmpty Input
inputs0, transitivity :: Format -> Transitivity
transitivity = Transitivity
transitivity0, Maybe CharacterSet
OutputMode
Censor
outputMode :: OutputMode
censor :: Censor
chosenCharacterSet :: Maybe CharacterSet
outputMode :: Format -> OutputMode
censor :: Format -> Censor
chosenCharacterSet :: Format -> Maybe CharacterSet
..}) =
    forall (t :: * -> *) a.
(Foldable t, Traversable t) =>
Text -> Text -> (a -> IO (Either CheckFailed ())) -> t a -> IO ()
handleMultipleChecksFailed Text
"format" Text
"formatted" Input -> IO (Either CheckFailed ())
go NonEmpty Input
inputs0
  where
    go :: Input -> IO (Either CheckFailed ())
go Input
input = do
        let directory :: FilePath
directory = case Input
input of
                Input
StandardInput ->
                    FilePath
"."
                InputFile FilePath
file ->
                    FilePath -> FilePath
System.FilePath.takeDirectory FilePath
file

        let status :: Status
status = FilePath -> Status
Dhall.Import.emptyStatus FilePath
directory

        let layoutHeaderAndExpr :: (Header, Expr Src a) -> SimpleDocStream Ann
layoutHeaderAndExpr (Header Text
header, Expr Src a
expr) =
                let characterSet :: CharacterSet
characterSet = forall a. a -> Maybe a -> a
fromMaybe (forall a. Expr Src a -> CharacterSet
detectCharacterSet Expr Src a
expr) Maybe CharacterSet
chosenCharacterSet
                in
                forall ann. Doc ann -> SimpleDocStream ann
Dhall.Pretty.layout
                    (   forall a ann. Pretty a => a -> Doc ann
Pretty.pretty Text
header
                    forall a. Semigroup a => a -> a -> a
<>  forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet CharacterSet
characterSet Expr Src a
expr
                    forall a. Semigroup a => a -> a -> a
<>  Doc Ann
"\n")

        (FilePath
inputName, Text
originalText, Transitivity
transitivity) <- case Input
input of
            InputFile FilePath
file -> do
                Text
text <- FilePath -> IO Text
Data.Text.IO.readFile FilePath
file

                forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
file, Text
text, Transitivity
transitivity0)
            Input
StandardInput -> do
                Text
text <- IO Text
Data.Text.IO.getContents

                forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
"(input)", Text
text, Transitivity
NonTransitive)


        headerAndExpr :: (Header, Expr Src Import)
headerAndExpr@(Header
_, Expr Src Import
parsedExpression) <- Censor -> FilePath -> Text -> IO (Header, Expr Src Import)
Dhall.Util.getExpressionAndHeaderFromStdinText Censor
censor FilePath
inputName Text
originalText

        case Transitivity
transitivity of
            Transitivity
Transitive ->
                forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Expr Src Import
parsedExpression forall a b. (a -> b) -> a -> b
$ \Import
import_ -> do
                    Maybe FilePath
maybeFilepath <- Status -> Import -> IO (Maybe FilePath)
Dhall.Import.dependencyToFile Status
status Import
import_

                    forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Maybe FilePath
maybeFilepath forall a b. (a -> b) -> a -> b
$ \FilePath
filepath ->
                        Input -> IO (Either CheckFailed ())
go (FilePath -> Input
InputFile FilePath
filepath)

            Transitivity
NonTransitive ->
                forall (m :: * -> *) a. Monad m => a -> m a
return ()

        let docStream :: SimpleDocStream Ann
docStream = forall {a}. Pretty a => (Header, Expr Src a) -> SimpleDocStream Ann
layoutHeaderAndExpr (Header, Expr Src Import)
headerAndExpr

        let formattedText :: Text
formattedText = forall ann. SimpleDocStream ann -> Text
Pretty.Text.renderStrict SimpleDocStream Ann
docStream

        case OutputMode
outputMode of
            OutputMode
Write -> do
                case Input
input of
                    InputFile FilePath
file ->
                        if Text
originalText forall a. Eq a => a -> a -> Bool
== Text
formattedText
                            then forall (m :: * -> *) a. Monad m => a -> m a
return ()
                            else FilePath -> Text -> IO ()
AtomicWrite.LazyText.atomicWriteFile
                                    FilePath
file
                                    (forall ann. SimpleDocStream ann -> Text
Pretty.Text.renderLazy SimpleDocStream Ann
docStream)

                    Input
StandardInput -> do
                        Bool
supportsANSI <- Handle -> IO Bool
System.Console.ANSI.hSupportsANSI Handle
System.IO.stdout

                        Handle -> SimpleDocStream AnsiStyle -> IO ()
Pretty.Terminal.renderIO
                            Handle
System.IO.stdout
                            (if Bool
supportsANSI
                                then (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ann -> AnsiStyle
annToAnsiStyle SimpleDocStream Ann
docStream)
                                else (forall ann xxx. SimpleDocStream ann -> SimpleDocStream xxx
Pretty.unAnnotateS SimpleDocStream Ann
docStream))

                forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right ())

            OutputMode
Check ->
                forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
                    if Text
originalText forall a. Eq a => a -> a -> Bool
== Text
formattedText
                        then forall a b. b -> Either a b
Right ()
                        else forall a b. a -> Either a b
Left CheckFailed{Input
input :: Input
input :: Input
..}