napkin-0.5.14
Copyright(c) Soostone Inc 2020
LicenseAllRightsReserved
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageGHC2021

Napkin.Types.Redshift

Description

 

Documentation

data Redshift #

Constructors

Redshift 

Instances

Instances details
Data Redshift # 
Instance details

Defined in Napkin.Types.Redshift

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Redshift -> c Redshift #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Redshift #

toConstr :: Redshift -> Constr #

dataTypeOf :: Redshift -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Redshift) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Redshift) #

gmapT :: (forall b. Data b => b -> b) -> Redshift -> Redshift #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Redshift -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Redshift -> r #

gmapQ :: (forall d. Data d => d -> u) -> Redshift -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Redshift -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Redshift -> m Redshift #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Redshift -> m Redshift #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Redshift -> m Redshift #

Show Redshift # 
Instance details

Defined in Napkin.Types.Redshift

Eq Redshift # 
Instance details

Defined in Napkin.Types.Redshift

Ord Redshift # 
Instance details

Defined in Napkin.Types.Redshift

Backend Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Associated Types

data BackendConn Redshift #

RunBackendEffect Redshift # 
Instance details

Defined in Napkin.Run.Effects.Interpreters.Backend.Redshift

HasPostgresConn Redshift # 
Instance details

Defined in Napkin.Run.Redshift

ReifiesBackend Redshift # 
Instance details

Defined in Napkin.Types.Redshift

RunBackendConn Redshift # 
Instance details

Defined in Napkin.Run.Redshift

ToDbBackend Redshift # 
Instance details

Defined in Napkin.Backends.Types

RenderSql AnnotateTableOrView Redshift # 
Instance details

Defined in Napkin.Render.Redshift

RenderSql ArrayStructExp Redshift # 
Instance details

Defined in Napkin.Render.Redshift

RenderSql DeleteFrom Redshift # 
Instance details

Defined in Napkin.Render.Redshift

RenderSql DropTable Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> DropTable -> Doc #

RenderSql DropView Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> DropView -> Doc #

RenderSql InsertIntoQuery Redshift # 
Instance details

Defined in Napkin.Render.Redshift

RenderSql RenameTable Redshift # 
Instance details

Defined in Napkin.Render.Redshift

RenderSql Actor Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Actor -> Doc #

RenderSql Grant Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Grant -> Doc #

RenderSql Object Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Object -> Doc #

RenderSql Privilege Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Privilege -> Doc #

RenderSql ExternFun Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> ExternFun -> Doc #

RenderSql From Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> From -> Doc #

RenderSql Name Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Name -> Doc #

RenderSql Query Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Query -> Doc #

RenderSql Relation Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Relation -> Doc #

RenderSql SExp Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> SExp -> Doc #

RenderSql SetTableSchema Redshift # 
Instance details

Defined in Napkin.Render.Redshift

RenderSql DistStyle Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> DistStyle -> Doc #

RenderSql SortKey Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> SortKey -> Doc #

RenderSql SortStyle Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> SortStyle -> Doc #

RenderSql String Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> String -> Doc #

HasBackendSchemaField Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Associated Types

data BackendSchemaField Redshift #

CSVImport Redshift # 
Instance details

Defined in Napkin.Run.Redshift

HasBackendQueryStats Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Associated Types

data BackendQueryStats Redshift #

SqlConcat Redshift # 
Instance details

Defined in Napkin.Untyped.Ops.Portable.Redshift

Methods

concat :: [SExp] -> SExp #

Command AEDA TableDiagnostics Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command AnnotateCommand () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command CheckTableExists Bool Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command CopyTable () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command DeleteFrom () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command DropTable () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command DropView () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command GetTableKind TableKind Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command InsertIntoQuery () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command ReadAnnotationCommand TableAnnotations Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command RenameTable () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command Grant () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command UpdateQuery () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command GetRelationSchema [BackendSchemaField Redshift] Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command ListTables (Set ListedTable) Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command NormalizeTableNames (Map (Ref Table) NormalizedTable) Redshift # 
Instance details

Defined in Napkin.Run.Redshift

FromJSON (YamlBackendMaterializedViewMeta Redshift) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

FromJSON (YamlBackendTableMeta Redshift) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

FromJSON (YamlBackendViewMeta Redshift) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

