squeal-postgresql-ltree-0.1.0.1: LTree extension for Squeal
Copyright(c) Eitan Chatav 2020
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.LTree

Description

This module implements a data type ltree for representing labels of data stored in a hierarchical tree-like structure.

Synopsis

Definition

createLTree :: Definition db db Source #

Loads ltree extension into the current database.

Types

newtype LTree Source #

A label is a sequence of alphanumeric characters and underscores (for example, in C locale the characters A-Za-z0-9_ are allowed). Labels must be less than 256 bytes long.

Examples: 42, Personal_Services

A label path is a sequence of zero or more labels separated by dots, for example L1.L2.L3, representing a path from the root of a hierarchical tree to a particular node. The length of a label path must be less than 65Kb, but keeping it under 2Kb is preferable. In practice this is not a major limitation; for example, the longest label path in the DMOZ catalogue (http://www.dmoz.org) is about 240 bytes.

Example: Top.Countries.Europe.Russia

ltree stores a label path.

Constructors

UnsafeLTree 

Fields

Instances

Instances details
Eq LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Methods

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

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

Ord LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Methods

compare :: LTree -> LTree -> Ordering #

(<) :: LTree -> LTree -> Bool #

(<=) :: LTree -> LTree -> Bool #

(>) :: LTree -> LTree -> Bool #

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

max :: LTree -> LTree -> LTree #

min :: LTree -> LTree -> LTree #

Read LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Show LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Methods

showsPrec :: Int -> LTree -> ShowS #

show :: LTree -> String #

showList :: [LTree] -> ShowS #

Generic LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Associated Types

type Rep LTree :: Type -> Type #

Methods

from :: LTree -> Rep LTree x #

to :: Rep LTree x -> LTree #

Inline LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Methods

inline :: forall (null :: PGType -> NullType). LTree -> Expr (null (PG LTree)) #

(TypeError ('Text "LTree binary instances not yet implemented.") :: Constraint) => FromPG LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

IsPG LTree Source #

PGltree

Instance details

Defined in Squeal.PostgreSQL.LTree

Associated Types

type PG LTree :: PGType #

(TypeError ('Text "LTree binary instances not yet implemented.") :: Constraint) => ToPG db LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

type Rep LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

type Rep LTree = D1 ('MetaData "LTree" "Squeal.PostgreSQL.LTree" "squeal-postgresql-ltree-0.1.0.1-EW1Obz6IXQ3I2nwjGW7OIA" 'True) (C1 ('MetaCons "UnsafeLTree" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLTree") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type PG LTree Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

newtype LQuery Source #

lquery represents a regular-expression-like pattern for matching ltree values. A simple word matches that label within a path. A star symbol (*) matches zero or more labels. For example:

foo         Match the exact label path foo
*.foo.*     Match any label path containing the label foo
*.foo       Match any label path whose last label is foo

Star symbols can also be quantified to restrict how many labels they can match:

*{n}        Match exactly n labels
*{n,}       Match at least n labels
*{n,m}      Match at least n but not more than m labels
*{,m}       Match at most m labels — same as  *{0,m}

There are several modifiers that can be put at the end of a non-star label in lquery to make it match more than just the exact match:

@           Match case-insensitively, for example a@ matches A
*           Match any label with this prefix, for example foo* matches foobar
%           Match initial underscore-separated words

The behavior of % is a bit complicated. It tries to match words rather than the entire label. For example foo_bar% matches foo_bar_baz but not foo_barbaz. If combined with *, prefix matching applies to each word separately, for example foo_bar%* matches foo1_bar2_baz but not foo1_br2_baz.

Also, you can write several possibly-modified labels separated with | (OR) to match any of those labels, and you can put ! (NOT) at the start to match any label that doesn't match any of the alternatives.

Here's an annotated example of lquery:

Top.*{0,2}.sport*@.!football|tennis.Russ*|Spain
1.  2.     3.      4.               5.

This query will match any label path that:

  1. begins with the label Top
  2. and next has zero to two labels before
  3. a label beginning with the case-insensitive prefix sport
  4. then a label not matching football nor tennis
  5. and then ends with a label beginning with Russ or exactly matching Spain.

Constructors

UnsafeLQuery 

Fields

Instances

Instances details
Eq LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Methods

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

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

Ord LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Read LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Show LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Generic LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Associated Types

type Rep LQuery :: Type -> Type #

Methods

from :: LQuery -> Rep LQuery x #

to :: Rep LQuery x -> LQuery #

Inline LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Methods

inline :: forall (null :: PGType -> NullType). LQuery -> Expr (null (PG LQuery)) #

(TypeError ('Text "LQuery binary instances not yet implemented.") :: Constraint) => FromPG LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

IsPG LQuery Source #

PGlquery

Instance details

Defined in Squeal.PostgreSQL.LTree

Associated Types

type PG LQuery :: PGType #

(TypeError ('Text "LQuery binary instances not yet implemented.") :: Constraint) => ToPG db LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

type Rep LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

type Rep LQuery = D1 ('MetaData "LQuery" "Squeal.PostgreSQL.LTree" "squeal-postgresql-ltree-0.1.0.1-EW1Obz6IXQ3I2nwjGW7OIA" 'True) (C1 ('MetaCons "UnsafeLQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type PG LQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

newtype LTxtQuery Source #

ltxtquery represents a full-text-search-like pattern for matching ltree values. An ltxtquery value contains words, possibly with the modifiers @, *, % at the end; the modifiers have the same meanings as in lquery. Words can be combined with & (AND), | (OR), ! (NOT), and parentheses. The key difference from lquery is that ltxtquery matches words without regard to their position in the label path.

Here's an example ltxtquery:

Europe & Russia*@ & !Transportation

This will match paths that contain the label Europe and any label beginning with Russia (case-insensitive), but not paths containing the label Transportation. The location of these words within the path is not important. Also, when % is used, the word can be matched to any underscore-separated word within a label, regardless of position.

Note: ltxtquery allows whitespace between symbols, but ltree and lquery do not.

Constructors

UnsafeLTxtQuery 

Fields

Instances

Instances details
Eq LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Ord LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Read LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Show LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Generic LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Associated Types

type Rep LTxtQuery :: Type -> Type #

Inline LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

Methods

inline :: forall (null :: PGType -> NullType). LTxtQuery -> Expr (null (PG LTxtQuery)) #

(TypeError ('Text "LTxtQuery binary instances not yet implemented.") :: Constraint) => FromPG LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

IsPG LTxtQuery Source #

PGltxtquery

Instance details

Defined in Squeal.PostgreSQL.LTree

Associated Types

type PG LTxtQuery :: PGType #

(TypeError ('Text "LTxtQuery binary instances not yet implemented.") :: Constraint) => ToPG db LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

type Rep LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

type Rep LTxtQuery = D1 ('MetaData "LTxtQuery" "Squeal.PostgreSQL.LTree" "squeal-postgresql-ltree-0.1.0.1-EW1Obz6IXQ3I2nwjGW7OIA" 'True) (C1 ('MetaCons "UnsafeLTxtQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLTxtQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type PG LTxtQuery Source # 
Instance details

Defined in Squeal.PostgreSQL.LTree

type PGltree = 'UnsafePGType "ltree" Source #

Postgres ltree type

type PGlquery = 'UnsafePGType "lquery" Source #

Postgres lquery type

type PGltxtquery = 'UnsafePGType "ltxtquery" Source #

Postgres ltxtquery type

ltree :: TypeExpression db (null PGltree) Source #

Postgres ltree type expression

lquery :: TypeExpression db (null PGlquery) Source #

Postgres lquery type expression

ltxtquery :: TypeExpression db (null PGltxtquery) Source #

Postgres ltxtquery type expression

Functions

subltree :: '[null PGltree, null 'PGint4, null 'PGint4] ---> null PGltree Source #

Returns subpath of ltree from position start to position end-1 (counting from 0).

subpath :: '[null PGltree, null 'PGint4, null 'PGint4] ---> null PGltree Source #

Returns subpath of ltree starting at position offset, with length len. If offset is negative, subpath starts that far from the end of the path. If len is negative, leaves that many labels off the end of the path.

subpathEnd :: '[null PGltree, null 'PGint4] ---> null PGltree Source #

Returns subpath of ltree starting at position offset, extending to end of path. If offset is negative, subpath starts that far from the end of the path.

nlevel :: null PGltree --> null 'PGint4 Source #

Returns number of labels in path.

indexLTree :: '[null PGltree, null PGltree] ---> null 'PGint4 Source #

Returns position of first occurrence of b in a, or -1 if not found.

indexOffset :: '[null PGltree, null PGltree, null 'PGint4] ---> null 'PGint4 Source #

Returns position of first occurrence of b in a, or -1 if not found. The search starts at position offset; negative offset means start -offset labels from the end of the path.

text2ltree :: null 'PGtext --> null PGltree Source #

Casts text to ltree.

ltree2text :: null PGltree --> null 'PGtext Source #

Casts ltree to text.

lca :: null ('PGvararray ('NotNull PGltree)) --> null PGltree Source #

Computes longest common ancestor of paths in array.

Operators

(%~) :: Operator (null0 PGltree) (null1 PGlquery) ('Null 'PGbool) infix 4 Source #

Does ltree match lquery?

(~%) :: Operator (null1 PGlquery) (null0 PGltree) ('Null 'PGbool) infix 4 Source #

Does ltree match lquery?

(%?) :: Operator (null0 PGltree) (null1 ('PGvararray ('NotNull PGlquery))) ('Null 'PGbool) infix 4 Source #

Does ltree match any lquery in array?

(?%) :: Operator (null0 ('PGvararray ('NotNull PGlquery))) (null1 PGltree) ('Null 'PGbool) infix 4 Source #

Does ltree match any lquery in array?

(%@) :: Operator (null0 PGltree) (null1 PGltxtquery) ('Null 'PGbool) infix 4 Source #

Does ltree match ltxtquery?

(@%) :: Operator (null0 PGltxtquery) (null1 PGltree) ('Null 'PGbool) infix 4 Source #

Does ltree match ltxtquery?

(@>%) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGltree) ('Null 'PGbool) infix 4 Source #

Does array contain an ancestor of ltree?

(%<@) :: Operator (null0 PGltree) (null1 ('PGvararray ('NotNull PGltree))) ('Null 'PGbool) infix 4 Source #

Does array contain an ancestor of ltree?

(<@%) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGltree) ('Null 'PGbool) infix 4 Source #

Does array contain a descendant of ltree?

(%@>) :: Operator (null0 PGltree) (null1 ('PGvararray ('NotNull PGltree))) ('Null 'PGbool) infix 4 Source #

Does array contain a descendant of ltree?

(&~) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGlquery) ('Null 'PGbool) infix 4 Source #

Does array contain any path matching lquery?

(~&) :: Operator (null0 PGlquery) (null1 ('PGvararray ('NotNull PGltree))) ('Null 'PGbool) infix 4 Source #

Does array contain any path matching lquery?

(&?) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 ('PGvararray ('NotNull PGlquery))) ('Null 'PGbool) infix 4 Source #

Does ltree array contain any path matching any lquery?

(?&) :: Operator (null0 ('PGvararray ('NotNull PGlquery))) (null1 ('PGvararray ('NotNull PGltree))) ('Null 'PGbool) infix 4 Source #

Does ltree array contain any path matching any lquery?

(&@) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGltxtquery) ('Null 'PGbool) infix 4 Source #

Does array contain any path matching ltxtquery?

(@&) :: Operator (null0 PGltxtquery) (null1 ('PGvararray ('NotNull PGltree))) ('Null 'PGbool) infix 4 Source #

Does array contain any path matching ltxtquery?

(?@>) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGltree) ('Null PGltree) infix 4 Source #

Returns first array entry that is an ancestor of ltree, or NULL if none.

(?<@) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGltree) ('Null PGltree) infix 4 Source #

Returns first array entry that is a descendant of ltree, or NULL if none.

(?~) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGlquery) ('Null PGltree) infix 4 Source #

Returns first array entry that matches lquery, or NULL if none.

(?@) :: Operator (null0 ('PGvararray ('NotNull PGltree))) (null1 PGltxtquery) ('Null PGltree) infix 4 Source #

Returns first array entry that matches ltxtquery, or NULL if none.

Orphan instances

PGTyped db PGltxtquery Source # 
Instance details

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null PGltxtquery) #

PGTyped db PGlquery Source # 
Instance details

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null PGlquery) #

