module Toml.Bi.Code
       ( 
         BiToml
       , Env
       , St
         
       , DecodeException (..)
       , LoadTomlException (..)
       , prettyException
         
       , decode
       , decodeFile
       , encode
       ) where
import Control.Exception (Exception, throwIO)
import Control.Monad.Except (ExceptT, runExceptT)
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Reader (Reader, runReader)
import Control.Monad.State (State, execState)
import Control.Monad.Trans.Maybe (MaybeT (..))
import Data.Bifunctor (first)
import Data.Foldable (toList)
import Data.Semigroup (Semigroup (..))
import Data.Text (Text)
import Toml.Bi.Monad (Bi, Bijection (..))
import Toml.Parser (ParseException (..), parse)
import Toml.PrefixTree (Key (..), unPiece)
import Toml.Printer (prettyToml)
import Toml.Type (TOML (..), TValue, showType)
import qualified Data.Text as Text
import qualified Data.Text.IO as TIO
data DecodeException
    = TrivialError
    | KeyNotFound Key  
    | TableNotFound Key  
    | TypeMismatch Key Text TValue  
    | ParseError ParseException  
    deriving (Eq, Show)  
instance Semigroup DecodeException where
    TrivialError <> e = e
    e <> _ = e
instance Monoid DecodeException where
    mempty = TrivialError
    mappend = (<>)
prettyException :: DecodeException -> Text
prettyException = \case
    TrivialError -> "Using 'empty' parser"
    KeyNotFound name -> "Key " <> joinKey name <> " not found"
    TableNotFound name -> "Table [" <> joinKey name <> "] not found"
    TypeMismatch name expected actual -> "Expected type " <> expected <> " for key " <> joinKey name
                                      <> " but got: " <> Text.pack (showType actual)
    ParseError (ParseException msg) -> "Parse error during conversion from TOML to custom user type: \n  " <> msg
  where
    joinKey :: Key -> Text
    joinKey = Text.intercalate "." . map unPiece . toList . unKey
type Env = ExceptT DecodeException (Reader TOML)
type St = MaybeT (State TOML)
type BiToml a = Bi Env St a
decode :: BiToml a -> Text -> Either DecodeException a
decode biToml text = do
    toml <- first ParseError (parse text)
    runReader (runExceptT $ biRead biToml) toml
encode :: BiToml a -> a -> Text
encode bi obj = prettyToml $ execState (runMaybeT $ biWrite bi obj) mempty
data LoadTomlException = LoadTomlException FilePath Text
instance Show LoadTomlException where
    show (LoadTomlException filePath msg) = "Couldnt parse file " ++ filePath ++ ": " ++ show msg
instance Exception LoadTomlException
decodeFile :: (MonadIO m) => BiToml a -> FilePath -> m a
decodeFile biToml filePath = liftIO $
    (decode biToml <$> TIO.readFile filePath) >>= errorWhenLeft
  where
    errorWhenLeft :: Either DecodeException a -> IO a
    errorWhenLeft (Left e)   = throwIO $ LoadTomlException filePath $ prettyException e
    errorWhenLeft (Right pc) = pure pc