{-# Language OverloadedStrings, GADTs #-}
module Toml.Pretty (
TomlDoc,
DocClass(..),
prettyToml,
prettyTomlOrdered,
prettyValue,
prettyToken,
prettySectionKind,
prettySimpleKey,
prettyKey,
prettySemanticError,
prettyMatchMessage,
prettyLocated,
) where
import Data.Char (ord, isAsciiLower, isAsciiUpper, isDigit, isPrint)
import Data.Foldable (fold)
import Data.List (partition, sortOn)
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Map qualified as Map
import Data.String (fromString)
import Data.Time (ZonedTime(zonedTimeZone), TimeZone (timeZoneMinutes))
import Data.Time.Format (formatTime, defaultTimeLocale)
import Prettyprinter
import Text.Printf (printf)
import Toml.FromValue.Matcher (MatchMessage(..), Scope (..))
import Toml.Lexer (Token(..))
import Toml.Located (Located(..))
import Toml.Parser.Types (SectionKind(..))
import Toml.Position (Position(..))
import Toml.Semantics (SemanticError (..), SemanticErrorKind (..))
import Toml.Value (Value(..), Table)
data DocClass
= TableClass
| KeyClass
| StringClass
| NumberClass
| DateClass
| BoolClass
deriving (ReadPrec [DocClass]
ReadPrec DocClass
Int -> ReadS DocClass
ReadS [DocClass]
(Int -> ReadS DocClass)
-> ReadS [DocClass]
-> ReadPrec DocClass
-> ReadPrec [DocClass]
-> Read DocClass
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DocClass
readsPrec :: Int -> ReadS DocClass
$creadList :: ReadS [DocClass]
readList :: ReadS [DocClass]
$creadPrec :: ReadPrec DocClass
readPrec :: ReadPrec DocClass
$creadListPrec :: ReadPrec [DocClass]
readListPrec :: ReadPrec [DocClass]
Read, Int -> DocClass -> String -> String
[DocClass] -> String -> String
DocClass -> String
(Int -> DocClass -> String -> String)
-> (DocClass -> String)
-> ([DocClass] -> String -> String)
-> Show DocClass
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DocClass -> String -> String
showsPrec :: Int -> DocClass -> String -> String
$cshow :: DocClass -> String
show :: DocClass -> String
$cshowList :: [DocClass] -> String -> String
showList :: [DocClass] -> String -> String
Show, DocClass -> DocClass -> Bool
(DocClass -> DocClass -> Bool)
-> (DocClass -> DocClass -> Bool) -> Eq DocClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocClass -> DocClass -> Bool
== :: DocClass -> DocClass -> Bool
$c/= :: DocClass -> DocClass -> Bool
/= :: DocClass -> DocClass -> Bool
Eq, Eq DocClass
Eq DocClass =>
(DocClass -> DocClass -> Ordering)
-> (DocClass -> DocClass -> Bool)
-> (DocClass -> DocClass -> Bool)
-> (DocClass -> DocClass -> Bool)
-> (DocClass -> DocClass -> Bool)
-> (DocClass -> DocClass -> DocClass)
-> (DocClass -> DocClass -> DocClass)
-> Ord DocClass
DocClass -> DocClass -> Bool
DocClass -> DocClass -> Ordering
DocClass -> DocClass -> DocClass
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DocClass -> DocClass -> Ordering
compare :: DocClass -> DocClass -> Ordering
$c< :: DocClass -> DocClass -> Bool
< :: DocClass -> DocClass -> Bool
$c<= :: DocClass -> DocClass -> Bool
<= :: DocClass -> DocClass -> Bool
$c> :: DocClass -> DocClass -> Bool
> :: DocClass -> DocClass -> Bool
$c>= :: DocClass -> DocClass -> Bool
>= :: DocClass -> DocClass -> Bool
$cmax :: DocClass -> DocClass -> DocClass
max :: DocClass -> DocClass -> DocClass
$cmin :: DocClass -> DocClass -> DocClass
min :: DocClass -> DocClass -> DocClass
Ord)
type TomlDoc = Doc DocClass
prettyKey :: NonEmpty String -> TomlDoc
prettyKey :: NonEmpty String -> Doc DocClass
prettyKey = DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
KeyClass (Doc DocClass -> Doc DocClass)
-> (NonEmpty String -> Doc DocClass)
-> NonEmpty String
-> Doc DocClass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (Doc DocClass) -> Doc DocClass
forall m. Monoid m => NonEmpty m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (NonEmpty (Doc DocClass) -> Doc DocClass)
-> (NonEmpty String -> NonEmpty (Doc DocClass))
-> NonEmpty String
-> Doc DocClass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc DocClass -> NonEmpty (Doc DocClass) -> NonEmpty (Doc DocClass)
forall a. a -> NonEmpty a -> NonEmpty a
NonEmpty.intersperse Doc DocClass
forall ann. Doc ann
dot (NonEmpty (Doc DocClass) -> NonEmpty (Doc DocClass))
-> (NonEmpty String -> NonEmpty (Doc DocClass))
-> NonEmpty String
-> NonEmpty (Doc DocClass)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Doc DocClass)
-> NonEmpty String -> NonEmpty (Doc DocClass)
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Doc DocClass
forall a. String -> Doc a
prettySimpleKey
prettySimpleKey :: String -> Doc a
prettySimpleKey :: forall a. String -> Doc a
prettySimpleKey String
str
| Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str), (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isBareKey String
str = String -> Doc a
forall a. IsString a => String -> a
fromString String
str
| Bool
otherwise = String -> Doc a
forall a. IsString a => String -> a
fromString (String -> String
quoteString String
str)
isBareKey :: Char -> Bool
isBareKey :: Char -> Bool
isBareKey Char
x = Char -> Bool
isAsciiLower Char
x Bool -> Bool -> Bool
|| Char -> Bool
isAsciiUpper Char
x Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
x Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'
quoteString :: String -> String
quoteString :: String -> String
quoteString = (Char
'"'Char -> String -> String
forall a. a -> [a] -> [a]
:) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
go
where
go :: String -> String
go = \case
String
"" -> String
"\""
Char
'"' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'"' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\\' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\b' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'b' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\f' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'f' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\n' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'n' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\r' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'r' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\t' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
't' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
x : String
xs
| Char -> Bool
isPrint Char
x -> Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
| Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\xffff' -> String -> Int -> String -> String
forall r. PrintfType r => String -> r
printf String
"\\u%04X%s" (Char -> Int
ord Char
x) (String -> String
go String
xs)
| Bool
otherwise -> String -> Int -> String -> String
forall r. PrintfType r => String -> r
printf String
"\\U%08X%s" (Char -> Int
ord Char
x) (String -> String
go String
xs)
quoteMlString :: String -> String
quoteMlString :: String -> String
quoteMlString = (String
"\"\"\"\n"String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
go
where
go :: String -> String
go = \case
String
"" -> String
"\"\"\""
Char
'"' : Char
'"' : Char
'"' : String
xs -> String
"\"\"\\\"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
go String
xs
Char
'\\' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\b' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'b' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\f' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'f' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\t' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
't' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\n' : String
xs -> Char
'\n' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\r' : Char
'\n' : String
xs -> Char
'\r' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'\n' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
'\r' : String
xs -> Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'r' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
Char
x : String
xs
| Char -> Bool
isPrint Char
x -> Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
| Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\xffff' -> String -> Int -> String -> String
forall r. PrintfType r => String -> r
printf String
"\\u%04X%s" (Char -> Int
ord Char
x) (String -> String
go String
xs)
| Bool
otherwise -> String -> Int -> String -> String
forall r. PrintfType r => String -> r
printf String
"\\U%08X%s" (Char -> Int
ord Char
x) (String -> String
go String
xs)
prettySectionKind :: SectionKind -> NonEmpty String -> TomlDoc
prettySectionKind :: SectionKind -> NonEmpty String -> Doc DocClass
prettySectionKind SectionKind
TableKind NonEmpty String
key =
DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
TableClass (Doc DocClass -> Doc DocClass
forall ann xxx. Doc ann -> Doc xxx
unAnnotate (Doc DocClass
forall ann. Doc ann
lbracket Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> NonEmpty String -> Doc DocClass
prettyKey NonEmpty String
key Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> Doc DocClass
forall ann. Doc ann
rbracket))
prettySectionKind SectionKind
ArrayTableKind NonEmpty String
key =
DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
TableClass (Doc DocClass -> Doc DocClass
forall ann xxx. Doc ann -> Doc xxx
unAnnotate (Doc DocClass
forall ann. Doc ann
lbracket Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> Doc DocClass
forall ann. Doc ann
lbracket Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> NonEmpty String -> Doc DocClass
prettyKey NonEmpty String
key Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> Doc DocClass
forall ann. Doc ann
rbracket Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> Doc DocClass
forall ann. Doc ann
rbracket))
prettyToken :: Token -> String
prettyToken :: Token -> String
prettyToken = \case
Token
TokComma -> String
"','"
Token
TokEquals -> String
"'='"
Token
TokPeriod -> String
"'.'"
Token
TokSquareO -> String
"'['"
Token
TokSquareC -> String
"']'"
Token
Tok2SquareO -> String
"'[['"
Token
Tok2SquareC -> String
"']]'"
Token
TokCurlyO -> String
"'{'"
Token
TokCurlyC -> String
"'}'"
Token
TokNewline -> String
"end-of-line"
TokBareKey String
_ -> String
"bare key"
Token
TokTrue -> String
"true literal"
Token
TokFalse -> String
"false literal"
TokString String
_ -> String
"string"
TokMlString String
_ -> String
"multi-line string"
TokInteger Integer
_ -> String
"integer"
TokFloat Double
_ -> String
"float"
TokOffsetDateTime ZonedTime
_ -> String
"offset date-time"
TokLocalDateTime LocalTime
_ -> String
"local date-time"
TokLocalDate Day
_ -> String
"local date"
TokLocalTime TimeOfDay
_ -> String
"local time"
Token
TokEOF -> String
"end-of-input"
prettyAssignment :: String -> Value -> TomlDoc
prettyAssignment :: String -> Value -> Doc DocClass
prettyAssignment = NonEmpty String -> Value -> Doc DocClass
go (NonEmpty String -> Value -> Doc DocClass)
-> (String -> NonEmpty String) -> String -> Value -> Doc DocClass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> NonEmpty String
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
where
go :: NonEmpty String -> Value -> Doc DocClass
go NonEmpty String
ks (Table (Table -> [(String, Value)]
forall k a. Map k a -> [(k, a)]
Map.assocs -> [(String
k,Value
v)])) = NonEmpty String -> Value -> Doc DocClass
go (String -> NonEmpty String -> NonEmpty String
forall a. a -> NonEmpty a -> NonEmpty a
NonEmpty.cons String
k NonEmpty String
ks) Value
v
go NonEmpty String
ks Value
v = NonEmpty String -> Doc DocClass
prettyKey (NonEmpty String -> NonEmpty String
forall a. NonEmpty a -> NonEmpty a
NonEmpty.reverse NonEmpty String
ks) Doc DocClass -> Doc DocClass -> Doc DocClass
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc DocClass
forall ann. Doc ann
equals Doc DocClass -> Doc DocClass -> Doc DocClass
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc DocClass
prettyValue Value
v
prettyValue :: Value -> TomlDoc
prettyValue :: Value -> Doc DocClass
prettyValue = \case
Integer Integer
i -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
NumberClass (Integer -> Doc DocClass
forall ann. Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
i)
Float Double
f
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
f -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
NumberClass Doc DocClass
"nan"
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
f -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
NumberClass (if Double
f Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 then Doc DocClass
"inf" else Doc DocClass
"-inf")
| Bool
otherwise -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
NumberClass (Double -> Doc DocClass
forall ann. Double -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Double
f)
Array [Value]
a -> Doc DocClass -> Doc DocClass
forall ann. Doc ann -> Doc ann
align ([Doc DocClass] -> Doc DocClass
forall ann. [Doc ann] -> Doc ann
list [Value -> Doc DocClass
prettyValue Value
v | Value
v <- [Value]
a])
Table Table
t -> Doc DocClass
forall ann. Doc ann
lbrace Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> (Doc DocClass -> Doc DocClass -> Doc DocClass)
-> [Doc DocClass] -> Doc DocClass
forall (t :: * -> *) ann.
Foldable t =>
(Doc ann -> Doc ann -> Doc ann) -> t (Doc ann) -> Doc ann
concatWith (Doc DocClass -> Doc DocClass -> Doc DocClass -> Doc DocClass
forall ann. Doc ann -> Doc ann -> Doc ann -> Doc ann
surround Doc DocClass
", ") [String -> Value -> Doc DocClass
prettyAssignment String
k Value
v | (String
k,Value
v) <- Table -> [(String, Value)]
forall k a. Map k a -> [(k, a)]
Map.assocs Table
t] Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> Doc DocClass
forall ann. Doc ann
rbrace
Bool Bool
True -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
BoolClass Doc DocClass
"true"
Bool Bool
False -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
BoolClass Doc DocClass
"false"
String String
str -> String -> Doc DocClass
prettySmartString String
str
TimeOfDay TimeOfDay
tod -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
DateClass (String -> Doc DocClass
forall a. IsString a => String -> a
fromString (TimeLocale -> String -> TimeOfDay -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%H:%M:%S%Q" TimeOfDay
tod))
ZonedTime ZonedTime
zt
| TimeZone -> Int
timeZoneMinutes (ZonedTime -> TimeZone
zonedTimeZone ZonedTime
zt) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 ->
DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
DateClass (String -> Doc DocClass
forall a. IsString a => String -> a
fromString (TimeLocale -> String -> ZonedTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%0Y-%m-%dT%H:%M:%S%QZ" ZonedTime
zt))
| Bool
otherwise -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
DateClass (String -> Doc DocClass
forall a. IsString a => String -> a
fromString (TimeLocale -> String -> ZonedTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%0Y-%m-%dT%H:%M:%S%Q%Ez" ZonedTime
zt))
LocalTime LocalTime
lt -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
DateClass (String -> Doc DocClass
forall a. IsString a => String -> a
fromString (TimeLocale -> String -> LocalTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%0Y-%m-%dT%H:%M:%S%Q" LocalTime
lt))
Day Day
d -> DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
DateClass (String -> Doc DocClass
forall a. IsString a => String -> a
fromString (TimeLocale -> String -> Day -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%0Y-%m-%d" Day
d))
prettySmartString :: String -> TomlDoc
prettySmartString :: String -> Doc DocClass
prettySmartString String
str
| Char
'\n' Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
str =
(Int -> Doc DocClass) -> Doc DocClass
forall ann. (Int -> Doc ann) -> Doc ann
column \Int
i ->
(PageWidth -> Doc DocClass) -> Doc DocClass
forall ann. (PageWidth -> Doc ann) -> Doc ann
pageWidth \case
AvailablePerLine Int
n Double
_ | String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
str Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i ->
String -> Doc DocClass
prettyMlString String
str
PageWidth
_ -> String -> Doc DocClass
prettyString String
str
| Bool
otherwise = String -> Doc DocClass
prettyString String
str
prettyMlString :: String -> TomlDoc
prettyMlString :: String -> Doc DocClass
prettyMlString String
str = DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
StringClass ((Int -> Doc DocClass) -> Doc DocClass
forall ann. (Int -> Doc ann) -> Doc ann
column \Int
i -> Int -> Doc DocClass -> Doc DocClass
forall ann. Int -> Doc ann -> Doc ann
hang (-Int
i) (String -> Doc DocClass
forall a. IsString a => String -> a
fromString (String -> String
quoteMlString String
str)))
prettyString :: String -> TomlDoc
prettyString :: String -> Doc DocClass
prettyString String
str = DocClass -> Doc DocClass -> Doc DocClass
forall ann. ann -> Doc ann -> Doc ann
annotate DocClass
StringClass (String -> Doc DocClass
forall a. IsString a => String -> a
fromString (String -> String
quoteString String
str))
isSimple :: Value -> Bool
isSimple :: Value -> Bool
isSimple = \case
Integer Integer
_ -> Bool
True
Float Double
_ -> Bool
True
Bool Bool
_ -> Bool
True
String String
_ -> Bool
True
TimeOfDay TimeOfDay
_ -> Bool
True
ZonedTime ZonedTime
_ -> Bool
True
LocalTime LocalTime
_ -> Bool
True
Day Day
_ -> Bool
True
Table Table
x -> Table -> Bool
isSingularTable Table
x
Array [Value]
x -> [Value] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Value]
x Bool -> Bool -> Bool
|| Bool -> Bool
not ((Value -> Bool) -> [Value] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Value -> Bool
isTable [Value]
x)
isAlwaysSimple :: Value -> Bool
isAlwaysSimple :: Value -> Bool
isAlwaysSimple = \case
Integer Integer
_ -> Bool
True
Float Double
_ -> Bool
True
Bool Bool
_ -> Bool
True
String String
_ -> Bool
True
TimeOfDay TimeOfDay
_ -> Bool
True
ZonedTime ZonedTime
_ -> Bool
True
LocalTime LocalTime
_ -> Bool
True
Day Day
_ -> Bool
True
Table Table
_ -> Bool
False
Array [Value]
x -> [Value] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Value]
x Bool -> Bool -> Bool
|| Bool -> Bool
not ((Value -> Bool) -> [Value] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Value -> Bool
isTable [Value]
x)
isTable :: Value -> Bool
isTable :: Value -> Bool
isTable Table {} = Bool
True
isTable Value
_ = Bool
False
isSingularTable :: Table -> Bool
isSingularTable :: Table -> Bool
isSingularTable (Table -> [Value]
forall k a. Map k a -> [a]
Map.elems -> [Value
v]) = Value -> Bool
isSimple Value
v
isSingularTable Table
_ = Bool
False
prettyToml ::
Table ->
TomlDoc
prettyToml :: Table -> Doc DocClass
prettyToml = KeyProjection -> SectionKind -> [String] -> Table -> Doc DocClass
prettyToml_ KeyProjection
NoProjection SectionKind
TableKind []
prettyTomlOrdered ::
Ord a =>
([String] -> String -> a) ->
Table ->
TomlDoc
prettyTomlOrdered :: forall a.
Ord a =>
([String] -> String -> a) -> Table -> Doc DocClass
prettyTomlOrdered [String] -> String -> a
proj = KeyProjection -> SectionKind -> [String] -> Table -> Doc DocClass
prettyToml_ (([String] -> String -> a) -> KeyProjection
forall a. Ord a => ([String] -> String -> a) -> KeyProjection
KeyProjection [String] -> String -> a
proj) SectionKind
TableKind []
data KeyProjection where
NoProjection :: KeyProjection
KeyProjection :: Ord a => ([String] -> String -> a) -> KeyProjection
prettyToml_ :: KeyProjection -> SectionKind -> [String] -> Table -> TomlDoc
prettyToml_ :: KeyProjection -> SectionKind -> [String] -> Table -> Doc DocClass
prettyToml_ KeyProjection
mbKeyProj SectionKind
kind [String]
prefix Table
t = [Doc DocClass] -> Doc DocClass
forall ann. [Doc ann] -> Doc ann
vcat ([Doc DocClass]
topLines [Doc DocClass] -> [Doc DocClass] -> [Doc DocClass]
forall a. [a] -> [a] -> [a]
++ [Doc DocClass]
subtables)
where
order :: [(String, Value)] -> [(String, Value)]
order =
case KeyProjection
mbKeyProj of
KeyProjection
NoProjection -> [(String, Value)] -> [(String, Value)]
forall a. a -> a
id
KeyProjection [String] -> String -> a
f -> ((String, Value) -> a) -> [(String, Value)] -> [(String, Value)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn ([String] -> String -> a
f [String]
prefix (String -> a)
-> ((String, Value) -> String) -> (String, Value) -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Value) -> String
forall a b. (a, b) -> a
fst)
kvs :: [(String, Value)]
kvs = [(String, Value)] -> [(String, Value)]
order (Table -> [(String, Value)]
forall k a. Map k a -> [(k, a)]
Map.assocs Table
t)
simpleToml :: Bool
simpleToml = (Value -> Bool) -> Table -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Value -> Bool
isSimple Table
t
([(String, Value)]
simple, [(String, Value)]
sections) = ((String, Value) -> Bool)
-> [(String, Value)] -> ([(String, Value)], [(String, Value)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (Value -> Bool
isAlwaysSimple (Value -> Bool)
-> ((String, Value) -> Value) -> (String, Value) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Value) -> Value
forall a b. (a, b) -> b
snd) [(String, Value)]
kvs
topLines :: [Doc DocClass]
topLines = [[Doc DocClass] -> Doc DocClass
forall m. Monoid m => [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold [Doc DocClass]
topElts | let topElts :: [Doc DocClass]
topElts = [Doc DocClass]
headers [Doc DocClass] -> [Doc DocClass] -> [Doc DocClass]
forall a. [a] -> [a] -> [a]
++ [Doc DocClass]
assignments, Bool -> Bool
not ([Doc DocClass] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Doc DocClass]
topElts)]
headers :: [Doc DocClass]
headers =
case [String] -> Maybe (NonEmpty String)
forall a. [a] -> Maybe (NonEmpty a)
NonEmpty.nonEmpty [String]
prefix of
Just NonEmpty String
key | Bool
simpleToml Bool -> Bool -> Bool
|| Bool -> Bool
not ([(String, Value)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, Value)]
simple) Bool -> Bool -> Bool
|| [(String, Value)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, Value)]
sections Bool -> Bool -> Bool
|| SectionKind
kind SectionKind -> SectionKind -> Bool
forall a. Eq a => a -> a -> Bool
== SectionKind
ArrayTableKind ->
[SectionKind -> NonEmpty String -> Doc DocClass
prettySectionKind SectionKind
kind NonEmpty String
key Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> Doc DocClass
forall ann. Doc ann
hardline]
Maybe (NonEmpty String)
_ -> []
assignments :: [Doc DocClass]
assignments = [String -> Value -> Doc DocClass
prettyAssignment String
k Value
v Doc DocClass -> Doc DocClass -> Doc DocClass
forall a. Semigroup a => a -> a -> a
<> Doc DocClass
forall ann. Doc ann
hardline | (String
k,Value
v) <- if Bool
simpleToml then [(String, Value)]
kvs else [(String, Value)]
simple]
subtables :: [Doc DocClass]
subtables = [[String] -> Value -> Doc DocClass
prettySection ([String]
prefix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
k]) Value
v | Bool -> Bool
not Bool
simpleToml, (String
k,Value
v) <- [(String, Value)]
sections]
prettySection :: [String] -> Value -> Doc DocClass
prettySection [String]
key (Table Table
tab) =
KeyProjection -> SectionKind -> [String] -> Table -> Doc DocClass
prettyToml_ KeyProjection
mbKeyProj SectionKind
TableKind [String]
key Table
tab
prettySection [String]
key (Array [Value]
a) =
[Doc DocClass] -> Doc DocClass
forall ann. [Doc ann] -> Doc ann
vcat [KeyProjection -> SectionKind -> [String] -> Table -> Doc DocClass
prettyToml_ KeyProjection
mbKeyProj SectionKind
ArrayTableKind [String]
key Table
tab | Table Table
tab <- [Value]
a]
prettySection [String]
_ Value
_ = String -> Doc DocClass
forall a. HasCallStack => String -> a
error String
"prettySection applied to simple value"
prettySemanticError :: SemanticError -> String
prettySemanticError :: SemanticError -> String
prettySemanticError (SemanticError String
key SemanticErrorKind
kind) =
String -> String -> String -> String
forall r. PrintfType r => String -> r
printf String
"key error: %s %s" (Doc Any -> String
forall a. Show a => a -> String
show (String -> Doc Any
forall a. String -> Doc a
prettySimpleKey String
key))
case SemanticErrorKind
kind of
SemanticErrorKind
AlreadyAssigned -> String
"is already assigned" :: String
SemanticErrorKind
ClosedTable -> String
"is a closed table"
SemanticErrorKind
ImplicitlyTable -> String
"is already implicitly defined to be a table"
prettyMatchMessage :: MatchMessage -> String
prettyMatchMessage :: MatchMessage -> String
prettyMatchMessage (MatchMessage [Scope]
scope String
msg) =
String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in top" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Scope -> String -> String) -> String -> [Scope] -> String
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Scope -> String -> String
f String
"" [Scope]
scope
where
f :: Scope -> String -> String
f (ScopeIndex Int
i) = (Char
'[' Char -> String -> String
forall a. a -> [a] -> [a]
:) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Show a => a -> String -> String
shows Int
i (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
']'Char -> String -> String
forall a. a -> [a] -> [a]
:)
f (ScopeKey String
key) = (Char
'.' Char -> String -> String
forall a. a -> [a] -> [a]
:) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Any -> String -> String
forall a. Show a => a -> String -> String
shows (String -> Doc Any
forall a. String -> Doc a
prettySimpleKey String
key)
prettyLocated :: Located String -> String
prettyLocated :: Located String -> String
prettyLocated (Located Position
p String
s) = String -> Int -> Int -> String -> String
forall r. PrintfType r => String -> r
printf String
"%d:%d: %s" (Position -> Int
posLine Position
p) (Position -> Int
posColumn Position
p) String
s