module Toml.Parser
( TomlParseError (..)
, parse
, parseKey
) where
import Control.DeepSeq (NFData)
import Data.Text (Text)
import GHC.Generics (Generic)
import Toml.Parser.Item (tomlP)
import Toml.Parser.Key (keyP)
import Toml.Parser.Validate (validateItems)
import Toml.Type.Key (Key)
import Toml.Type.TOML (TOML)
import qualified Data.Text as T
import qualified Toml.Parser.Core as P (errorBundlePretty, parse)
newtype TomlParseError = TomlParseError
{ TomlParseError -> Text
unTomlParseError :: Text
} deriving stock (Int -> TomlParseError -> ShowS
[TomlParseError] -> ShowS
TomlParseError -> String
(Int -> TomlParseError -> ShowS)
-> (TomlParseError -> String)
-> ([TomlParseError] -> ShowS)
-> Show TomlParseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TomlParseError] -> ShowS
$cshowList :: [TomlParseError] -> ShowS
show :: TomlParseError -> String
$cshow :: TomlParseError -> String
showsPrec :: Int -> TomlParseError -> ShowS
$cshowsPrec :: Int -> TomlParseError -> ShowS
Show, (forall x. TomlParseError -> Rep TomlParseError x)
-> (forall x. Rep TomlParseError x -> TomlParseError)
-> Generic TomlParseError
forall x. Rep TomlParseError x -> TomlParseError
forall x. TomlParseError -> Rep TomlParseError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TomlParseError x -> TomlParseError
$cfrom :: forall x. TomlParseError -> Rep TomlParseError x
Generic)
deriving newtype (TomlParseError -> TomlParseError -> Bool
(TomlParseError -> TomlParseError -> Bool)
-> (TomlParseError -> TomlParseError -> Bool) -> Eq TomlParseError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TomlParseError -> TomlParseError -> Bool
$c/= :: TomlParseError -> TomlParseError -> Bool
== :: TomlParseError -> TomlParseError -> Bool
$c== :: TomlParseError -> TomlParseError -> Bool
Eq, TomlParseError -> ()
(TomlParseError -> ()) -> NFData TomlParseError
forall a. (a -> ()) -> NFData a
rnf :: TomlParseError -> ()
$crnf :: TomlParseError -> ()
NFData)
parse :: Text -> Either TomlParseError TOML
parse :: Text -> Either TomlParseError TOML
parse t :: Text
t = case Parsec Void Text [TomlItem]
-> String -> Text -> Either (ParseErrorBundle Text Void) [TomlItem]
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
P.parse Parsec Void Text [TomlItem]
tomlP "" Text
t of
Left err :: ParseErrorBundle Text Void
err -> TomlParseError -> Either TomlParseError TOML
forall a b. a -> Either a b
Left (TomlParseError -> Either TomlParseError TOML)
-> TomlParseError -> Either TomlParseError TOML
forall a b. (a -> b) -> a -> b
$ Text -> TomlParseError
TomlParseError (Text -> TomlParseError) -> Text -> TomlParseError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ParseErrorBundle Text Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
P.errorBundlePretty ParseErrorBundle Text Void
err
Right items :: [TomlItem]
items -> case [TomlItem] -> Either ValidationError TOML
validateItems [TomlItem]
items of
Left err :: ValidationError
err -> TomlParseError -> Either TomlParseError TOML
forall a b. a -> Either a b
Left (TomlParseError -> Either TomlParseError TOML)
-> TomlParseError -> Either TomlParseError TOML
forall a b. (a -> b) -> a -> b
$ Text -> TomlParseError
TomlParseError (Text -> TomlParseError) -> Text -> TomlParseError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ValidationError -> String
forall a. Show a => a -> String
show ValidationError
err
Right toml :: TOML
toml -> TOML -> Either TomlParseError TOML
forall a b. b -> Either a b
Right TOML
toml
parseKey :: Text -> Either TomlParseError Key
parseKey :: Text -> Either TomlParseError Key
parseKey t :: Text
t = case Parsec Void Text Key
-> String -> Text -> Either (ParseErrorBundle Text Void) Key
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
P.parse Parsec Void Text Key
keyP "" Text
t of
Left err :: ParseErrorBundle Text Void
err -> TomlParseError -> Either TomlParseError Key
forall a b. a -> Either a b
Left (TomlParseError -> Either TomlParseError Key)
-> TomlParseError -> Either TomlParseError Key
forall a b. (a -> b) -> a -> b
$ Text -> TomlParseError
TomlParseError (Text -> TomlParseError) -> Text -> TomlParseError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ParseErrorBundle Text Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
P.errorBundlePretty ParseErrorBundle Text Void
err
Right key :: Key
key -> Key -> Either TomlParseError Key
forall a b. b -> Either a b
Right Key
key