{-# LANGUAGE
DataKinds
, OverloadedStrings
, TypeOperators
#-}
module Squeal.PostgreSQL.UUID.OSSP
(
createUuidOssp
, uuidGenerateV1
, uuidGenerateV1mc
, uuidGenerateV3
, uuidGenerateV4
, uuidGenerateV5
, uuidNil
, uuidNSUrl
, uuidNSDns
, uuidNSOid
, uuidNSX500
) where
import Squeal.PostgreSQL
createUuidOssp :: Definition db db
createUuidOssp :: Definition db db
createUuidOssp = ByteString -> Definition db db
forall (db0 :: SchemasType) (db1 :: SchemasType).
ByteString -> Definition db0 db1
UnsafeDefinition ByteString
"CREATE EXTENSION \"uuid-ossp\";"
uuidGenerateV1 :: Expr (null 'PGuuid)
uuidGenerateV1 :: Expression grp lat with db params from (null 'PGuuid)
uuidGenerateV1 = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_generate_v1()"
uuidGenerateV1mc :: Expr (null 'PGuuid)
uuidGenerateV1mc :: Expression grp lat with db params from (null 'PGuuid)
uuidGenerateV1mc = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_generate_v1mc()"
uuidGenerateV3 :: '[null 'PGuuid, null 'PGtext] ---> null 'PGuuid
uuidGenerateV3 :: NP
(Expression grp lat with db params from)
'[null 'PGuuid, null 'PGtext]
-> Expression grp lat with db params from (null 'PGuuid)
uuidGenerateV3 = ByteString -> '[null 'PGuuid, null 'PGtext] ---> null 'PGuuid
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"uuid_generate_v3"
uuidGenerateV4 :: Expr (null 'PGuuid)
uuidGenerateV4 :: Expression grp lat with db params from (null 'PGuuid)
uuidGenerateV4 = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_generate_v4()"
uuidGenerateV5 :: '[null 'PGuuid, null 'PGtext] ---> null 'PGuuid
uuidGenerateV5 :: NP
(Expression grp lat with db params from)
'[null 'PGuuid, null 'PGtext]
-> Expression grp lat with db params from (null 'PGuuid)
uuidGenerateV5 = ByteString -> '[null 'PGuuid, null 'PGtext] ---> null 'PGuuid
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"uuid_generate_v5"
uuidNil :: Expr (null 'PGuuid)
uuidNil :: Expression grp lat with db params from (null 'PGuuid)
uuidNil = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_nil()"
uuidNSDns :: Expr (null 'PGuuid)
uuidNSDns :: Expression grp lat with db params from (null 'PGuuid)
uuidNSDns = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_ns_dns()"
uuidNSUrl :: Expr (null 'PGuuid)
uuidNSUrl :: Expression grp lat with db params from (null 'PGuuid)
uuidNSUrl = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_ns_url()"
uuidNSOid :: Expr (null 'PGuuid)
uuidNSOid :: Expression grp lat with db params from (null 'PGuuid)
uuidNSOid = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_ns_oid()"
uuidNSX500 :: Expr (null 'PGuuid)
uuidNSX500 :: Expression grp lat with db params from (null 'PGuuid)
uuidNSX500 = ByteString -> Expression grp lat with db params from (null 'PGuuid)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"uuid_ns_x500()"