{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
module Expresso.TH.QQ (expressoType) where
import Control.Exception
import Language.Haskell.TH (ExpQ, Loc(..), Q, location, runIO)
import Language.Haskell.TH.Quote (QuasiQuoter(..), dataToExpQ)
import qualified Text.Parsec as P
import qualified Text.Parsec.Pos as P
import Text.Parsec.String
import Expresso.Parser
expressoType :: QuasiQuoter
expressoType = def { quoteExp = genTypeDecl }
def :: QuasiQuoter
def = QuasiQuoter
    { quoteExp  = failure "expressions"
    , quotePat  = failure "patterns"
    , quoteType = failure "types"
    , quoteDec  = failure "declarations"
    }
  where
    failure kind =
        fail $ "This quasi-quoter does not support splicing " ++ kind
genTypeDecl :: String -> ExpQ
genTypeDecl str = do
    l <- location'
    c <- runIO $ parseIO (P.setPosition l *> topLevel pTypeAnn) str
    dataToExpQ (const Nothing) c
location' :: Q P.SourcePos
location' = aux <$> location
  where
    aux :: Loc -> P.SourcePos
    aux loc = uncurry (P.newPos (loc_filename loc)) (loc_start loc)
parseIO :: Parser a -> String -> IO a
parseIO p str =
  case P.parse p "" str of
    Left err -> throwIO (userError (show err))
    Right a  -> return a