{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Singletons.TypeError (
TypeError, sTypeError, typeError,
ErrorMessage'(..), ErrorMessage, PErrorMessage,
Sing(SText, SShowType, (:%<>:), (:%$$:)), SErrorMessage,
ConvertPErrorMessage, showErrorMessage,
TextSym0, TextSym1,
ShowTypeSym0, ShowTypeSym1,
type (:<>:@#@$), type (:<>:@#@$$), type (:<>:@#@$$$),
type (:$$:@#@$), type (:$$:@#@$$), type (:$$:@#@$$$),
TypeErrorSym0, TypeErrorSym1
) where
import Data.Kind
import Data.Singletons.TH
import qualified Data.Text as Text
import qualified GHC.TypeLits as TL (ErrorMessage(..), TypeError)
import GHC.Stack (HasCallStack)
import GHC.TypeLits hiding (ErrorMessage(..), TypeError)
import Prelude hiding ((<>))
import Text.PrettyPrint (Doc, text, (<>), ($$))
data ErrorMessage' s
= Text s
| forall t. ShowType t
| ErrorMessage' s :<>: ErrorMessage' s
| ErrorMessage' s :$$: ErrorMessage' s
infixl 6 :<>:
infixl 5 :$$:
type ErrorMessage = ErrorMessage' Text.Text
type PErrorMessage = ErrorMessage' Symbol
data instance Sing :: PErrorMessage -> Type where
SText :: Sing t -> Sing ('Text t :: PErrorMessage)
SShowType :: Sing ty -> Sing ('ShowType ty :: PErrorMessage)
(:%<>:) :: Sing e1 -> Sing e2 -> Sing (e1 ':<>: e2 :: PErrorMessage)
(:%$$:) :: Sing e1 -> Sing e2 -> Sing (e1 ':$$: e2 :: PErrorMessage)
infixl 6 :%<>:
infixl 5 :%$$:
type SErrorMessage = (Sing :: PErrorMessage -> Type)
instance SingKind PErrorMessage where
type Demote PErrorMessage = ErrorMessage
fromSing (SText t) = Text (fromSing t)
fromSing (SShowType{}) = ShowType (error "Can't single ShowType")
fromSing (e1 :%<>: e2) = fromSing e1 :<>: fromSing e2
fromSing (e1 :%$$: e2) = fromSing e1 :$$: fromSing e2
toSing (Text t) = withSomeSing t $ SomeSing . SText
toSing (ShowType{}) = SomeSing $ SShowType (error "Can't single ShowType")
toSing (e1 :<>: e2) = withSomeSing e1 $ \sE1 ->
withSomeSing e2 $ \sE2 ->
SomeSing (sE1 :%<>: sE2)
toSing (e1 :$$: e2) = withSomeSing e1 $ \sE1 ->
withSomeSing e2 $ \sE2 ->
SomeSing (sE1 :%$$: sE2)
instance SingI t => SingI ('Text t :: PErrorMessage) where
sing = SText sing
instance SingI ty => SingI ('ShowType ty :: PErrorMessage) where
sing = SShowType sing
instance (SingI e1, SingI e2) => SingI (e1 ':<>: e2 :: PErrorMessage) where
sing = sing :%<>: sing
instance (SingI e1, SingI e2) => SingI (e1 ':$$: e2 :: PErrorMessage) where
sing = sing :%$$: sing
showErrorMessage :: ErrorMessage -> String
showErrorMessage = show . go
where
go :: ErrorMessage -> Doc
go (Text t) = text (Text.unpack t)
go (ShowType _) = text "<type>"
go (e1 :<>: e2) = go e1 <> go e2
go (e1 :$$: e2) = go e1 $$ go e2
typeError :: HasCallStack => ErrorMessage -> a
typeError = error . showErrorMessage
type family ConvertPErrorMessage (a :: PErrorMessage) :: TL.ErrorMessage where
ConvertPErrorMessage ('Text t) = 'TL.Text t
ConvertPErrorMessage ('ShowType ty) = 'TL.ShowType ty
ConvertPErrorMessage (e1 ':<>: e2) = ConvertPErrorMessage e1 'TL.:<>: ConvertPErrorMessage e2
ConvertPErrorMessage (e1 ':$$: e2) = ConvertPErrorMessage e1 'TL.:$$: ConvertPErrorMessage e2
type family TypeError (a :: PErrorMessage) :: b where
TypeError a = TL.TypeError (ConvertPErrorMessage a)
sTypeError :: HasCallStack => Sing err -> Sing (TypeError err)
sTypeError = typeError . fromSing
$(genDefunSymbols [''ErrorMessage', ''TypeError])
instance SingI (TextSym0 :: Symbol ~> PErrorMessage) where
sing = singFun1 SText
instance SingI (TyCon1 'Text :: Symbol ~> PErrorMessage) where
sing = singFun1 SText
instance SingI (ShowTypeSym0 :: t ~> PErrorMessage) where
sing = singFun1 SShowType
instance SingI (TyCon1 'ShowType :: t ~> PErrorMessage) where
sing = singFun1 SShowType
instance SingI ((:<>:@#@$) :: PErrorMessage ~> PErrorMessage ~> PErrorMessage) where
sing = singFun2 (:%<>:)
instance SingI (TyCon2 '(:<>:) :: PErrorMessage ~> PErrorMessage ~> PErrorMessage) where
sing = singFun2 (:%<>:)
instance SingI x => SingI ((:<>:@#@$$) x :: PErrorMessage ~> PErrorMessage) where
sing = singFun1 (sing @x :%<>:)
instance SingI x => SingI (TyCon1 ('(:<>:) x) :: PErrorMessage ~> PErrorMessage) where
sing = singFun1 (sing @x :%<>:)
instance SingI ((:$$:@#@$) :: PErrorMessage ~> PErrorMessage ~> PErrorMessage) where
sing = singFun2 (:%$$:)
instance SingI (TyCon2 '(:$$:) :: PErrorMessage ~> PErrorMessage ~> PErrorMessage) where
sing = singFun2 (:%$$:)
instance SingI x => SingI ((:$$:@#@$$) x :: PErrorMessage ~> PErrorMessage) where
sing = singFun1 (sing @x :%$$:)
instance SingI x => SingI (TyCon1 ('(:$$:) x) :: PErrorMessage ~> PErrorMessage) where
sing = singFun1 (sing @x :%$$:)
instance SingI TypeErrorSym0 where
sing = singFun1 sTypeError