{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.PostgreSQL.Entity.Internal.Unsafe
( Field (..)
)
where
import Data.Kind
import Data.String
import Data.Text (Text)
import GHC.TypeLits
data Field
= Field Text (Maybe Text)
deriving stock (Field -> Field -> Bool
(Field -> Field -> Bool) -> (Field -> Field -> Bool) -> Eq Field
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
/= :: Field -> Field -> Bool
Eq, Int -> Field -> ShowS
[Field] -> ShowS
Field -> String
(Int -> Field -> ShowS)
-> (Field -> String) -> ([Field] -> ShowS) -> Show Field
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Field -> ShowS
showsPrec :: Int -> Field -> ShowS
$cshow :: Field -> String
show :: Field -> String
$cshowList :: [Field] -> ShowS
showList :: [Field] -> ShowS
Show)
instance ForbiddenIsString => IsString Field where
fromString :: String -> Field
fromString = String -> String -> Field
forall a. HasCallStack => String -> a
error String
"You cannot pass a field as a string. Please use the `field` quasi-quoter instead."
type family ForbiddenIsString :: Constraint where
ForbiddenIsString =
TypeError
( 'Text "🚫 You cannot pass a Field name as a string."
':$$: 'Text "Please use the `field` quasi-quoter instead."
)