PGTyped db PGltree Source # 
Instance details

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null PGltree) #

PGSubset PGltree Source #

(@>) Is left argument an ancestor of right (or equal)?

(<@) Is left argument a descendant of right (or equal)?

Instance details

Methods

(@>) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 PGltree) (null1 PGltree) ('Null 'PGbool) #

(<@) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 PGltree) (null1 PGltree) ('Null 'PGbool) #

OidOf db PGltxtquery Source # 
Instance details

Methods

oidOf :: ReaderT (K Connection db) IO Oid #

OidOf db PGlquery Source # 
Instance details

Methods

oidOf :: ReaderT (K Connection db) IO Oid #

OidOf db PGltree Source # 
Instance details

Methods

oidOf :: ReaderT (K Connection db) IO Oid #

OidOfArray db PGltxtquery Source # 
Instance details

OidOfArray db PGlquery Source # 
Instance details

OidOfArray db PGltree Source # 
Instance details

IsString (Expression grp lat with db params from (null PGltxtquery)) Source # 
Instance details

Methods

fromString :: String -> Expression grp lat with db params from (null PGltxtquery) #

IsString (Expression grp lat with db params from (null PGlquery)) Source # 
Instance details

Methods

fromString :: String -> Expression grp lat with db params from (null PGlquery) #

IsString (Expression grp lat with db params from (null PGltree)) Source # 
Instance details

Methods

fromString :: String -> Expression grp lat with db params from (null PGltree) #

Semigroup (Expression grp lat with db params from (null PGltree)) Source #

(<>) Concatenates ltree paths.

Instance details

Methods

(<>) :: Expression grp lat with db params from (null PGltree) -> Expression grp lat with db params from (null PGltree) -> Expression grp lat with db params from (null PGltree) #

sconcat :: NonEmpty (Expression grp lat with db params from (null PGltree)) -> Expression grp lat with db params from (null PGltree) #

stimes :: Integral b => b -> Expression grp lat with db params from (null PGltree) -> Expression grp lat with db params from (null PGltree) #

Monoid (Expression grp lat with db params from (null PGltree)) Source # 
Instance details

Methods

mempty :: Expression grp lat with db params from (null PGltree) #

mappend :: Expression grp lat with db params from (null PGltree) -> Expression grp lat with db params from (null PGltree) -> Expression grp lat with db params from (null PGltree) #

mconcat :: [Expression grp lat with db params from (null PGltree)] -> Expression grp lat with db params from (null PGltree) #