module Typist.TextShow where
import TextShow
import GHC.OverloadedLabels
import GHC.TypeLits
import Typist
import qualified Data.Text as Text
import qualified Data.Text.Lazy as Text.Lazy
import qualified Data.Text.Lazy.Builder as Builder
data Name (s :: Symbol) = Name
instance IsLabel s (Name s) where
fromLabel :: Name s
fromLabel = Name s
forall (s :: Symbol). Name s
Name
{-# INLINE (#=) #-}
(#=) :: (TextShow a) => Name s -> a -> (Rec as -> Rec (Arg n s ': as))
#= :: forall a (s :: Symbol) (as :: [*]) (n :: Nat).
TextShow a =>
Name s -> a -> Rec as -> Rec (Arg n s : as)
(#=) Name s
Name a
a = (Builder -> Arg n s
forall (n :: Nat) (s :: Symbol). Builder -> Arg n s
Arg (a -> Builder
forall a. TextShow a => a -> Builder
showb a
a) Arg n s -> Rec as -> Rec (Arg n s : as)
forall (n :: Nat) (s :: Symbol) (ns :: [*]).
Arg n s -> Rec ns -> Rec (Arg n s : ns)
:&)
newtype Unquoted a = Unquoted a
instance TextShow (Unquoted String) where
showb :: Unquoted String -> Builder
showb (Unquoted String
s) = String -> Builder
fromString String
s
instance TextShow (Unquoted Text.Text) where
showb :: Unquoted Text -> Builder
showb (Unquoted Text
s) = Text -> Builder
Builder.fromText Text
s
instance TextShow (Unquoted Text.Lazy.Text) where
showb :: Unquoted Text -> Builder
showb (Unquoted Text
s) = Text -> Builder
Builder.fromLazyText Text
s
instance TextShow (Unquoted Builder.Builder) where
showb :: Unquoted Builder -> Builder
showb (Unquoted Builder
s) = Builder
s