squeal-postgresql-0.8.0.0: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Definition.Index

Description

create and drop indexes

Synopsis

Create

createIndex Source #

Arguments

:: (Has sch db schema, Has tab schema ('Table table), KnownSymbol ix) 
=> Alias ix

index alias

-> QualifiedAlias sch tab

table alias

-> IndexMethod method

index method

-> [SortExpression 'Ungrouped '[] '[] db '[] '[tab ::: TableToRow table]]

sorted columns

-> Definition db (Alter sch (Create ix ('Index method) schema) db) 

Create an index.

>>> :{
type Table = '[] :=>
  '[ "a" ::: 'NoDef :=> 'Null 'PGint4
   , "b" ::: 'NoDef :=> 'Null 'PGfloat4 ]
:}
>>> :{
let
  setup :: Definition (Public '[]) (Public '["tab" ::: 'Table Table, "ix" ::: 'Index 'Btree])
  setup =
    createTable #tab (nullable int `as` #a :* nullable real `as` #b) Nil >>>
    createIndex #ix #tab btree [#a & AscNullsFirst, #b & AscNullsLast]
in printSQL setup
:}
CREATE TABLE "tab" ("a" int NULL, "b" real NULL);
CREATE INDEX "ix" ON "tab" USING btree (("a") ASC NULLS FIRST, ("b") ASC NULLS LAST);

createIndexIfNotExists Source #

Arguments

:: (Has sch db schema, Has tab schema ('Table table), KnownSymbol ix) 
=> Alias ix

index alias

-> QualifiedAlias sch tab

table alias

-> IndexMethod method

index method

-> [SortExpression 'Ungrouped '[] '[] db '[] '[tab ::: TableToRow table]]

sorted columns

-> Definition db (Alter sch (CreateIfNotExists ix ('Index method) schema) db) 

Create an index if it doesn't exist.

Drop

dropIndex Source #

Arguments

:: (Has sch db schema, KnownSymbol ix) 
=> QualifiedAlias sch ix

index alias

-> Definition db (Alter sch (DropSchemum ix 'Index schema) db) 

Drop an index.

>>> printSQL (dropIndex #ix :: Definition (Public '["ix" ::: 'Index 'Btree]) (Public '[]))
DROP INDEX "ix";

dropIndexIfExists Source #

Arguments

:: (Has sch db schema, KnownSymbol ix) 
=> QualifiedAlias sch ix

index alias

-> Definition db (Alter sch (DropSchemumIfExists ix 'Index schema) db) 

Drop an index if it exists.

Index Method

newtype IndexMethod ty Source #

PostgreSQL provides several index types: B-tree, Hash, GiST, SP-GiST, GIN and BRIN. Each index type uses a different algorithm that is best suited to different types of queries.

Instances

Instances details
Eq (IndexMethod ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Index

Methods

(==) :: IndexMethod ty -> IndexMethod ty -> Bool #

(/=) :: IndexMethod ty -> IndexMethod ty -> Bool #

Ord (IndexMethod ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Index

Show (IndexMethod ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Index

Generic (IndexMethod ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Index

Associated Types

type Rep (IndexMethod ty) :: Type -> Type #

Methods

from :: IndexMethod ty -> Rep (IndexMethod ty) x #

to :: Rep (IndexMethod ty) x -> IndexMethod ty #

RenderSQL (IndexMethod ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Index

type Rep (IndexMethod ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Index

type Rep (IndexMethod ty) = D1 ('MetaData "IndexMethod" "Squeal.PostgreSQL.Definition.Index" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "UnsafeIndexMethod" 'PrefixI 'True) (S1 ('MetaSel ('Just "renderIndexMethod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

btree :: IndexMethod 'Btree Source #

B-trees can handle equality and range queries on data that can be sorted into some ordering.

hash :: IndexMethod 'Hash Source #

Hash indexes can only handle simple equality comparisons.

gist :: IndexMethod 'Gist Source #

GiST indexes are not a single kind of index, but rather an infrastructure within which many different indexing strategies can be implemented.

spgist :: IndexMethod 'Spgist Source #

SP-GiST indexes, like GiST indexes, offer an infrastructure that supports various kinds of searches.

gin :: IndexMethod 'Gin Source #

GIN indexes are “inverted indexes” which are appropriate for data values that contain multiple component values, such as arrays.

brin :: IndexMethod 'Brin Source #

BRIN indexes (a shorthand for Block Range INdexes) store summaries about the values stored in consecutive physical block ranges of a table.