FromJSON (DbBackendOptions Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Generic (DbBackendOptions Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Associated Types

type Rep (DbBackendOptions Redshift) :: Type -> Type #

Show (DbBackendOptions Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Default (DbBackendOptions Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Eq (DbBackendOptions Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

MaybeDefault (YamlBackendMaterializedViewMeta Redshift) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

MaybeDefault (YamlBackendTableMeta Redshift) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

MaybeDefault (YamlBackendViewMeta Redshift) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

RenderSql (CreateMaterializedView ()) Redshift # 
Instance details

Defined in Napkin.Render.Redshift

RenderSql (CreateTable TableMeta) Redshift #

Commands

Instance details

Defined in Napkin.Render.Redshift

RenderSql (CreateTable ()) Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> CreateTable () -> Doc #

RenderSql (CreateView ()) Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> CreateView () -> Doc #

RenderSql a Redshift => RenderSql (Alias a) Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Alias a -> Doc #

Command (CreateMaterializedView ()) () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command (CreateTable TableMeta) () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command (CreateTable ()) () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command (CreateView ()) () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

FromJSON (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

ToJSON (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Monoid (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Semigroup (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Generic (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Associated Types

type Rep (BackendQueryStats Redshift) :: Type -> Type #

Show (BackendSchemaField Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Show (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Eq (BackendSchemaField Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

Eq (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

RenderSql (Ref t) Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Ref t -> Doc #

data BackendConn Redshift # 
Instance details

Defined in Napkin.Run.Redshift

data BackendSpecificEffect Redshift m a # 
Instance details

Defined in Napkin.Run.Effects.Languages.Backend.Redshift

newtype DbBackendOptions Redshift # 
Instance details

Defined in Napkin.Run.Redshift

type BackendMaterializedViewMeta Redshift # 
Instance details

Defined in Napkin.Types.Redshift

type BackendTableMeta Redshift # 
Instance details

Defined in Napkin.Types.Redshift

type BackendViewMeta Redshift # 
Instance details

Defined in Napkin.Types.Redshift

data BackendSchemaField Redshift # 
Instance details

Defined in Napkin.Run.Redshift

data BackendQueryStats Redshift # 
Instance details

Defined in Napkin.Run.Redshift

type Rep (DbBackendOptions Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

type Rep (DbBackendOptions Redshift) = D1 ('MetaData "DbBackendOptions" "Napkin.Run.Redshift" "napkin-0.5.14-JrXUGmKUOt9J0meJSj0Kh4" 'True) (C1 ('MetaCons "RedshiftOptions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))
type Rep (BackendQueryStats Redshift) # 
Instance details

Defined in Napkin.Run.Redshift

type Rep (BackendQueryStats Redshift) = D1 ('MetaData "BackendQueryStats" "Napkin.Run.Redshift" "napkin-0.5.14-JrXUGmKUOt9J0meJSj0Kh4" 'False) (C1 ('MetaCons "BackendQueryStats" 'PrefixI 'False) (U1 :: Type -> Type))

data TableMeta #

Instances

Instances details
Data TableMeta # 
Instance details

Defined in Napkin.Types.Redshift

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableMeta -> c TableMeta #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableMeta #

toConstr :: TableMeta -> Constr #

dataTypeOf :: TableMeta -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableMeta) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableMeta) #

gmapT :: (forall b. Data b => b -> b) -> TableMeta -> TableMeta #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableMeta -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableMeta -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableMeta -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableMeta -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableMeta -> m TableMeta #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableMeta -> m TableMeta #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableMeta -> m TableMeta #

Generic TableMeta # 
Instance details

Defined in Napkin.Types.Redshift

Associated Types

type Rep TableMeta :: Type -> Type #

Show TableMeta # 
Instance details

Defined in Napkin.Types.Redshift

Default TableMeta # 
Instance details

Defined in Napkin.Types.Redshift

Methods

def :: TableMeta #

Eq TableMeta # 
Instance details

Defined in Napkin.Types.Redshift

RenderSql (CreateTable TableMeta) Redshift #

Commands

Instance details

Defined in Napkin.Render.Redshift

Command (CreateTable TableMeta) () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

type Rep TableMeta # 
Instance details

Defined in Napkin.Types.Redshift

type Rep TableMeta = D1 ('MetaData "TableMeta" "Napkin.Types.Redshift" "napkin-0.5.14-JrXUGmKUOt9J0meJSj0Kh4" 'False) (C1 ('MetaCons "TableMeta" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_tmLocal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_tmTemp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_tmDistStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DistStyle) :*: S1 ('MetaSel ('Just "_tmSorting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SortKey)))))

data DistStyle #

Constructors

DistEven 
DistKey SExp 
DistAll 

Instances

Instances details
FromJSON DistStyle # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

Data DistStyle # 
Instance details

Defined in Napkin.Types.Redshift

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DistStyle -> c DistStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DistStyle #

toConstr :: DistStyle -> Constr #

dataTypeOf :: DistStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DistStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DistStyle) #

gmapT :: (forall b. Data b => b -> b) -> DistStyle -> DistStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DistStyle -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DistStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> DistStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DistStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DistStyle -> m DistStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DistStyle -> m DistStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DistStyle -> m DistStyle #

Generic DistStyle # 
Instance details

Defined in Napkin.Types.Redshift

Associated Types

type Rep DistStyle :: Type -> Type #

Show DistStyle # 
Instance details

Defined in Napkin.Types.Redshift

Default DistStyle # 
Instance details

Defined in Napkin.Types.Redshift

Methods

def :: DistStyle #

Eq DistStyle # 
Instance details

Defined in Napkin.Types.Redshift

RenderSql DistStyle Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> DistStyle -> Doc #

type Rep DistStyle # 
Instance details

Defined in Napkin.Types.Redshift

type Rep DistStyle = D1 ('MetaData "DistStyle" "Napkin.Types.Redshift" "napkin-0.5.14-JrXUGmKUOt9J0meJSj0Kh4" 'False) (C1 ('MetaCons "DistEven" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DistKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp)) :+: C1 ('MetaCons "DistAll" 'PrefixI 'False) (U1 :: Type -> Type)))

data SortStyle #

Instances

Instances details
FromJSON SortStyle # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

Data SortStyle # 
Instance details

Defined in Napkin.Types.Redshift

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortStyle -> c SortStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortStyle #

toConstr :: SortStyle -> Constr #

dataTypeOf :: SortStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SortStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortStyle) #

gmapT :: (forall b. Data b => b -> b) -> SortStyle -> SortStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortStyle -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortStyle -> m SortStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortStyle -> m SortStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortStyle -> m SortStyle #

Generic SortStyle # 
Instance details

Defined in Napkin.Types.Redshift

Associated Types

type Rep SortStyle :: Type -> Type #

Show SortStyle # 
Instance details

Defined in Napkin.Types.Redshift

Default SortStyle # 
Instance details

Defined in Napkin.Types.Redshift

Methods

def :: SortStyle #

Eq SortStyle # 
Instance details

Defined in Napkin.Types.Redshift

RenderSql SortStyle Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> SortStyle -> Doc #

type Rep SortStyle # 
Instance details

Defined in Napkin.Types.Redshift

type Rep SortStyle = D1 ('MetaData "SortStyle" "Napkin.Types.Redshift" "napkin-0.5.14-JrXUGmKUOt9J0meJSj0Kh4" 'False) (C1 ('MetaCons "SortCompound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SortInterleaved" 'PrefixI 'False) (U1 :: Type -> Type))

data SortKey #

Constructors

SortKey SortStyle [SExp] 

Instances

Instances details
FromJSON SortKey # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

Data SortKey # 
Instance details

Defined in Napkin.Types.Redshift

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortKey -> c SortKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortKey #

toConstr :: SortKey -> Constr #

dataTypeOf :: SortKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SortKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortKey) #

gmapT :: (forall b. Data b => b -> b) -> SortKey -> SortKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortKey -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortKey -> m SortKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortKey -> m SortKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortKey -> m SortKey #

Generic SortKey # 
Instance details

Defined in Napkin.Types.Redshift

Associated Types

type Rep SortKey :: Type -> Type #

Methods

from :: SortKey -> Rep SortKey x #

to :: Rep SortKey x -> SortKey #

Show SortKey # 
Instance details

Defined in Napkin.Types.Redshift

Eq SortKey # 
Instance details

Defined in Napkin.Types.Redshift

Methods

(==) :: SortKey -> SortKey -> Bool #

(/=) :: SortKey -> SortKey -> Bool #

RenderSql SortKey Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> SortKey -> Doc #

type Rep SortKey # 
Instance details

Defined in Napkin.Types.Redshift

type Rep SortKey = D1 ('MetaData "SortKey" "Napkin.Types.Redshift" "napkin-0.5.14-JrXUGmKUOt9J0meJSj0Kh4" 'False) (C1 ('MetaCons "SortKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SortStyle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SExp])))