module Hix.Pretty where import Distribution.Pretty (Pretty, pretty) import Text.PrettyPrint (Doc, comma, punctuate, sep, text) showP :: ∀ b a . Pretty a => IsString b => a -> b showP :: forall b a. (Pretty a, IsString b) => a -> b showP = Doc -> b forall b a. (Show a, IsString b) => a -> b show (Doc -> b) -> (a -> Doc) -> a -> b forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Doc forall a. Pretty a => a -> Doc pretty showPM :: ∀ b a . Pretty a => IsString b => Maybe a -> b showPM :: forall b a. (Pretty a, IsString b) => Maybe a -> b showPM = Maybe Doc -> b forall b a. (Show a, IsString b) => a -> b show (Maybe Doc -> b) -> (Maybe a -> Maybe Doc) -> Maybe a -> b forall b c a. (b -> c) -> (a -> b) -> a -> c . (a -> Doc) -> Maybe a -> Maybe Doc forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap a -> Doc forall a. Pretty a => a -> Doc pretty prettyL :: ∀ t a . Pretty a => Foldable t => t a -> Doc prettyL :: forall (t :: * -> *) a. (Pretty a, Foldable t) => t a -> Doc prettyL = [Doc] -> Doc sep ([Doc] -> Doc) -> (t a -> [Doc]) -> t a -> Doc forall b c a. (b -> c) -> (a -> b) -> a -> c . Doc -> [Doc] -> [Doc] punctuate Doc comma ([Doc] -> [Doc]) -> (t a -> [Doc]) -> t a -> [Doc] forall b c a. (b -> c) -> (a -> b) -> a -> c . (a -> Doc) -> [a] -> [Doc] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap a -> Doc forall a. Pretty a => a -> Doc pretty ([a] -> [Doc]) -> (t a -> [a]) -> t a -> [Doc] forall b c a. (b -> c) -> (a -> b) -> a -> c . t a -> [a] forall a. t a -> [a] forall (t :: * -> *) a. Foldable t => t a -> [a] toList showPL :: ∀ t b a . Pretty a => Foldable t => IsString b => t a -> b showPL :: forall (t :: * -> *) b a. (Pretty a, Foldable t, IsString b) => t a -> b showPL = Doc -> b forall b a. (Show a, IsString b) => a -> b show (Doc -> b) -> (t a -> Doc) -> t a -> b forall b c a. (b -> c) -> (a -> b) -> a -> c . t a -> Doc forall (t :: * -> *) a. (Pretty a, Foldable t) => t a -> Doc prettyL prettyText :: Text -> Doc prettyText :: Text -> Doc prettyText = String -> Doc text (String -> Doc) -> (Text -> String) -> Text -> Doc forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> String forall a. ToString a => a -> String toString