{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE TypeFamilies   #-}

-- | Default rendering to string types.

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)

-- | A default layout for default rendering.
layoutDef :: Doc ann -> SimpleDocStream ann
layoutDef :: Doc ann -> SimpleDocStream ann
layoutDef = LayoutOptions -> Doc ann -> SimpleDocStream ann
forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
layoutSmart LayoutOptions
defaultLayoutOptions

-- | A class for rendering 'Doc's as string types.
class Render str where
    -- | Render a 'Doc' as a string type.
    render :: Doc ann -> str

instance a ~ Char => Render [a] where
    render :: Doc ann -> [a]
render = SimpleDocStream ann -> String
forall ann. SimpleDocStream ann -> String
renderString (SimpleDocStream ann -> String)
-> (Doc ann -> SimpleDocStream ann) -> Doc ann -> String
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 :: 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 :: 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

-- | Pretty-print and render a value as a string type.
display :: forall str a. (Pretty a, Render str) => a -> str
display :: a -> str
display = Doc Any -> 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 a ann. Pretty a => a -> Doc ann
pretty

-- | Pretty-print and render a value as a string type in a configurable way.
displayBy :: forall str a config. (PrettyBy config a, Render str) => config -> a -> str
displayBy :: config -> a -> str
displayBy config
config = Doc Any -> 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 config a ann. PrettyBy config a => config -> a -> Doc ann
prettyBy config
config