1
1
mirror of https://github.com/github/semantic.git synced 2024-12-24 23:42:31 +03:00
semantic/src/Renderer/SExpression.hs

53 lines
2.3 KiB
Haskell
Raw Normal View History

{-# LANGUAGE GADTs, RankNTypes, ScopedTypeVariables #-}
2017-04-20 21:00:02 +03:00
module Renderer.SExpression
( renderSExpressionDiff
, renderSExpressionTerm
2017-04-20 21:00:02 +03:00
) where
import Data.Bifunctor.Join
2017-07-28 21:37:02 +03:00
import Data.ByteString.Char8 hiding (foldr, spanEnd)
2017-09-09 18:55:32 +03:00
import Data.Functor.Foldable (cata)
2017-03-31 23:12:26 +03:00
import Data.Record
2017-07-28 21:37:02 +03:00
import Data.Semigroup
import Diff
import Patch
2017-07-28 21:37:02 +03:00
import Prelude hiding (replicate)
2017-09-08 18:40:23 +03:00
import Term
-- | Returns a ByteString SExpression formatted diff.
2017-09-09 18:55:32 +03:00
renderSExpressionDiff :: (ConstrainAll Show fields, Foldable f, Functor f) => Diff f (Record fields) -> ByteString
renderSExpressionDiff diff = printDiff diff 0 <> "\n"
-- | Returns a ByteString SExpression formatted term.
2017-09-09 18:55:32 +03:00
renderSExpressionTerm :: (ConstrainAll Show fields, Foldable f, Functor f) => Term f (Record fields) -> ByteString
renderSExpressionTerm term = printTerm term 0 <> "\n"
2017-04-20 21:00:02 +03:00
2017-09-09 18:55:32 +03:00
printDiff :: (ConstrainAll Show fields, Foldable f, Functor f) => Diff f (Record fields) -> Int -> ByteString
printDiff = cata $ \ diff level -> case diff of
2017-09-09 13:23:57 +03:00
Patch patch -> case patch of
Insert term -> pad (level - 1) <> "{+" <> printTerm term level <> "+}"
Delete term -> pad (level - 1) <> "{-" <> printTerm term level <> "-}"
Replace a b -> pad (level - 1) <> "{ " <> printTerm a level <> pad (level - 1) <> "->" <> printTerm b level <> " }"
2017-09-09 18:55:32 +03:00
Copy (Join (_, annotation)) syntax -> pad' level <> "(" <> showAnnotation annotation <> foldr (\d acc -> d (level + 1) <> acc) "" syntax <> ")"
where
pad' :: Int -> ByteString
pad' n = if n < 1 then "" else pad n
pad :: Int -> ByteString
pad n | n < 0 = ""
| n < 1 = "\n"
2017-07-28 21:37:02 +03:00
| otherwise = "\n" <> replicate (2 * n) ' '
2017-09-09 18:58:41 +03:00
printTerm :: (ConstrainAll Show fields, Foldable f, Functor f) => Term f (Record fields) -> Int -> ByteString
printTerm term level = cata go term level 0
where
pad :: Int -> Int -> ByteString
2016-12-10 01:47:00 +03:00
pad p n | n < 1 = ""
2017-07-28 21:37:02 +03:00
| otherwise = "\n" <> replicate (2 * (p + n)) ' '
2017-09-09 18:58:41 +03:00
go (annotation :< syntax) parentLevel level =
pad parentLevel level <> "(" <> showAnnotation annotation <> foldr (\t acc -> t parentLevel (level + 1) <> acc) "" syntax <> ")"
showAnnotation :: ConstrainAll Show fields => Record fields -> ByteString
showAnnotation Nil = ""
2017-07-28 21:37:02 +03:00
showAnnotation (only :. Nil) = pack (show only)
showAnnotation (first :. rest) = pack (show first) <> " " <> showAnnotation rest