{-# LANGUAGE PolyKinds #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Typing.Show where import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TLB import qualified Symantic.Document as Doc import Language.Symantic.Grammar import Language.Symantic.Typing.Type import Language.Symantic.Typing.Module import Language.Symantic.Typing.Document stringDocTerm :: Doc.Plain TLB.Builder -> String stringDocTerm = TL.unpack . TLB.toLazyText . Doc.runPlain showType :: Config_Doc_Type -> Type src vs t -> String showType conf ty = stringDocTerm $ docType conf 0 ty showTypeS :: Config_Doc_Type -> Precedence -> Type src vs t -> ShowS showTypeS conf pr ty = showString $ stringDocTerm $ docType conf pr ty showTypes :: Config_Doc_Type -> Types src vs ts -> String showTypes conf tys = stringDocTerm $ docTypes conf tys showTypesS :: Config_Doc_Type -> Types src vs ts -> ShowS showTypesS conf tys = showString $ stringDocTerm $ docTypes conf tys instance NameTyOf c => Show (Const src c) where showsPrec _p = showString . stringDocTerm . docConst mempty instance Source src => Show (Type src vs t) where showsPrec = showTypeS config_Doc_Type instance Source src => Show (TypeK src vs kt) where showsPrec p (TypeK t) = showsPrec p t instance Source src => Show (TypeVT src) where showsPrec p (TypeVT t) = showsPrec p t instance Source src => Show (TypeT src vs) where showsPrec p (TypeT t) = showsPrec p t instance Source src => Show (Types src vs ts) where showsPrec _ = showTypesS config_Doc_Type