{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.PostgreSQL.Entity.Types
(
Entity (..)
, Field
, field
, fieldName
, fieldType
, UpdateRow (..)
, SortKeyword (..)
, Options (..)
, defaultEntityOptions
, GenericEntity (..)
, EntityOptions (..)
, PrimaryKey
, Schema
, TableName
, FieldModifiers
, TextModifier (..)
, StripPrefix
, CamelTo
, CamelToSnake
, CamelToKebab
)
where
import Data.Char
import Data.Kind
import Data.Maybe
import Data.Proxy
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Display (Display, ShowInstance (..))
import qualified Data.Text.Manipulate as T
import Data.Vector (Vector)
import qualified Data.Vector as V
import qualified Data.Vector as Vector
import Database.PostgreSQL.Entity.Internal.QQ (field)
import Database.PostgreSQL.Entity.Internal.Unsafe (Field (Field))
import Database.PostgreSQL.Simple.ToRow (ToRow (..))
import GHC.Generics
import GHC.TypeLits
class Entity e where
tableName :: Text
default tableName :: GetTableName (Rep e) => Text
tableName = forall (e :: * -> *). GetTableName e => Options -> Text
getTableName @(Rep e) Options
defaultEntityOptions
schema :: Maybe Text
schema = Maybe Text
forall a. Maybe a
Nothing
primaryKey :: Field
default primaryKey :: GetFields (Rep e) => Field
primaryKey = Field
newPrimaryKey
where
primMod :: Text -> Text
primMod = Options -> Text -> Text
primaryKeyModifiers Options
defaultEntityOptions
fs :: Vector Field
fs = forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @(Rep e) Options
defaultEntityOptions
newPrimaryKey :: Field
newPrimaryKey =
case (Field -> Bool) -> Vector Field -> Maybe Field
forall a. (a -> Bool) -> Vector a -> Maybe a
Vector.find (\(Field Text
name Maybe Text
_type) -> Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Text
primMod Text
name) Vector Field
fs of
Maybe Field
Nothing -> Text -> Maybe Text -> Field
Field (Text -> Text
primMod Text
"") Maybe Text
forall a. Maybe a
Nothing
Just Field
f -> Field
f
fields :: Vector Field
default fields :: GetFields (Rep e) => Vector Field
fields = forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @(Rep e) Options
defaultEntityOptions
class GetTableName (e :: Type -> Type) where
getTableName :: Options -> Text
instance TypeError ('Text "You can't derive Entity for a void type") => GetTableName V1 where
getTableName :: Options -> Text
getTableName Options
_opts = [Char] -> Text
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a void type"
instance TypeError ('Text "You can't derive Entity for a unit type") => GetTableName U1 where
getTableName :: Options -> Text
getTableName Options
_opts = [Char] -> Text
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a unit type"
instance TypeError ('Text "You can't derive Entity for a sum type") => GetTableName (e :+: f) where
getTableName :: Options -> Text
getTableName Options
_opts = [Char] -> Text
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a sum type"
instance TypeError ('Text "You can't derive an Entity for a type constructor's field") => GetTableName (K1 i c) where
getTableName :: Options -> Text
getTableName Options
_opts = [Char] -> Text
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a type constructor's field"
instance TypeError ('Text "You don't have to derive GetTableName for a product type") => GetTableName (e :*: f) where
getTableName :: Options -> Text
getTableName Options
_opts = [Char] -> Text
forall a. HasCallStack => [Char] -> a
error [Char]
"You don't have to derive GetTableName for a product type"
instance GetTableName e => GetTableName (M1 C _1 e) where
getTableName :: Options -> Text
getTableName Options
opts = forall (e :: * -> *). GetTableName e => Options -> Text
getTableName @e Options
opts
instance GetTableName e => GetTableName (M1 S _1 e) where
getTableName :: Options -> Text
getTableName Options
opts = forall (e :: * -> *). GetTableName e => Options -> Text
getTableName @e Options
opts
instance
KnownSymbol name
=> GetTableName (M1 D ('MetaData name _1 _2 _3) e)
where
getTableName :: Options -> Text
getTableName Options{Text -> Text
tableNameModifiers :: Text -> Text
$sel:tableNameModifiers:Options :: Options -> Text -> Text
tableNameModifiers, Text -> Text
fieldModifiers :: Text -> Text
$sel:fieldModifiers:Options :: Options -> Text -> Text
fieldModifiers} = Text -> Text
tableNameModifiers (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
fieldModifiers (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Proxy name -> [Char]
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal (Proxy name
forall {k} (t :: k). Proxy t
Proxy :: Proxy name)
class GetFields (e :: Type -> Type) where
getField :: Options -> Vector Field
instance TypeError ('Text "You can't derive Entity for a void type") => GetFields V1 where
getField :: Options -> Vector Field
getField Options
_opts = [Char] -> Vector Field
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a void type"
instance TypeError ('Text "You can't derive Entity for a unit type") => GetFields U1 where
getField :: Options -> Vector Field
getField Options
_opts = [Char] -> Vector Field
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a unit type"
instance TypeError ('Text "You can't derive Entity for a sum type") => GetFields (e :+: f) where
getField :: Options -> Vector Field
getField Options
_opts = [Char] -> Vector Field
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a sum type"
instance TypeError ('Text "You can't derive Entity for a a type constructor's field") => GetFields (K1 i c) where
getField :: Options -> Vector Field
getField Options
_opts = [Char] -> Vector Field
forall a. HasCallStack => [Char] -> a
error [Char]
"You can't derive Entity for a type constructor's field"
instance (GetFields e, GetFields f) => GetFields (e :*: f) where
getField :: Options -> Vector Field
getField Options
opts = forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @e Options
opts Vector Field -> Vector Field -> Vector Field
forall a. Semigroup a => a -> a -> a
<> forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @f Options
opts
instance GetFields e => GetFields (M1 C _1 e) where
getField :: Options -> Vector Field
getField Options
opts = forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @e Options
opts
instance GetFields e => GetFields (M1 D ('MetaData _1 _2 _3 _4) e) where
getField :: Options -> Vector Field
getField Options
opts = forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @e Options
opts
instance KnownSymbol name => GetFields (M1 S ('MetaSel ('Just name) _1 _2 _3) _4) where
getField :: Options -> Vector Field
getField Options{Text -> Text
$sel:fieldModifiers:Options :: Options -> Text -> Text
fieldModifiers :: Text -> Text
fieldModifiers} = Field -> Vector Field
forall a. a -> Vector a
V.singleton (Field -> Vector Field) -> Field -> Vector Field
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Field
Field Text
fieldName' Maybe Text
forall a. Maybe a
Nothing
where
fieldName' :: Text
fieldName' = Text -> Text
fieldModifiers (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Proxy name -> [Char]
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @name)
newtype GenericEntity t e = GenericEntity {forall {k} (t :: k) e. GenericEntity t e -> e
getGenericEntity :: e}
instance (EntityOptions t, GetTableName (Rep e), GetFields (Rep e)) => Entity (GenericEntity t e) where
tableName :: Text
tableName = forall (e :: * -> *). GetTableName e => Options -> Text
getTableName @(Rep e) (forall (xs :: k). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @t)
schema :: Maybe Text
schema = Options -> Maybe Text
schemaModifier (forall (xs :: k). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @t)
primaryKey :: Field
primaryKey = Field
newPrimaryKey
where
primMod :: Text -> Text
primMod = Options -> Text -> Text
primaryKeyModifiers (forall (xs :: k). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @t)
fs :: Vector Field
fs = forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @(Rep e) (forall (xs :: k). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @t)
newPrimaryKey :: Field
newPrimaryKey =
case (Field -> Bool) -> Vector Field -> Maybe Field
forall a. (a -> Bool) -> Vector a -> Maybe a
Vector.find (\(Field Text
name Maybe Text
_type) -> Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Text
primMod Text
name) Vector Field
fs of
Maybe Field
Nothing -> Text -> Maybe Text -> Field
Field (Text -> Text
primMod Text
"") Maybe Text
forall a. Maybe a
Nothing
Just Field
f -> Field
f
fields :: Vector Field
fields = forall (e :: * -> *). GetFields e => Options -> Vector Field
getField @(Rep e) (forall (xs :: k). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @t)
data Options = Options
{ Options -> Text -> Text
tableNameModifiers :: Text -> Text
, Options -> Maybe Text
schemaModifier :: Maybe Text
, Options -> Text -> Text
primaryKeyModifiers :: Text -> Text
, Options -> Text -> Text
fieldModifiers :: Text -> Text
}
defaultEntityOptions :: Options
defaultEntityOptions :: Options
defaultEntityOptions =
Options
{ $sel:tableNameModifiers:Options :: Text -> Text
tableNameModifiers = Text -> Text
T.toSnake
, $sel:schemaModifier:Options :: Maybe Text
schemaModifier = Maybe Text
forall a. Maybe a
Nothing
, $sel:primaryKeyModifiers:Options :: Text -> Text
primaryKeyModifiers = Text -> Text
T.toSnake
, $sel:fieldModifiers:Options :: Text -> Text
fieldModifiers = Text -> Text
T.toSnake
}
class EntityOptions xs where
entityOptions :: Options
instance EntityOptions '[] where
entityOptions :: Options
entityOptions = Options
defaultEntityOptions
instance (GetName name, EntityOptions xs) => EntityOptions (TableName name ': xs) where
entityOptions :: Options
entityOptions = (forall (xs :: [*]). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @xs){$sel:tableNameModifiers:Options :: Text -> Text
tableNameModifiers = Text -> Text -> Text
forall a b. a -> b -> a
const (forall {k} (name :: k). GetName name => Text
forall (name :: Symbol). GetName name => Text
getName @name)}
instance (GetName name, EntityOptions xs) => EntityOptions (PrimaryKey name ': xs) where
entityOptions :: Options
entityOptions = (forall (xs :: [*]). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @xs){$sel:primaryKeyModifiers:Options :: Text -> Text
primaryKeyModifiers = Text -> Text -> Text
forall a b. a -> b -> a
const (forall {k} (name :: k). GetName name => Text
forall (name :: Symbol). GetName name => Text
getName @name)}
instance (TextModifier mods, EntityOptions xs) => EntityOptions (FieldModifiers mods ': xs) where
entityOptions :: Options
entityOptions = (forall (xs :: [*]). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @xs){$sel:fieldModifiers:Options :: Text -> Text
fieldModifiers = forall (t :: k). TextModifier t => Text -> Text
forall {k} (t :: k). TextModifier t => Text -> Text
getTextModifier @mods}
instance (GetName name, EntityOptions xs) => EntityOptions (Schema name ': xs) where
entityOptions :: Options
entityOptions = (forall (xs :: [*]). EntityOptions xs => Options
forall {k} (xs :: k). EntityOptions xs => Options
entityOptions @xs){$sel:schemaModifier:Options :: Maybe Text
schemaModifier = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ forall {k} (name :: k). GetName name => Text
forall (name :: Symbol). GetName name => Text
getName @name}
data TableName (t :: Symbol)
data PrimaryKey (t :: Symbol)
data Schema (t :: Symbol)
data FieldModifiers ms
data StripPrefix (prefix :: Symbol)
data CamelTo (separator :: Symbol)
type CamelToSnake = CamelTo "_"
type CamelToKebab = CamelTo "-"
class TextModifier t where
getTextModifier :: Text -> Text
instance TextModifier '[] where
getTextModifier :: Text -> Text
getTextModifier = Text -> Text
forall a. a -> a
id
instance (TextModifier x, TextModifier xs) => TextModifier (x ': xs) where
getTextModifier :: Text -> Text
getTextModifier = forall (t :: [a]). TextModifier t => Text -> Text
forall {k} (t :: k). TextModifier t => Text -> Text
getTextModifier @xs (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: a). TextModifier t => Text -> Text
forall {k} (t :: k). TextModifier t => Text -> Text
getTextModifier @x
instance KnownSymbol prefix => TextModifier (StripPrefix prefix) where
getTextModifier :: Text -> Text
getTextModifier Text
fld = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
fld (Text -> Text -> Maybe Text
T.stripPrefix Text
prefixToStrip Text
fld)
where
prefixToStrip :: Text
prefixToStrip = [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Proxy prefix -> [Char]
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @prefix)
instance (KnownSymbol separator, NonEmptyText separator) => TextModifier (CamelTo separator) where
getTextModifier :: Text -> Text
getTextModifier Text
fld = [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Char -> [Char] -> [Char]
camelTo2 Char
char (Text -> [Char]
T.unpack Text
fld)
where
char :: Char
char :: Char
char = [Char] -> Char
forall a. HasCallStack => [a] -> a
head ([Char] -> Char) -> [Char] -> Char
forall a b. (a -> b) -> a -> b
$ Proxy separator -> [Char]
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @separator)
camelTo2 :: Char -> String -> String
camelTo2 :: Char -> [Char] -> [Char]
camelTo2 Char
c [Char]
text = (Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
go2 ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
go1 [Char]
text
where
go1 :: [Char] -> [Char]
go1 [Char]
"" = [Char]
""
go1 (Char
x : Char
u : Char
l : [Char]
xs) | Char -> Bool
isUpper Char
u Bool -> Bool -> Bool
&& Char -> Bool
isLower Char
l = Char
x Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
c Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
u Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
l Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
go1 [Char]
xs
go1 (Char
x : [Char]
xs) = Char
x Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
go1 [Char]
xs
go2 :: [Char] -> [Char]
go2 [Char]
"" = [Char]
""
go2 (Char
l : Char
u : [Char]
xs) | Char -> Bool
isLower Char
l Bool -> Bool -> Bool
&& Char -> Bool
isUpper Char
u = Char
l Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
c Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
u Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
go2 [Char]
xs
go2 (Char
x : [Char]
xs) = Char
x Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
go2 [Char]
xs
class GetName name where
getName :: Text
instance (KnownSymbol name, NonEmptyText name) => GetName name where
getName :: Text
getName = [Char] -> Text
T.pack (Proxy name -> [Char]
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @name))
type family NonEmptyText (xs :: Symbol) :: Constraint where
NonEmptyText "" = TypeError ('Text "User-provided string cannot be empty!")
NonEmptyText _ = ()
fieldName :: Field -> Text
fieldName :: Field -> Text
fieldName (Field Text
name Maybe Text
_) = Text
name
fieldType :: Field -> Maybe Text
fieldType :: Field -> Maybe Text
fieldType (Field Text
_ Maybe Text
typ) = Maybe Text
typ
newtype UpdateRow a = UpdateRow {forall a. UpdateRow a -> a
getUpdate :: a}
deriving stock (UpdateRow a -> UpdateRow a -> Bool
(UpdateRow a -> UpdateRow a -> Bool)
-> (UpdateRow a -> UpdateRow a -> Bool) -> Eq (UpdateRow a)
forall a. Eq a => UpdateRow a -> UpdateRow a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => UpdateRow a -> UpdateRow a -> Bool
== :: UpdateRow a -> UpdateRow a -> Bool
$c/= :: forall a. Eq a => UpdateRow a -> UpdateRow a -> Bool
/= :: UpdateRow a -> UpdateRow a -> Bool
Eq, Int -> UpdateRow a -> [Char] -> [Char]
[UpdateRow a] -> [Char] -> [Char]
UpdateRow a -> [Char]
(Int -> UpdateRow a -> [Char] -> [Char])
-> (UpdateRow a -> [Char])
-> ([UpdateRow a] -> [Char] -> [Char])
-> Show (UpdateRow a)
forall a. Show a => Int -> UpdateRow a -> [Char] -> [Char]
forall a. Show a => [UpdateRow a] -> [Char] -> [Char]
forall a. Show a => UpdateRow a -> [Char]
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: forall a. Show a => Int -> UpdateRow a -> [Char] -> [Char]
showsPrec :: Int -> UpdateRow a -> [Char] -> [Char]
$cshow :: forall a. Show a => UpdateRow a -> [Char]
show :: UpdateRow a -> [Char]
$cshowList :: forall a. Show a => [UpdateRow a] -> [Char] -> [Char]
showList :: [UpdateRow a] -> [Char] -> [Char]
Show)
deriving newtype (Maybe Text
Text
Vector Field
Field
Text -> Maybe Text -> Field -> Vector Field -> Entity (UpdateRow a)
forall e. Text -> Maybe Text -> Field -> Vector Field -> Entity e
forall a. Entity a => Maybe Text
forall a. Entity a => Text
forall a. Entity a => Vector Field
forall a. Entity a => Field
$ctableName :: forall a. Entity a => Text
tableName :: Text
$cschema :: forall a. Entity a => Maybe Text
schema :: Maybe Text
$cprimaryKey :: forall a. Entity a => Field
primaryKey :: Field
$cfields :: forall a. Entity a => Vector Field
fields :: Vector Field
Entity)
instance ToRow a => ToRow (UpdateRow a) where
toRow :: UpdateRow a -> [Action]
toRow = (Int -> [Action] -> [Action]
forall a. Int -> [a] -> [a]
drop (Int -> [Action] -> [Action])
-> (Int -> [Action] -> [Action]) -> Int -> [Action] -> [Action]
forall a. Semigroup a => a -> a -> a
<> Int -> [Action] -> [Action]
forall a. Int -> [a] -> [a]
take) Int
1 ([Action] -> [Action])
-> (UpdateRow a -> [Action]) -> UpdateRow a -> [Action]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Action]
forall a. ToRow a => a -> [Action]
toRow (a -> [Action]) -> (UpdateRow a -> a) -> UpdateRow a -> [Action]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UpdateRow a -> a
forall a. UpdateRow a -> a
getUpdate
data SortKeyword = ASC | DESC
deriving stock (SortKeyword -> SortKeyword -> Bool
(SortKeyword -> SortKeyword -> Bool)
-> (SortKeyword -> SortKeyword -> Bool) -> Eq SortKeyword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SortKeyword -> SortKeyword -> Bool
== :: SortKeyword -> SortKeyword -> Bool
$c/= :: SortKeyword -> SortKeyword -> Bool
/= :: SortKeyword -> SortKeyword -> Bool
Eq, Int -> SortKeyword -> [Char] -> [Char]
[SortKeyword] -> [Char] -> [Char]
SortKeyword -> [Char]
(Int -> SortKeyword -> [Char] -> [Char])
-> (SortKeyword -> [Char])
-> ([SortKeyword] -> [Char] -> [Char])
-> Show SortKeyword
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> SortKeyword -> [Char] -> [Char]
showsPrec :: Int -> SortKeyword -> [Char] -> [Char]
$cshow :: SortKeyword -> [Char]
show :: SortKeyword -> [Char]
$cshowList :: [SortKeyword] -> [Char] -> [Char]
showList :: [SortKeyword] -> [Char] -> [Char]
Show)
deriving
(Int -> SortKeyword -> Builder
[SortKeyword] -> Builder
SortKeyword -> Builder
(SortKeyword -> Builder)
-> ([SortKeyword] -> Builder)
-> (Int -> SortKeyword -> Builder)
-> Display SortKeyword
forall a.
(a -> Builder)
-> ([a] -> Builder) -> (Int -> a -> Builder) -> Display a
$cdisplayBuilder :: SortKeyword -> Builder
displayBuilder :: SortKeyword -> Builder
$cdisplayList :: [SortKeyword] -> Builder
displayList :: [SortKeyword] -> Builder
$cdisplayPrec :: Int -> SortKeyword -> Builder
displayPrec :: Int -> SortKeyword -> Builder
Display)
via ShowInstance SortKeyword