{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
module Fmt.Internal.Template where
import Data.CallStack
import Data.String (IsString(..))
import Data.Text (Text, splitOn)
import Data.Text.Lazy.Builder hiding (fromString)
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Formatting.Buildable (Buildable(..))
import Fmt.Internal.Core (FromBuilder(..))
format :: (HasCallStack, FormatType r) => Format -> r
format f = format' f []
{-# INLINE format #-}
formatLn :: (HasCallStack, FormatType r) => Format -> r
formatLn f = format' (f <> "\n") []
{-# INLINE formatLn #-}
newtype Format = Format { fromFormat :: Text }
deriving (Eq, Ord, Show)
instance Semigroup Format where
Format a <> Format b = Format (a <> b)
instance Monoid Format where
mempty = Format mempty
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
#endif
instance IsString Format where
fromString = Format . fromString
renderFormat :: Format -> [Builder] -> Builder
renderFormat fmt ps = zipParams (crack fmt) ps
{-# INLINE renderFormat #-}
zipParams :: [Builder] -> [Builder] -> Builder
zipParams fragments params = go fragments params
where go (f:fs) (y:ys) = f <> y <> go fs ys
go [f] [] = f
go _ _ = error $ "Fmt.format: there were " <> show (length fragments - 1) <>
" sites, but " <> show (length params) <> " parameters"
crack :: Format -> [Builder]
crack = map fromText . splitOn "{}" . fromFormat
class FormatType r where
format' :: Format -> [Builder] -> r
instance (Buildable a, FormatType r) => FormatType (a -> r) where
format' f xs = \x -> format' f (build x : xs)
instance {-# OVERLAPPABLE #-} FromBuilder r => FormatType r where
format' f xs = fromBuilder $ renderFormat f (reverse xs)