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.

194 lines
7.5 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 (Bound x _) = pretty x
  19. pretty (Defined x _) = pretty x
  20. prettyTm :: Term -> Doc AnsiStyle
  21. prettyTm = prettyTm . everywhere (mkT beautify) where
  22. prettyTm (Ref v) =
  23. case T.uncons (getNameText v) of
  24. Just ('.', w) -> keyword (pretty w)
  25. _ -> pretty v
  26. prettyTm (App Im f x) = parenFun f <+> braces (prettyTm x)
  27. prettyTm (App Ex f x) = parenFun f <+> parenArg x
  28. prettyTm (Pair x y) = parens $ prettyTm x <> operator comma <+> prettyTm y
  29. prettyTm (Proj1 x) = prettyTm x <> operator (pretty ".1")
  30. prettyTm (Proj2 x) = prettyTm x <> operator (pretty ".2")
  31. prettyTm l@(Lam _ _ _) = pretty '\\' <> hsep (map prettyArgList al) <+> pretty "->" <+> prettyTm bod where
  32. unwindLam (Lam p x y) = first ((p, x):) (unwindLam y)
  33. unwindLam (PathIntro _ _ _ (Lam p x y)) = first ((p, x):) (unwindLam y)
  34. unwindLam t = ([], t)
  35. (al, bod) = unwindLam l
  36. used = freeVars bod
  37. prettyArgList (Ex, v)
  38. | v `Set.member` used = pretty v
  39. | otherwise = pretty "_"
  40. prettyArgList (Im, v)
  41. | v `Set.member` used = braces $ pretty v
  42. | otherwise = pretty "_"
  43. prettyTm (Meta x) = keyword $ pretty '?' <> pretty (mvName x)
  44. prettyTm Type{} = keyword $ pretty "Type"
  45. prettyTm Typeω{} = keyword $ pretty "Typeω"
  46. prettyTm I{} = keyword $ pretty "I"
  47. prettyTm I0{} = keyword $ pretty "i0"
  48. prettyTm I1{} = keyword $ pretty "i1"
  49. prettyTm (Pi Ex (T.unpack . getNameText -> "_") d r) = prettyDom d <+> pretty "->" <+> prettyTm r
  50. prettyTm (Pi Im v d r) = group (braces (pretty v <+> colon <+> prettyTm d)) <> softline <> pretty "->" <+> prettyTm r
  51. prettyTm (Pi Ex v d r) = group (parens (pretty v <+> colon <+> prettyTm d)) <> softline <> pretty "->" <+> prettyTm r
  52. prettyTm (Sigma (T.unpack . getNameText -> "_") d r) = prettyDom d <+> pretty "*" <+> prettyTm r
  53. prettyTm (Sigma v d r) = parens (pretty v <+> colon <+> prettyTm d) <+> pretty "*" <+> prettyTm r
  54. prettyTm (IAnd x y) = parens $ prettyTm x <+> operator (pretty "&&") <+> prettyTm y
  55. prettyTm (IOr x y) = parens $ prettyTm x <+> operator (pretty "||") <+> prettyTm y
  56. prettyTm (INot x) = operator (pretty '~') <> prettyTm x
  57. prettyTm (System xs) = braces (mempty <+> hsep (punctuate comma (map go (Map.toList xs))) <+> mempty) where
  58. go (f, t) = prettyTm f <+> operator (pretty "=>") <+> prettyTm t
  59. prettyTm x = error (show x)
  60. beautify (PathP l x y) = toFun "PathP" [l, x, y]
  61. beautify (IElim _ _ _ f i) = App Ex f i
  62. beautify (PathIntro _ _ _ f) = f
  63. beautify (IsOne phi) = toFun "IsOne" [phi]
  64. beautify ItIsOne = Ref (Bound (T.pack ".1=1") 0)
  65. beautify (IsOne1 phi) = toFun "isOne1" [phi]
  66. beautify (IsOne2 phi) = toFun "isOne2" [phi]
  67. beautify Bool = Ref (Bound (T.pack ".Bool") 0)
  68. beautify Tt = Ref (Bound (T.pack ".true") 0)
  69. beautify Ff = Ref (Bound (T.pack ".false") 0)
  70. beautify (If a b c d) = toFun "if" [a, b, c, d]
  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@IsOne1{} = parens $ prettyTm x
  92. parenArg x@IsOne2{} = parens $ prettyTm x
  93. parenArg x@Partial{} = parens $ prettyTm x
  94. parenArg x@PartialP{} = parens $ prettyTm x
  95. parenArg x@Sub{} = parens $ prettyTm x
  96. parenArg x@Inc{} = parens $ prettyTm x
  97. parenArg x@Ouc{} = parens $ prettyTm x
  98. parenArg x@Comp{} = parens $ prettyTm x
  99. parenArg x = prettyDom x
  100. prettyDom :: Term -> Doc AnsiStyle
  101. prettyDom x@Pi{} = parens (prettyTm x)
  102. prettyDom x@Sigma{} = parens (prettyTm x)
  103. prettyDom x = parenFun x
  104. parenFun :: Term -> Doc AnsiStyle
  105. parenFun x@Lam{} = parens $ prettyTm x
  106. parenFun x@PathIntro{} = parens $ prettyTm x
  107. parenFun x = prettyTm x
  108. render :: Doc AnsiStyle -> Text
  109. render = L.toStrict . renderLazy . layoutSmart defaultLayoutOptions
  110. showValue :: Value -> String
  111. showValue = L.unpack . renderLazy . layoutSmart defaultLayoutOptions . prettyTm . quote
  112. showFace :: Map Head Bool -> Doc AnsiStyle
  113. showFace = hsep . map go . Map.toList where
  114. go (h, b) = parens $ prettyTm (quote (VNe h mempty)) <+> operator (pretty "=") <+> pretty (if b then "i1" else "i0")
  115. freeVars :: Term -> Set Name
  116. freeVars (Ref v) = Set.singleton v
  117. freeVars (App _ f x) = Set.union (freeVars f) (freeVars x)
  118. freeVars (Pi _ n x y) = Set.union (freeVars x) (n `Set.delete` freeVars y)
  119. freeVars (Lam _ n x) = n `Set.delete` freeVars x
  120. freeVars (Let ns x) = Set.union (freeVars x `Set.difference` bound) freed where
  121. bound = Set.fromList (map (\(x, _, _) -> x) ns)
  122. freed = foldr (\(_, x, y) -> Set.union (Set.union (freeVars x) (freeVars y))) mempty ns
  123. freeVars Meta{} = 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 (IsOne1 a) = Set.unions $ map freeVars [a]
  141. freeVars (IsOne2 a) = Set.unions $ map freeVars [a]
  142. freeVars ItIsOne{} = mempty
  143. freeVars (Partial x y) = Set.unions $ map freeVars [x, y]
  144. freeVars (PartialP x y) = Set.unions $ map freeVars [x, y]
  145. freeVars (System fs) = foldr (\(x, y) -> Set.union (Set.union (freeVars x) (freeVars y))) mempty (Map.toList fs)
  146. freeVars (Sub x y z) = Set.unions $ map freeVars [x, y, z]
  147. freeVars (Inc x y z) = Set.unions $ map freeVars [x, y, z]
  148. freeVars (Ouc x y z a) = Set.unions $ map freeVars [x, y, z, a]
  149. freeVars (Comp x y z a) = Set.unions $ map freeVars [x, y, z, a]
  150. freeVars (GlueTy x y z a) = Set.unions $ map freeVars [x, y, z, a]
  151. freeVars (Glue x y z a b c) = Set.unions $ map freeVars [x, y, z, a, b, c]
  152. freeVars (Unglue x y z a c) = Set.unions $ map freeVars [x, y, z, a, c]
  153. freeVars Bool{} = mempty
  154. freeVars Tt{} = mempty
  155. freeVars Ff{} = mempty
  156. freeVars (If x y z a) = Set.unions $ map freeVars [x, y, z, a]