{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE ViewPatterns          #-}
module Language.Ninja.Errors.Parser
  ( 
    ParseError (..)
  , throwParseError, throwGenericParseError
  , throwLexBindingFailure
  , throwLexExpectedColon
  , throwLexUnexpectedDollar
  , throwLexUnexpectedSeparator
  , throwLexParsecError
  , throwParseBadDepthField
  , throwParseUnexpectedBinding
  ) where
import           Control.Exception         (Exception)
import           Control.Monad.Error.Class (MonadError (throwError))
import           GHC.Generics              (Generic)
import           Data.Text                 (Text)
import           Data.Aeson                ((.=))
import qualified Data.Aeson                as Aeson
import qualified Text.Megaparsec           as M
import           Data.Foldable             (toList)
import           Flow                      ((|>))
data ParseError
  = 
    
    
    GenericParseError      !Text
  | 
    
    
    LexBindingFailure      !Text
  | 
    
    
    LexExpectedColon
  | 
    
    
    LexUnexpectedDollar
  | 
    
    
    LexUnexpectedSeparator Char
  | 
    
    
    LexParsecError         !(M.ParseError Char M.Dec)
  | 
    
    
    ParseBadDepthField     !Text
  | 
    
    
    ParseUnexpectedBinding !Text
  deriving (Eq, Show, Generic)
throwParseError :: (MonadError ParseError m) => ParseError -> m a
throwParseError = throwError
throwGenericParseError :: (MonadError ParseError m) => Text -> m a
throwGenericParseError msg = throwParseError (GenericParseError msg)
throwLexBindingFailure :: (MonadError ParseError m) => Text -> m a
throwLexBindingFailure t = throwParseError (LexBindingFailure t)
throwLexExpectedColon :: (MonadError ParseError m) => m a
throwLexExpectedColon = throwParseError LexExpectedColon
throwLexUnexpectedDollar :: (MonadError ParseError m) => m a
throwLexUnexpectedDollar = throwParseError LexUnexpectedDollar
throwLexUnexpectedSeparator :: (MonadError ParseError m) => Char -> m a
throwLexUnexpectedSeparator c = throwParseError (LexUnexpectedSeparator c)
throwLexParsecError :: (MonadError ParseError m)
                    => M.ParseError Char M.Dec -> m a
throwLexParsecError pe = throwParseError (LexParsecError pe)
throwParseBadDepthField :: (MonadError ParseError m) => Text -> m a
throwParseBadDepthField t = throwParseError (ParseBadDepthField t)
throwParseUnexpectedBinding :: (MonadError ParseError m) => Text -> m a
throwParseUnexpectedBinding t = throwParseError (ParseUnexpectedBinding t)
instance Exception ParseError
instance Aeson.ToJSON ParseError where
  toJSON = go
    where
      go (GenericParseError t)      = obj "generic-parse-error"      t
      go (LexBindingFailure t)      = obj "lex-binding-failure"      t
      go LexExpectedColon           = obj "lex-expected-colon"       nullJ
      go LexUnexpectedDollar        = obj "lex-unexpected-dollar"    nullJ
      go (LexUnexpectedSeparator c) = obj "lex-unexpected-separator" c
      go (LexParsecError pe)        = obj "lex-parsec-error"         (peJ pe)
      go (ParseBadDepthField t)     = obj "parse-bad-depth-field"    t
      go (ParseUnexpectedBinding t) = obj "parse-unexpected-binding" t
      peJ :: M.ParseError Char M.Dec -> Aeson.Value
      peJ (decomposePE -> (pos, custom, unexpected, expected))
        = [ "pos"        .= (posJ     <$> pos)
          , "unexpected" .= (errItemJ <$> unexpected)
          , "expected"   .= (errItemJ <$> expected)
          , "custom"     .= (decJ     <$> custom)
          ] |> Aeson.object
      decomposePE :: M.ParseError Char M.Dec
                  -> ( [M.SourcePos], [M.Dec]
                     , [M.ErrorItem Char], [M.ErrorItem Char] )
      decomposePE (M.ParseError {..})
        = ( toList errorPos, toList errorCustom
          , toList errorUnexpected, toList errorExpected )
      posJ :: M.SourcePos -> Aeson.Value
      posJ (M.SourcePos {..}) = [ "name"   .= sourceName
                                , "line"   .= M.unPos sourceLine
                                , "column" .= M.unPos sourceColumn
                                ] |> Aeson.object
      errItemJ :: M.ErrorItem Char -> Aeson.Value
      errItemJ (M.Tokens xs) = Aeson.toJSON (toList xs)
      errItemJ (M.Label  xs) = Aeson.toJSON (toList xs)
      errItemJ M.EndOfInput  = "eof"
      decJ :: M.Dec -> Aeson.Value
      decJ (M.DecFail message)        = [ "message"  .= message
                                        ] |> Aeson.object |> obj "fail"
      decJ (M.DecIndentation ord x y) = [ "ordering" .= ord
                                        , "start"    .= M.unPos x
                                        , "end"      .= M.unPos y
                                        ] |> Aeson.object |> obj "indentation"
      obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
      obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
      nullJ = Aeson.Null :: Aeson.Value