{-# LANGUAGE FlexibleInstances #-}
module Formatting.FromBuilder
( FromBuilder(..)
, formatted
) where
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Builder (Builder)
import qualified Data.Text.Lazy.Builder as TL
import Formatting.Internal (Format (..))
class FromBuilder a where
fromBuilder :: Builder -> a
instance FromBuilder Builder where
fromBuilder :: Builder -> Builder
fromBuilder = Builder -> Builder
forall a. a -> a
id
{-# INLINE fromBuilder #-}
instance FromBuilder TL.Text where
fromBuilder :: Builder -> Text
fromBuilder = Builder -> Text
TL.toLazyText
{-# INLINE fromBuilder #-}
instance FromBuilder T.Text where
fromBuilder :: Builder -> Text
fromBuilder = Text -> Text
TL.toStrict (Text -> Text) -> (Builder -> Text) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TL.toLazyText
{-# INLINE fromBuilder #-}
instance FromBuilder [Char] where
fromBuilder :: Builder -> [Char]
fromBuilder = Text -> [Char]
TL.unpack (Text -> [Char]) -> (Builder -> Text) -> Builder -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TL.toLazyText
{-# INLINE fromBuilder #-}
formatted :: FromBuilder t => (t -> o) -> Format o a -> a
formatted :: forall t o a. FromBuilder t => (t -> o) -> Format o a -> a
formatted t -> o
k Format o a
f = Format o a -> (Builder -> o) -> a
forall r a. Format r a -> (Builder -> r) -> a
runFormat Format o a
f (t -> o
k (t -> o) -> (Builder -> t) -> Builder -> o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> t
forall a. FromBuilder a => Builder -> a
fromBuilder)