{-# LANGUAGE CPP #-} module Test.Sandwich.Formatters.Print.Util where import Control.Monad.Reader import qualified Data.List as L import Test.Sandwich.Formatters.Print.Types import Text.Show.Pretty as P isSingleLine :: P.Value -> Bool isSingleLine :: Value -> Bool isSingleLine (Con {}) = Bool False isSingleLine (InfixCons Value op [(Name, Value)] tuples) = Value -> Bool isSingleLine Value op Bool -> Bool -> Bool && ((Value -> Bool) -> [Value] -> Bool forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool all Value -> Bool isSingleLine (((Name, Value) -> Value) -> [(Name, Value)] -> [Value] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Name, Value) -> Value forall a b. (a, b) -> b snd [(Name, Value)] tuples)) isSingleLine (Rec {}) = Bool False isSingleLine (Tuple [Value] values) = (Value -> Bool) -> [Value] -> Bool forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool all Value -> Bool isSingleLine [Value] values isSingleLine (List [Value] values) = (Value -> Bool) -> [Value] -> Bool forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool all Value -> Bool isSingleLine [Value] values isSingleLine (Neg Value value) = Value -> Bool isSingleLine Value value isSingleLine (Ratio Value v1 Value v2) = (Value -> Bool) -> [Value] -> Bool forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool all Value -> Bool isSingleLine [Value v1, Value v2] isSingleLine (String Name s) = Char '\n' Char -> Name -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `L.notElem` Name s #if MIN_VERSION_pretty_show(1,10,0) isSingleLine (Quote Name s) = Char '\n' Char -> Name -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `L.notElem` Name s #endif isSingleLine Value _ = Bool True withBumpIndent :: MonadReader (PrintFormatter, Int, c) m => m b -> m b withBumpIndent :: forall c (m :: * -> *) b. MonadReader (PrintFormatter, Int, c) m => m b -> m b withBumpIndent m b action = do (PrintFormatter {Bool Int Maybe LogLevel IncludeTimestamps printFormatterUseColor :: Bool printFormatterLogLevel :: Maybe LogLevel printFormatterVisibilityThreshold :: Int printFormatterIncludeCallStacks :: Bool printFormatterIndentSize :: Int printFormatterIncludeTimestamps :: IncludeTimestamps printFormatterUseColor :: PrintFormatter -> Bool printFormatterLogLevel :: PrintFormatter -> Maybe LogLevel printFormatterVisibilityThreshold :: PrintFormatter -> Int printFormatterIncludeCallStacks :: PrintFormatter -> Bool printFormatterIndentSize :: PrintFormatter -> Int printFormatterIncludeTimestamps :: PrintFormatter -> IncludeTimestamps ..}, Int _, c _) <- m (PrintFormatter, Int, c) forall r (m :: * -> *). MonadReader r m => m r ask Int -> m b -> m b forall a c (m :: * -> *) b. MonadReader (a, Int, c) m => Int -> m b -> m b withBumpIndent' Int printFormatterIndentSize m b action withBumpIndent' :: (MonadReader (a, Int, c) m) => Int -> m b -> m b withBumpIndent' :: forall a c (m :: * -> *) b. MonadReader (a, Int, c) m => Int -> m b -> m b withBumpIndent' Int n = ((a, Int, c) -> (a, Int, c)) -> m b -> m b forall a. ((a, Int, c) -> (a, Int, c)) -> m a -> m a forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a local (\(a pf, Int indent, c h) -> (a pf, Int indent Int -> Int -> Int forall a. Num a => a -> a -> a + Int n, c h)) fst3 :: (a, b, c) -> a fst3 :: forall a b c. (a, b, c) -> a fst3 (a x, b _, c _) = a x