{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleContexts #-}
module Data.TypedEncoding.Conv.Text where
import qualified Data.Text as T
import qualified Data.TypedEncoding.Common.Util.TypeLits as Knds
import Data.TypedEncoding.Instances.Support
pack :: (
Knds.UnSnoc xs ~ '(,) ys y
, Superset "r-UNICODE.D76" y
, encs ~ RemoveRs ys
, AllEncodeInto "r-UNICODE.D76" encs
) => Enc xs c String -> Enc xs c T.Text
pack = unsafeChangePayload T.pack
unpack :: (
Knds.UnSnoc xs ~ '(,) ys y
, Superset "r-UNICODE.D76" y
, encs ~ RemoveRs ys
, AllEncodeInto "r-UNICODE.D76" encs
) => Enc xs c T.Text -> Enc xs c String
unpack = unsafeChangePayload T.unpack
utf8Promote :: Enc xs c T.Text -> Enc (Snoc xs "r-UTF8") c T.Text
utf8Promote = withUnsafeCoerce id
utf8Demote :: (UnSnoc xs ~ '(,) ys "r-UTF8") => Enc xs c T.Text -> Enc ys c T.Text
utf8Demote = withUnsafeCoerce id
d76Promote :: Enc xs c T.Text -> Enc (Snoc xs "r-UNICODE.D76") c T.Text
d76Promote = withUnsafeCoerce id
d76Demote :: (UnSnoc xs ~ '(,) ys "r-UNICODE.D76") => Enc xs c T.Text -> Enc ys c T.Text
d76Demote = withUnsafeCoerce id