{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Text.PrettyBy.Default
( layoutDef
, Render (..)
, display
, displayBy
) where
import Text.Pretty
import Text.PrettyBy.Internal
import Data.Text qualified as Strict
import Data.Text.Lazy qualified as Lazy
import Prettyprinter.Render.String (renderString)
import Prettyprinter.Render.Text (renderLazy, renderStrict)
layoutDef :: Doc ann -> SimpleDocStream ann
layoutDef :: forall ann. Doc ann -> SimpleDocStream ann
layoutDef = LayoutOptions -> Doc ann -> SimpleDocStream ann
forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
layoutSmart LayoutOptions
defaultLayoutOptions
class Render str where
render :: Doc ann -> str
instance a ~ Char => Render [a] where
render :: forall ann. Doc ann -> [a]
render = SimpleDocStream ann -> [a]
SimpleDocStream ann -> String
forall ann. SimpleDocStream ann -> String
renderString (SimpleDocStream ann -> [a])
-> (Doc ann -> SimpleDocStream ann) -> Doc ann -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc ann -> SimpleDocStream ann
forall ann. Doc ann -> SimpleDocStream ann
layoutDef
instance Render Strict.Text where
render :: forall ann. Doc ann -> Text
render = SimpleDocStream ann -> Text
forall ann. SimpleDocStream ann -> Text
renderStrict (SimpleDocStream ann -> Text)
-> (Doc ann -> SimpleDocStream ann) -> Doc ann -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc ann -> SimpleDocStream ann
forall ann. Doc ann -> SimpleDocStream ann
layoutDef
instance Render Lazy.Text where
render :: forall ann. Doc ann -> Text
render = SimpleDocStream ann -> Text
forall ann. SimpleDocStream ann -> Text
renderLazy (SimpleDocStream ann -> Text)
-> (Doc ann -> SimpleDocStream ann) -> Doc ann -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc ann -> SimpleDocStream ann
forall ann. Doc ann -> SimpleDocStream ann
layoutDef
display :: forall str a. (Pretty a, Render str) => a -> str
display :: forall str a. (Pretty a, Render str) => a -> str
display = Doc Any -> str
forall ann. Doc ann -> str
forall str ann. Render str => Doc ann -> str
render (Doc Any -> str) -> (a -> Doc Any) -> a -> str
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Doc Any
forall ann. a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty
displayBy :: forall str a config. (PrettyBy config a, Render str) => config -> a -> str
displayBy :: forall str a config.
(PrettyBy config a, Render str) =>
config -> a -> str
displayBy config
config = Doc Any -> str
forall ann. Doc ann -> str
forall str ann. Render str => Doc ann -> str
render (Doc Any -> str) -> (a -> Doc Any) -> a -> str
forall b c a. (b -> c) -> (a -> b) -> a -> c
. config -> a -> Doc Any
forall ann. config -> a -> Doc ann
forall config a ann. PrettyBy config a => config -> a -> Doc ann
prettyBy config
config