less prototype, less bad code implementation of CCHM type theory
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

191 lines
7.4 KiB

  1. {-# OPTIONS_GHC -Wno-orphans #-}
  2. {-# LANGUAGE ViewPatterns #-}
  3. module Syntax.Pretty where
  4. import Control.Arrow (Arrow(first))
  5. import qualified Data.Map.Strict as Map
  6. import qualified Data.Text.Lazy as L
  7. import qualified Data.Set as Set
  8. import qualified Data.Text as T
  9. import Data.Map.Strict (Map)
  10. import Data.Text (Text)
  11. import Data.Set (Set)
  12. import Data.Generics
  13. import Presyntax.Presyntax (Plicity(..))
  14. import Prettyprinter.Render.Terminal
  15. import Prettyprinter
  16. import Syntax
  17. instance Pretty Name where
  18. pretty = pretty . getNameText
  19. prettyTm :: Term -> Doc AnsiStyle
  20. prettyTm = prettyTm . everywhere (mkT beautify) where
  21. prettyTm (Ref v) =
  22. case T.uncons (getNameText v) of
  23. Just ('.', w) -> keyword (pretty w)
  24. _ -> pretty v
  25. prettyTm (Con v) = keyword (pretty v)
  26. prettyTm (Data v) = operator (pretty v)
  27. prettyTm (App Im f x) = parenFun f <+> braces (prettyTm x)
  28. prettyTm (App Ex f x) = parenFun f <+> parenArg x
  29. prettyTm (Pair x y) = parens $ prettyTm x <> operator comma <+> prettyTm y
  30. prettyTm (Proj1 x) = prettyTm x <> operator (pretty ".1")
  31. prettyTm (Proj2 x) = prettyTm x <> operator (pretty ".2")
  32. prettyTm l@(Lam _ _ _) = pretty '\\' <> hsep (map prettyArgList al) <+> pretty "->" <+> prettyTm bod where
  33. unwindLam (Lam p x y) = first ((p, x):) (unwindLam y)
  34. unwindLam (PathIntro _ _ _ (Lam p x y)) = first ((p, x):) (unwindLam y)
  35. unwindLam t = ([], t)
  36. (al, bod) = unwindLam l
  37. used = freeVars bod
  38. prettyArgList (Ex, v)
  39. | v `Set.member` used = pretty v
  40. | otherwise = pretty "_"
  41. prettyArgList (Im, v)
  42. | v `Set.member` used = braces $ pretty v
  43. | otherwise = pretty "_"
  44. prettyTm (Meta x) = keyword $ pretty '?' <> pretty (mvName x)
  45. prettyTm Type{} = keyword $ pretty "Type"
  46. prettyTm Typeω{} = keyword $ pretty "Typeω"
  47. prettyTm I{} = keyword $ pretty "I"
  48. prettyTm I0{} = keyword $ pretty "i0"
  49. prettyTm I1{} = keyword $ pretty "i1"
  50. prettyTm (Pi Ex (T.unpack . getNameText -> "_") d r) = prettyDom d <+> pretty "->" <+> prettyTm r
  51. prettyTm (Pi Im v d r) = group (braces (pretty v <+> colon <+> prettyTm d)) <> softline <> pretty "->" <+> prettyTm r
  52. prettyTm (Pi Ex v d r) = group (parens (pretty v <+> colon <+> prettyTm d)) <> softline <> pretty "->" <+> prettyTm r
  53. prettyTm (Sigma (T.unpack . getNameText -> "_") d r) = prettyDom d <+> pretty "*" <+> prettyTm r
  54. prettyTm (Sigma v d r) = parens (pretty v <+> colon <+> prettyTm d) <+> pretty "*" <+> prettyTm r
  55. prettyTm (IAnd x y) = parens $ prettyTm x <+> operator (pretty "&&") <+> prettyTm y
  56. prettyTm (IOr x y) = parens $ prettyTm x <+> operator (pretty "||") <+> prettyTm y
  57. prettyTm (INot x) = operator (pretty '~') <> prettyTm x
  58. prettyTm (System xs) = braces (mempty <+> hsep (punctuate comma (map go (Map.toList xs))) <+> mempty) where
  59. go (f, t) = prettyTm f <+> operator (pretty "=>") <+> prettyTm t
  60. prettyTm (Case x xs) = keyword (pretty "case") <+> prettyTm x <+> keyword (pretty "of") <+> braces (prettyCase xs)
  61. prettyTm x = error (show x)
  62. prettyCase = vsep . map go where
  63. go (x, xs) = prettyTm x <+> operator (pretty "=>") <+> prettyTm xs
  64. beautify (PathP l x y) = toFun "PathP" [l, x, y]
  65. beautify (IElim _ _ _ f i) = App Ex f i
  66. beautify (PathIntro _ _ _ f) = f
  67. beautify (IsOne phi) = toFun "IsOne" [phi]
  68. beautify ItIsOne = Ref (Bound (T.pack ".1=1") 0)
  69. beautify (Lam Ex v (App Ex f (Ref v')))
  70. | v == v', v `Set.notMember` freeVars f = f
  71. beautify (Partial phi a) = toFun "Partial" [phi, a]
  72. beautify (PartialP phi a) = toFun "PartialP" [phi, a]
  73. beautify (Comp a phi u a0) = toFun "comp" [a, phi, u, a0]
  74. beautify (Sub a phi u) = toFun "Sub" [a, phi, u]
  75. beautify (Inc _ _ u) = toFun "inS" [u]
  76. beautify (Ouc _ _ _ u) = toFun "outS" [u]
  77. beautify (GlueTy a I1 _ _) = a
  78. beautify (GlueTy a b c d) = toFun "Glue" [a,b,c,d]
  79. beautify (Glue a b c d e f) = toFun "glue" [a,b,c,d,e,f]
  80. beautify (Unglue a b c d e) = toFun "unglue" [a,b,c,d,e]
  81. beautify x = x
  82. toFun s a = foldl (App Ex) (Ref (Bound (T.pack ('.':s)) 0)) a
  83. keyword :: Doc AnsiStyle -> Doc AnsiStyle
  84. keyword = annotate (color Magenta)
  85. operator :: Doc AnsiStyle -> Doc AnsiStyle
  86. operator = annotate (color Yellow)
  87. parenArg :: Term -> Doc AnsiStyle
  88. parenArg x@App{} = parens (prettyTm x)
  89. parenArg x@IElim{} = parens (prettyTm x)
  90. parenArg x@IsOne{} = parens $ prettyTm x
  91. parenArg x@Partial{} = parens $ prettyTm x
  92. parenArg x@PartialP{} = parens $ prettyTm x
  93. parenArg x@Sub{} = parens $ prettyTm x
  94. parenArg x@Inc{} = parens $ prettyTm x
  95. parenArg x@Ouc{} = parens $ prettyTm x
  96. parenArg x@Comp{} = parens $ prettyTm x
  97. parenArg x = prettyDom x
  98. prettyDom :: Term -> Doc AnsiStyle
  99. prettyDom x@Pi{} = parens (prettyTm x)
  100. prettyDom x@Sigma{} = parens (prettyTm x)
  101. prettyDom x = parenFun x
  102. parenFun :: Term -> Doc AnsiStyle
  103. parenFun x@Lam{} = parens $ prettyTm x
  104. parenFun x@PathIntro{} = parens $ prettyTm x
  105. parenFun x = prettyTm x
  106. render :: Doc AnsiStyle -> Text
  107. render = L.toStrict . renderLazy . layoutSmart defaultLayoutOptions
  108. showValue :: Value -> String
  109. showValue = L.unpack . renderLazy . layoutSmart defaultLayoutOptions . prettyTm . quote
  110. showFace :: Map Head Bool -> Doc AnsiStyle
  111. showFace = hsep . map go . Map.toList where
  112. go (h, b) = parens $ prettyTm (quote (VNe h mempty)) <+> operator (pretty "=") <+> pretty (if b then "i1" else "i0")
  113. freeVars :: Term -> Set Name
  114. freeVars (Ref v) = Set.singleton v
  115. freeVars (App _ f x) = Set.union (freeVars f) (freeVars x)
  116. freeVars (Pi _ n x y) = Set.union (freeVars x) (n `Set.delete` freeVars y)
  117. freeVars (Lam _ n x) = n `Set.delete` freeVars x
  118. freeVars (Let ns x) = Set.union (freeVars x `Set.difference` bound) freed where
  119. bound = Set.fromList (map (\(x, _, _) -> x) ns)
  120. freed = foldr (\(_, x, y) -> Set.union (Set.union (freeVars x) (freeVars y))) mempty ns
  121. freeVars Meta{} = mempty
  122. freeVars Con{} = mempty
  123. freeVars Data{} = mempty
  124. freeVars Type{} = mempty
  125. freeVars Typeω{} = mempty
  126. freeVars I{} = mempty
  127. freeVars I0{} = mempty
  128. freeVars I1{} = mempty
  129. freeVars (Sigma n x y) = Set.union (freeVars x) (n `Set.delete` freeVars y)
  130. freeVars (Pair x y) = Set.unions $ map freeVars [x, y]
  131. freeVars (Proj1 x) = Set.unions $ map freeVars [x]
  132. freeVars (Proj2 x) = Set.unions $ map freeVars [x]
  133. freeVars (IAnd x y) = Set.unions $ map freeVars [x, y]
  134. freeVars (IOr x y) = Set.unions $ map freeVars [x, y]
  135. freeVars (INot x) = Set.unions $ map freeVars [x]
  136. freeVars (PathP x y z) = Set.unions $ map freeVars [x, y, z]
  137. freeVars (IElim x y z a b) = Set.unions $ map freeVars [x, y, z, a, b]
  138. freeVars (PathIntro x y z a) = Set.unions $ map freeVars [x, y, z, a]
  139. freeVars (IsOne a) = Set.unions $ map freeVars [a]
  140. freeVars ItIsOne{} = mempty
  141. freeVars (Partial x y) = Set.unions $ map freeVars [x, y]
  142. freeVars (PartialP x y) = Set.unions $ map freeVars [x, y]
  143. freeVars (System fs) = foldr (\(x, y) -> Set.union (Set.union (freeVars x) (freeVars y))) mempty (Map.toList fs)
  144. freeVars (Sub x y z) = Set.unions $ map freeVars [x, y, z]
  145. freeVars (Inc x y z) = Set.unions $ map freeVars [x, y, z]
  146. freeVars (Ouc x y z a) = Set.unions $ map freeVars [x, y, z, a]
  147. freeVars (Comp x y z a) = Set.unions $ map freeVars [x, y, z, a]
  148. freeVars (GlueTy x y z a) = Set.unions $ map freeVars [x, y, z, a]
  149. freeVars (Glue x y z a b c) = Set.unions $ map freeVars [x, y, z, a, b, c]
  150. freeVars (Unglue x y z a c) = Set.unions $ map freeVars [x, y, z, a, c]
  151. freeVars (Case x y) = freeVars x <> foldMap (freeVars . snd) y