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

Reworking space v tabs

This commit is contained in:
Timothy Clem 2018-08-28 10:32:32 -07:00
parent 0adb827343
commit a923fb0938
5 changed files with 32 additions and 18 deletions

View File

@ -8,8 +8,8 @@ module Data.Reprinting.Splice
, layout
, layouts
, space
, indent
, Whitespace(..)
, Indentation(..)
) where
import Data.Reprinting.Token
@ -61,16 +61,13 @@ layouts = fromList . fmap Layout
space :: Seq Splice
space = layout Space
-- | Indent n times.
indent :: Integral b => b -> Seq Splice
indent times
| times > 0 = stimes times (layout Indent)
| otherwise = mempty
-- | Indentation, spacing, and other whitespace.
data Whitespace
= HardWrap
| SoftWrap
| Space
| Indent
| Indent Int Indentation
deriving (Eq, Show)
data Indentation = Tabs | Spaces
deriving (Eq, Show)

View File

@ -62,11 +62,11 @@ beautifyingJSON _ = autoT (Kleisli step) ~> flattened where
step (Defer el cs) = throwError (NoTranslation el cs)
step (Verbatim txt) = pure $ emit txt
step (New el cs txt) = pure $ case (el, listToMaybe cs) of
(TOpen, Just THash) -> emit txt <> layouts [HardWrap, Indent]
(TOpen, Just THash) -> emit txt <> layouts [HardWrap, Indent 2 Spaces]
(TClose, Just THash) -> layout HardWrap <> emit txt
(TSep, Just TList) -> emit txt <> space
(TSep, Just TPair) -> emit txt <> space
(TSep, Just THash) -> emit txt <> layouts [HardWrap, Indent]
(TSep, Just THash) -> emit txt <> layouts [HardWrap, Indent 2 Spaces]
_ -> emit txt
-- | Produce whitespace minimal JSON.

View File

@ -4,10 +4,11 @@ import Control.Arrow
import Control.Monad.Effect
import Control.Monad.Effect.Exception (Exc, throwError)
import Data.Machine
import Data.Sequence (Seq)
import Data.Reprinting.Errors
import Data.Reprinting.Splice
import Data.Reprinting.Token as Token
import Data.Semigroup (stimes)
import Data.Sequence (Seq)
-- | Print Python syntax.
printingPython :: (Member (Exc TranslationError) effs) => ProcessT (Eff effs) Fragment Splice
@ -34,7 +35,7 @@ step (Defer el cs) = case (el, cs) of
(TOpen, TIf:_) -> pure $ emit "if" <> space
(TThen, TIf:_) -> pure $ emit ":"
(TElse, TIf:xs) -> pure $ endContext (depth xs) <> emit "else:"
(TClose, TIf:xs) -> pure $ endContext (depth xs)
(TClose, TIf:xs) -> pure mempty
-- Booleans
(Truth True, _) -> pure $ emit "True"
@ -57,7 +58,7 @@ step (Defer el cs) = case (el, cs) of
(TClose, [Imperative]) -> pure $ layout HardWrap -- but end the program with a newline.
(TOpen, Imperative:xs) -> pure $ layout HardWrap <> indent (depth xs)
(TSep, Imperative:xs) -> pure $ layout HardWrap <> indent (depth xs)
(TClose, Imperative:xs) -> pure $ indent (pred (depth xs))
(TClose, Imperative:xs) -> pure mempty -- $ indent (pred (depth xs))
_ -> throwError (NoTranslation el cs)
@ -75,3 +76,9 @@ prec cs = case filter isInfix cs of
-- | Depth of imperative scope.
depth :: [Context] -> Int
depth = length . filter (== Imperative)
-- | Indent n times.
indent :: Integral b => b -> Seq Splice
indent times
| times > 0 = stimes times (layout (Indent 4 Spaces))
| otherwise = mempty

View File

@ -8,6 +8,7 @@ import Data.Sequence (Seq)
import Data.Reprinting.Errors
import Data.Reprinting.Splice
import Data.Reprinting.Token as Token
import Data.Semigroup (stimes)
-- | Print Ruby syntax.
printingRuby :: (Member (Exc TranslationError) effs) => ProcessT (Eff effs) Fragment Splice
@ -61,3 +62,9 @@ prec cs = case filter isInfix cs of
-- | Depth of imperative scope.
depth :: [Context] -> Int
depth = length . filter (== Imperative)
-- | Indent n times.
indent :: Integral b => b -> Seq Splice
indent times
| times > 0 = stimes times (layout (Indent 2 Spaces))
| otherwise = mempty

View File

@ -16,8 +16,11 @@ typesetting :: Monad m => ProcessT m Splice (Doc a)
typesetting = auto step
step :: Splice -> Doc a
step (Emit t) = pretty t
step (Layout SoftWrap) = softline
step (Layout HardWrap) = line
step (Layout Space) = space
step (Layout Indent) = stimes (2 :: Int) space -- TODO: Configuration of tabs v. spaces
step (Emit t) = pretty t
step (Layout SoftWrap) = softline
step (Layout HardWrap) = hardline
step (Layout Space) = space
step (Layout (Indent 0 Spaces)) = mempty
step (Layout (Indent n Spaces)) = stimes n space
step (Layout (Indent 0 Tabs)) = mempty
step (Layout (Indent n Tabs)) = stimes n "\t"