module Hydra.Sources.Tier4.Ext.Cypher.Functions where data CypherFunction = CypherFunction { CypherFunction -> String cypherFunctionName :: String, CypherFunction -> Maybe String cypherFunctionKeyword :: Maybe String, CypherFunction -> [CypherFunctionForm] cypherFunctionForms :: [CypherFunctionForm]} deriving (CypherFunction -> CypherFunction -> Bool (CypherFunction -> CypherFunction -> Bool) -> (CypherFunction -> CypherFunction -> Bool) -> Eq CypherFunction forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: CypherFunction -> CypherFunction -> Bool == :: CypherFunction -> CypherFunction -> Bool $c/= :: CypherFunction -> CypherFunction -> Bool /= :: CypherFunction -> CypherFunction -> Bool Eq, Eq CypherFunction Eq CypherFunction => (CypherFunction -> CypherFunction -> Ordering) -> (CypherFunction -> CypherFunction -> Bool) -> (CypherFunction -> CypherFunction -> Bool) -> (CypherFunction -> CypherFunction -> Bool) -> (CypherFunction -> CypherFunction -> Bool) -> (CypherFunction -> CypherFunction -> CypherFunction) -> (CypherFunction -> CypherFunction -> CypherFunction) -> Ord CypherFunction CypherFunction -> CypherFunction -> Bool CypherFunction -> CypherFunction -> Ordering CypherFunction -> CypherFunction -> CypherFunction forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: CypherFunction -> CypherFunction -> Ordering compare :: CypherFunction -> CypherFunction -> Ordering $c< :: CypherFunction -> CypherFunction -> Bool < :: CypherFunction -> CypherFunction -> Bool $c<= :: CypherFunction -> CypherFunction -> Bool <= :: CypherFunction -> CypherFunction -> Bool $c> :: CypherFunction -> CypherFunction -> Bool > :: CypherFunction -> CypherFunction -> Bool $c>= :: CypherFunction -> CypherFunction -> Bool >= :: CypherFunction -> CypherFunction -> Bool $cmax :: CypherFunction -> CypherFunction -> CypherFunction max :: CypherFunction -> CypherFunction -> CypherFunction $cmin :: CypherFunction -> CypherFunction -> CypherFunction min :: CypherFunction -> CypherFunction -> CypherFunction Ord, Int -> CypherFunction -> ShowS [CypherFunction] -> ShowS CypherFunction -> String (Int -> CypherFunction -> ShowS) -> (CypherFunction -> String) -> ([CypherFunction] -> ShowS) -> Show CypherFunction forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> CypherFunction -> ShowS showsPrec :: Int -> CypherFunction -> ShowS $cshow :: CypherFunction -> String show :: CypherFunction -> String $cshowList :: [CypherFunction] -> ShowS showList :: [CypherFunction] -> ShowS Show) data CypherFunctionForm = CypherFunctionForm { CypherFunctionForm -> String cypherFunctionFormSignature :: String, CypherFunctionForm -> String cypherFunctionFormDescription :: String} deriving (CypherFunctionForm -> CypherFunctionForm -> Bool (CypherFunctionForm -> CypherFunctionForm -> Bool) -> (CypherFunctionForm -> CypherFunctionForm -> Bool) -> Eq CypherFunctionForm forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: CypherFunctionForm -> CypherFunctionForm -> Bool == :: CypherFunctionForm -> CypherFunctionForm -> Bool $c/= :: CypherFunctionForm -> CypherFunctionForm -> Bool /= :: CypherFunctionForm -> CypherFunctionForm -> Bool Eq, Eq CypherFunctionForm Eq CypherFunctionForm => (CypherFunctionForm -> CypherFunctionForm -> Ordering) -> (CypherFunctionForm -> CypherFunctionForm -> Bool) -> (CypherFunctionForm -> CypherFunctionForm -> Bool) -> (CypherFunctionForm -> CypherFunctionForm -> Bool) -> (CypherFunctionForm -> CypherFunctionForm -> Bool) -> (CypherFunctionForm -> CypherFunctionForm -> CypherFunctionForm) -> (CypherFunctionForm -> CypherFunctionForm -> CypherFunctionForm) -> Ord CypherFunctionForm CypherFunctionForm -> CypherFunctionForm -> Bool CypherFunctionForm -> CypherFunctionForm -> Ordering CypherFunctionForm -> CypherFunctionForm -> CypherFunctionForm forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: CypherFunctionForm -> CypherFunctionForm -> Ordering compare :: CypherFunctionForm -> CypherFunctionForm -> Ordering $c< :: CypherFunctionForm -> CypherFunctionForm -> Bool < :: CypherFunctionForm -> CypherFunctionForm -> Bool $c<= :: CypherFunctionForm -> CypherFunctionForm -> Bool <= :: CypherFunctionForm -> CypherFunctionForm -> Bool $c> :: CypherFunctionForm -> CypherFunctionForm -> Bool > :: CypherFunctionForm -> CypherFunctionForm -> Bool $c>= :: CypherFunctionForm -> CypherFunctionForm -> Bool >= :: CypherFunctionForm -> CypherFunctionForm -> Bool $cmax :: CypherFunctionForm -> CypherFunctionForm -> CypherFunctionForm max :: CypherFunctionForm -> CypherFunctionForm -> CypherFunctionForm $cmin :: CypherFunctionForm -> CypherFunctionForm -> CypherFunctionForm min :: CypherFunctionForm -> CypherFunctionForm -> CypherFunctionForm Ord, Int -> CypherFunctionForm -> ShowS [CypherFunctionForm] -> ShowS CypherFunctionForm -> String (Int -> CypherFunctionForm -> ShowS) -> (CypherFunctionForm -> String) -> ([CypherFunctionForm] -> ShowS) -> Show CypherFunctionForm forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> CypherFunctionForm -> ShowS showsPrec :: Int -> CypherFunctionForm -> ShowS $cshow :: CypherFunctionForm -> String show :: CypherFunctionForm -> String $cshowList :: [CypherFunctionForm] -> ShowS showList :: [CypherFunctionForm] -> ShowS Show) data CypherLibrary = CypherLibrary { CypherLibrary -> String cypherLibraryName :: String, CypherLibrary -> String cypherLibraryDescription :: String, CypherLibrary -> [CypherFunction] cypherLibraryFunctions :: [CypherFunction]} deriving (CypherLibrary -> CypherLibrary -> Bool (CypherLibrary -> CypherLibrary -> Bool) -> (CypherLibrary -> CypherLibrary -> Bool) -> Eq CypherLibrary forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: CypherLibrary -> CypherLibrary -> Bool == :: CypherLibrary -> CypherLibrary -> Bool $c/= :: CypherLibrary -> CypherLibrary -> Bool /= :: CypherLibrary -> CypherLibrary -> Bool Eq, Eq CypherLibrary Eq CypherLibrary => (CypherLibrary -> CypherLibrary -> Ordering) -> (CypherLibrary -> CypherLibrary -> Bool) -> (CypherLibrary -> CypherLibrary -> Bool) -> (CypherLibrary -> CypherLibrary -> Bool) -> (CypherLibrary -> CypherLibrary -> Bool) -> (CypherLibrary -> CypherLibrary -> CypherLibrary) -> (CypherLibrary -> CypherLibrary -> CypherLibrary) -> Ord CypherLibrary CypherLibrary -> CypherLibrary -> Bool CypherLibrary -> CypherLibrary -> Ordering CypherLibrary -> CypherLibrary -> CypherLibrary forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: CypherLibrary -> CypherLibrary -> Ordering compare :: CypherLibrary -> CypherLibrary -> Ordering $c< :: CypherLibrary -> CypherLibrary -> Bool < :: CypherLibrary -> CypherLibrary -> Bool $c<= :: CypherLibrary -> CypherLibrary -> Bool <= :: CypherLibrary -> CypherLibrary -> Bool $c> :: CypherLibrary -> CypherLibrary -> Bool > :: CypherLibrary -> CypherLibrary -> Bool $c>= :: CypherLibrary -> CypherLibrary -> Bool >= :: CypherLibrary -> CypherLibrary -> Bool $cmax :: CypherLibrary -> CypherLibrary -> CypherLibrary max :: CypherLibrary -> CypherLibrary -> CypherLibrary $cmin :: CypherLibrary -> CypherLibrary -> CypherLibrary min :: CypherLibrary -> CypherLibrary -> CypherLibrary Ord, Int -> CypherLibrary -> ShowS [CypherLibrary] -> ShowS CypherLibrary -> String (Int -> CypherLibrary -> ShowS) -> (CypherLibrary -> String) -> ([CypherLibrary] -> ShowS) -> Show CypherLibrary forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> CypherLibrary -> ShowS showsPrec :: Int -> CypherLibrary -> ShowS $cshow :: CypherLibrary -> String show :: CypherLibrary -> String $cshowList :: [CypherLibrary] -> ShowS showList :: [CypherLibrary] -> ShowS Show) cypherLibraries :: [CypherLibrary] cypherLibraries :: [CypherLibrary] cypherLibraries = [ String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Aggregate" String "aggregate functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "avg" (String -> Maybe String forall a. a -> Maybe a Just String "AVG") [ String -> String -> CypherFunctionForm CypherFunctionForm String "avg(input :: DURATION) :: DURATION" String "Returns the average of a set of DURATION values.", String -> String -> CypherFunctionForm CypherFunctionForm String "avg(input :: FLOAT) :: FLOAT" String "Returns the average of a set of FLOAT values.", String -> String -> CypherFunctionForm CypherFunctionForm String "avg(input :: INTEGER) :: INTEGER" String "Returns the average of a set of INTEGER values."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "collect" (String -> Maybe String forall a. a -> Maybe a Just String "COLLECT") [String -> String -> CypherFunctionForm CypherFunctionForm String "collect(input :: ANY) :: LIST<ANY>" String "Returns a list containing the values returned by an expression."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "count" (String -> Maybe String forall a. a -> Maybe a Just String "COUNT") [String -> String -> CypherFunctionForm CypherFunctionForm String "count(input :: ANY) :: INTEGER" String "Returns the number of values or rows."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "max" (String -> Maybe String forall a. a -> Maybe a Just String "MAX") [String -> String -> CypherFunctionForm CypherFunctionForm String "max(input :: ANY) :: ANY" String "Returns the maximum value in a set of values."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "min" (String -> Maybe String forall a. a -> Maybe a Just String "MIN") [String -> String -> CypherFunctionForm CypherFunctionForm String "min(input :: ANY) :: ANY" String "Returns the minimum value in a set of values."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "percentileCont" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "percentileCont(input :: FLOAT, percentile :: FLOAT) :: FLOAT" String "Returns the percentile of a value over a group using linear interpolation."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "percentileDisc" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "percentileDisc(input :: FLOAT, percentile :: FLOAT) :: FLOAT" String "Returns the nearest FLOAT value to the given percentile over a group using a rounding method.", String -> String -> CypherFunctionForm CypherFunctionForm String "percentileDisc(input :: INTEGER, percentile :: FLOAT) :: INTEGER" String "Returns the nearest INTEGER value to the given percentile over a group using a rounding method."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "stdev" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "stdev(input :: FLOAT) :: FLOAT" String "Returns the standard deviation for the given value over a group for a sample of a population."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "stdevp" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "stdevp(input :: FLOAT) :: FLOAT" String "Returns the standard deviation for the given value over a group for an entire population."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "sum" (String -> Maybe String forall a. a -> Maybe a Just String "SUM") [ String -> String -> CypherFunctionForm CypherFunctionForm String "sum(input :: DURATION) :: DURATION" String "Returns the sum of a set of DURATION values.", String -> String -> CypherFunctionForm CypherFunctionForm String "sum(input :: FLOAT) :: FLOAT" String "Returns the sum of a set of FLOAT values.", String -> String -> CypherFunctionForm CypherFunctionForm String "sum(input :: INTEGER) :: INTEGER" String "Returns the sum of a set of INTEGER values."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Database" String "database functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "db.nameFromElementId" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "db.nameFromElementId(name :: STRING) :: STRING" String "Resolves the database name from the given element id. Introduced in 5.12."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "GenAI" String "genAI functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "genai.vector.encode" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "genai.vector.encode(resource :: STRING, provider :: STRING, configuration :: MAP = {}) :: LIST<FLOAT>" String "Encode a given resource as a vector using the named provider. Introduced in 5.17."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Graph" String "graph functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "graph.byElementId" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "USE graph.byElementId(elementId :: STRING)" String "Resolves the constituent graph to which a given element id belongs. Introduced in 5.13."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "graph.byName" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "USE graph.byName(name :: STRING)" String "Resolves a constituent graph by name."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "graph.names" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "graph.names() :: LIST<STRING>" String "Returns a list containing the names of all graphs in the current composite database."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "graph.propertiesByName" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "graph.propertiesByName(name :: STRING) :: MAP" String "Returns a map containing the properties associated with the given graph."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "List" String "list functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "keys" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "keys(input :: MAP) :: LIST<STRING>" String "Returns a LIST<STRING> containing the STRING representations for all the property names of a MAP.", String -> String -> CypherFunctionForm CypherFunctionForm String "keys(input :: NODE) :: LIST<STRING>" String "Returns a LIST<STRING> containing the STRING representations for all the property names of a NODE.", String -> String -> CypherFunctionForm CypherFunctionForm String "keys(input :: RELATIONSHIP) :: LIST<STRING>" String "Returns a LIST<STRING> containing the STRING representations for all the property names of a RELATIONSHIP."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "labels" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "labels(input :: NODE) :: LIST<STRING>" String "Returns a LIST<STRING> containing the STRING representations for all the labels of a NODE."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "nodes" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "nodes(input :: PATH) :: LIST<NODE>" String "Returns a LIST<NODE> containing all the NODE values in a PATH."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "range" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "range(start :: INTEGER, end :: INTEGER) :: LIST<INTEGER>" String "Returns a LIST<INTEGER> comprising all INTEGER values within a specified range.", String -> String -> CypherFunctionForm CypherFunctionForm String "range(start :: INTEGER, end :: INTEGER, step :: INTEGER) :: LIST<INTEGER>" String "Returns a LIST<INTEGER> comprising all INTEGER values within a specified range created with step length."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "reduce" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "reduce(accumulator :: VARIABLE = initial :: ANY, variable :: VARIABLE IN list :: LIST<ANY> | expression :: ANY) :: ANY" String "Runs an expression against individual elements of a LIST<ANY>, storing the result of the expression in an accumulator."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "relationships" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "relationships(input :: PATH) :: LIST<RELATIONSHIP>" String "Returns a LIST<RELATIONSHIP> containing all the RELATIONSHIP values in a PATH."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "reverse" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "reverse(input :: LIST<ANY>) :: LIST<ANY>" String "Returns a LIST<ANY> in which the order of all elements in the given LIST<ANY> have been reversed."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "tail" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "tail(input :: LIST<ANY>) :: LIST<ANY>" String "Returns all but the first element in a LIST<ANY>."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toBooleanList" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toBooleanList(input :: LIST<ANY>) :: LIST<BOOLEAN>" String "Converts a LIST<ANY> of values to a LIST<BOOLEAN> values. If any values are not convertible to BOOLEAN they will be null in the LIST<BOOLEAN> returned."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toFloatList" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toFloatList(input :: LIST<ANY>) :: LIST<FLOAT>" String "Converts a LIST<ANY> to a LIST<FLOAT> values. If any values are not convertible to FLOAT they will be null in the LIST<FLOAT> returned."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toIntegerList" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toIntegerList(input :: LIST<ANY>) :: LIST<INTEGER>" String "Converts a LIST<ANY> to a LIST<INTEGER> values. If any values are not convertible to INTEGER they will be null in the LIST<INTEGER> returned."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toStringList" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toStringList(input :: LIST<ANY>) :: LIST<STRING>" String "Converts a LIST<ANY> to a LIST<STRING> values. If any values are not convertible to STRING they will be null in the LIST<STRING> returned."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "LoadCSV" String "load CSV functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "file" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "file() :: STRING" String "Returns the absolute path of the file that LOAD CSV is using."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "linenumber" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "linenumber() :: INTEGER" String "Returns the line number that LOAD CSV is currently using."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Logarithmic" String "logarithmic functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "e" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "e() :: FLOAT" String "Returns the base of the natural logarithm, e."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "exp" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "exp(input :: FLOAT) :: FLOAT" String "Returns e^n, where e is the base of the natural logarithm, and n is the value of the argument expression."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "log" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "log(input :: FLOAT) :: FLOAT" String "Returns the natural logarithm of a FLOAT."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "log10" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "log10(input :: FLOAT) :: FLOAT" String "Returns the common logarithm (base 10) of a FLOAT."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "sqrt" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "sqrt(input :: FLOAT) :: FLOAT" String "Returns the square root of a FLOAT."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Numeric" String "numeric functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "abs" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "abs(input :: FLOAT) :: FLOAT" String "Returns the absolute value of a FLOAT.", String -> String -> CypherFunctionForm CypherFunctionForm String "abs(input :: INTEGER) :: INTEGER" String "Returns the absolute value of an INTEGER."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "ceil" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "ceil(input :: FLOAT) :: FLOAT" String "Returns the smallest FLOAT that is greater than or equal to a number and equal to an INTEGER."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "floor" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "floor(input :: FLOAT) :: FLOAT" String "Returns the largest FLOAT that is less than or equal to a number and equal to an INTEGER."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "isNaN" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "isNaN(input :: FLOAT) :: BOOLEAN" String "Returns true if the floating point number is NaN.", String -> String -> CypherFunctionForm CypherFunctionForm String "isNaN(input :: INTEGER) :: BOOLEAN" String "Returns true if the integer number is NaN."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "rand" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "rand() :: FLOAT" String "Returns a random FLOAT in the range from 0 (inclusive) to 1 (exclusive)."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "round" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "round(input :: FLOAT) :: FLOAT" String "Returns the value of a number rounded to the nearest INTEGER.", String -> String -> CypherFunctionForm CypherFunctionForm String "round(value :: FLOAT, precision :: INTEGER | FLOAT) :: FLOAT" String "Returns the value of a number rounded to the specified precision using rounding mode HALF_UP.", String -> String -> CypherFunctionForm CypherFunctionForm String "round(value :: FLOAT, precision :: INTEGER | FLOAT, mode :: STRING) :: FLOAT" String "Returns the value of a number rounded to the specified precision with the specified rounding mode."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "sign" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "sign(input :: FLOAT) :: INTEGER" String "Returns the signum of a FLOAT: 0 if the number is 0, -1 for any negative number, and 1 for any positive number.", String -> String -> CypherFunctionForm CypherFunctionForm String "sign(input :: INTEGER) :: INTEGER" String "Returns the signum of an INTEGER: 0 if the number is 0, -1 for any negative number, and 1 for any positive number."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Predicate" String "predicate functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "all" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "all(variable :: VARIABLE IN list :: LIST<ANY> WHERE predicate :: ANY) :: BOOLEAN" String "Returns true if the predicate holds for all elements in the given LIST<ANY>."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "any" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "any(variable :: VARIABLE IN list :: LIST<ANY> WHERE predicate :: ANY) :: BOOLEAN" String "Returns true if the predicate holds for at least one element in the given LIST<ANY>."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "exists" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "exists(input :: ANY) :: BOOLEAN" String "Returns true if a match for the pattern exists in the graph."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "isEmpty" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "isEmpty(input :: LIST<ANY>) :: BOOLEAN" String "Checks whether a LIST<ANY> is empty.", String -> String -> CypherFunctionForm CypherFunctionForm String "isEmpty(input :: MAP) :: BOOLEAN" String "Checks whether a MAP is empty.", String -> String -> CypherFunctionForm CypherFunctionForm String "isEmpty(input :: STRING) :: BOOLEAN" String "Checks whether a STRING is empty."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "none" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "none(variable :: VARIABLE IN list :: LIST<ANY> WHERE predicate :: ANY) :: BOOLEAN" String "Returns true if the predicate holds for no element in the given LIST<ANY>."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "single" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "single(variable :: VARIABLE IN list :: LIST<ANY> WHERE predicate :: ANY) :: BOOLEAN" String "Returns true if the predicate holds for exactly one of the elements in the given LIST<ANY>."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Scalar" String "scalar functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "char_length" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "char_length(input :: STRING) :: INTEGER" String "Returns the number of Unicode characters in a STRING."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "character_length" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "character_length(input :: STRING) :: INTEGER" String "Returns the number of Unicode characters in a STRING."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "coalesce" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "coalesce(input :: ANY) :: ANY" String "Returns the first non-null value in a list of expressions."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "elementId" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "elementId(input :: NODE) :: STRING" String "Returns a node identifier, unique within a specific transaction and DBMS.", String -> String -> CypherFunctionForm CypherFunctionForm String "elementId(input :: RELATIONSHIP) :: STRING" String "Returns a relationship identifier, unique within a specific transaction and DBMS."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "endNode" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "elementId(input :: RELATIONSHIP) :: STRING" String "Returns a relationship identifier, unique within a specific transaction and DBMS."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "head" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "head(list :: LIST<ANY>) :: ANY" String "Returns the first element in a LIST<ANY>."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "id" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "id(input :: NODE) :: INTEGER" String "[Deprecated] Returns the id of a NODE. Replaced by elementId().", String -> String -> CypherFunctionForm CypherFunctionForm String "id(input :: RELATIONSHIP) :: INTEGER" String "[Deprecated] Returns the id of a RELATIONSHIP. Replaced by elementId()."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "last" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "last(list :: LIST<ANY>) :: ANY" String "Returns the last element in a LIST<ANY>."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "length" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "length(input :: PATH) :: INTEGER" String "Returns the length of a PATH."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "nullIf" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "nullIf(v1 :: ANY, v2 :: ANY) :: ANY" String "Returns null if the two given parameters are equivalent, otherwise returns the value of the first parameter."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "properties" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "properties(input :: MAP) :: MAP" String "Returns a MAP containing all the properties of a MAP.", String -> String -> CypherFunctionForm CypherFunctionForm String "properties(input :: NODE) :: MAP" String "Returns a MAP containing all the properties of a NODE.", String -> String -> CypherFunctionForm CypherFunctionForm String "properties(input :: RELATIONSHIP) :: MAP" String "Returns a MAP containing all the properties of a RELATIONSHIP."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "randomUUID" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "randomUUID() :: STRING" String "Generates a random UUID."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "size" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "size(input :: LIST<ANY>) :: INTEGER" String "Returns the number of items in a LIST<ANY>.", String -> String -> CypherFunctionForm CypherFunctionForm String "size(input :: STRING) :: INTEGER" String "Returns the number of Unicode characters in a STRING."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "startNode" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "startNode(input :: RELATIONSHIP) :: NODE" String "Returns the start NODE of a RELATIONSHIP."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toBoolean" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "toBoolean(input :: STRING) :: BOOLEAN" String "Converts a STRING value to a BOOLEAN value.", String -> String -> CypherFunctionForm CypherFunctionForm String "toBoolean(input :: BOOLEAN) :: BOOLEAN" String "Converts a BOOLEAN value to a BOOLEAN value.", String -> String -> CypherFunctionForm CypherFunctionForm String "toBoolean(input :: INTEGER) :: BOOLEAN" String "Converts an INTEGER value to a BOOLEAN value."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toBooleanOrNull" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toBooleanOrNull(input :: ANY) :: BOOLEAN" String "Converts a value to a BOOLEAN value, or null if the value cannot be converted."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toFloat" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "toFloat(input :: INTEGER | FLOAT) :: FLOAT" String "Converts an INTEGER value to a FLOAT value.", String -> String -> CypherFunctionForm CypherFunctionForm String "toFloat(input :: STRING) :: FLOAT" String "Converts a STRING value to a FLOAT value."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toFloatOrNull" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toFloatOrNull(input :: ANY) :: FLOAT" String "Converts a value to a FLOAT value, or null if the value cannot be converted."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toInteger" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "toInteger(input :: INTEGER | FLOAT) :: INTEGER" String "Converts a FLOAT value to an INTEGER value.", String -> String -> CypherFunctionForm CypherFunctionForm String "toInteger(input :: BOOLEAN) :: INTEGER" String "Converts a BOOLEAN value to an INTEGER value.", String -> String -> CypherFunctionForm CypherFunctionForm String "toInteger(input :: STRING) :: INTEGER" String "Converts a STRING value to an INTEGER value."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toIntegerOrNull" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toIntegerOrNull(input :: ANY) :: INTEGER" String "Converts a value to an INTEGER value, or null if the value cannot be converted."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "type" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "type(input :: RELATIONSHIP) :: STRING" String "Returns a STRING representation of the RELATIONSHIP type."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "valueType" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "valueType(input :: ANY) :: STRING" String "Returns a STRING representation of the most precise value type that the given expression evaluates to."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Spatial" String "spatial functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "point.distance" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "point.distance(from :: POINT, to :: POINT) :: FLOAT" String "Returns a FLOAT representing the geodesic distance between any two points in the same CRS."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "point" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "point(input :: MAP) :: POINT" String "Returns a 2D point object, given two coordinate values in the Cartesian coordinate system.", String -> String -> CypherFunctionForm CypherFunctionForm String "point(input :: MAP) :: POINT" String "Returns a 3D point object, given three coordinate values in the Cartesian coordinate system.", String -> String -> CypherFunctionForm CypherFunctionForm String "point(input :: MAP) :: POINT" String "Returns a 2D point object, given two coordinate values in the WGS 84 geographic coordinate system.", String -> String -> CypherFunctionForm CypherFunctionForm String "point(input :: MAP) :: POINT" String "Returns a 3D point object, given three coordinate values in the WGS 84 geographic coordinate system."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "point.withinBBox" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "point.withinBBox(point :: POINT, lowerLeft :: POINT, upperRight :: POINT) :: BOOLEAN" String "Returns true if the provided point is within the bounding box defined by the two provided points, lowerLeft and upperRight."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "String" String "string functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "btrim" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "btrim(original :: STRING) :: STRING" String "Returns the given STRING with leading and trailing whitespace removed.", String -> String -> CypherFunctionForm CypherFunctionForm String "btrim(input :: STRING, trimCharacterString :: STRING) :: STRING" String "Returns the given STRING with leading and trailing trimCharacterString characters removed. Introduced in 5.20."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "left" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "left(original :: STRING, length :: INTEGER) :: STRING" String "Returns a STRING containing the specified number (INTEGER) of leftmost characters in the given STRING."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "lower" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "lower(input :: STRING) :: STRING" String "Returns the given STRING in lowercase. This function is an alias to the toLower() function, and it was introduced as part of Cypher's GQL conformance. Introduced in 5.21."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "ltrim" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "ltrim(input :: STRING) :: STRING" String "Returns the given STRING with leading whitespace removed.", String -> String -> CypherFunctionForm CypherFunctionForm String "ltrim(input :: STRING, trimCharacterString :: STRING) :: STRING" String "Returns the given STRING with leading trimCharacterString characters removed. Introduced in 5.20."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "normalize" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "normalize(input :: STRING) :: STRING" String "Returns the given STRING normalized according to the normalization CypherFunctionForm NFC. Introduced in 5.17.", String -> String -> CypherFunctionForm CypherFunctionForm String "normalize(input :: STRING, normalForm = NFC :: [NFC, NFD, NFKC, NFKD]) :: STRING" String "Returns the given STRING normalized according to the specified normalization CypherFunctionForm. Introduced in 5.17."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "replace" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "replace(original :: STRING, search :: STRING, replace :: STRING) :: STRING" String "Returns a STRING in which all occurrences of a specified search STRING in the given STRING have been replaced by another (specified) replacement STRING."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "reverse" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "reverse(input :: STRING) :: STRING" String "Returns a STRING in which the order of all characters in the given STRING have been reversed."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "right" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "right(original :: STRING, length :: INTEGER) :: STRING" String "Returns a STRING containing the specified number of rightmost characters in the given STRING."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "rtrim" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "rtrim(input :: STRING) :: STRING" String "Returns the given STRING with trailing whitespace removed.", String -> String -> CypherFunctionForm CypherFunctionForm String "rtrim(input :: STRING, trimCharacterString :: STRING) :: STRING" String "Returns the given STRING with trailing trimCharacterString characters removed. Introduced in 5.20."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "split" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "split(original :: STRING, splitDelimiter :: STRING) :: LIST<STRING>" String "Returns a LIST<STRING> resulting from the splitting of the given STRING around matches of the given delimiter.", String -> String -> CypherFunctionForm CypherFunctionForm String "split(original :: STRING, splitDelimiters :: LIST<STRING>) :: LIST<STRING>" String "Returns a LIST<STRING> resulting from the splitting of the given STRING around matches of any of the given delimiters."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "substring" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "substring(original :: STRING, start :: INTEGER) :: STRING" String "Returns a substring of the given STRING, beginning with a 0-based index start.", String -> String -> CypherFunctionForm CypherFunctionForm String "substring(original :: STRING, start :: INTEGER, length :: INTEGER) :: STRING" String "Returns a substring of a given length from the given STRING, beginning with a 0-based index start."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toLower" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toLower(input :: STRING) :: STRING" String "Returns the given STRING in lowercase."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toString" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toString(input :: ANY) :: STRING" String "Converts an INTEGER, FLOAT, BOOLEAN, POINT or temporal type (i.e. DATE, ZONED TIME, LOCAL TIME, ZONED DATETIME, LOCAL DATETIME or DURATION) value to a STRING."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toStringOrNull" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toStringOrNull(input :: ANY) :: STRING" String "Converts an INTEGER, FLOAT, BOOLEAN, POINT or temporal type (i.e. DATE, ZONED TIME, LOCAL TIME, ZONED DATETIME, LOCAL DATETIME or DURATION) value to a STRING, or null if the value cannot be converted."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "toUpper" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "toUpper(input :: STRING) :: STRING" String "Returns the given STRING in uppercase."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "trim" Maybe String forall a. Maybe a Nothing [ String -> String -> CypherFunctionForm CypherFunctionForm String "trim(input :: STRING) :: STRING" String "Returns the given STRING with leading and trailing whitespace removed.", String -> String -> CypherFunctionForm CypherFunctionForm String "trim([LEADING | TRAILING | BOTH] [trimCharacterString :: STRING] FROM input :: STRING) :: STRING" String "Returns the given STRING with the leading and/or trailing trimCharacterString character removed. Introduced in 5.20."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "upper" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "upper(input :: STRING) :: STRING" String "Returns the given STRING in uppercase. This function is an alias to the toUpper() function, and it was introduced as part of Cypher's GQL conformance. Introduced in 5.21."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "TemporalDuration" String "temporal duration functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "duration" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "duration(input :: ANY) :: DURATION" String "Constructs a DURATION value."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "duration.between" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "duration.between(from :: ANY, to :: ANY) :: DURATION" String "Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in logical units."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "duration.inDays" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "duration.inDays(from :: ANY, to :: ANY) :: DURATION" String "Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in days."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "duration.inMonths" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "duration.inMonths(from :: ANY, to :: ANY) :: DURATION" String "Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in months."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "duration.inSeconds" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "duration.inSeconds(from :: ANY, to :: ANY) :: DURATION" String "Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in seconds."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "TemporalInstant" String "temporal instant functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "date" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "date(input = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: DATE" String "Creates a DATE instant."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "date.realtime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "date.realtime(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: DATE" String "Returns the current DATE instant using the realtime clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "date.statement" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "date.statement(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: DATE" String "Returns the current DATE instant using the statement clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "date.transaction" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "date.transaction(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: DATE" String "Returns the current DATE instant using the transaction clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "date.truncate" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "date.truncate(unit :: STRING, input = DEFAULT_TEMPORAL_ARGUMENT :: ANY, fields = null :: MAP) :: DATE" String "Truncates the given temporal value to a DATE instant using the specified unit."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "datetime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "datetime(input = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED DATETIME" String "Creates a ZONED DATETIME instant."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "datetime.fromepoch" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "datetime.fromepoch(seconds :: INTEGER | FLOAT, nanoseconds :: INTEGER | FLOAT) :: ZONED DATETIME" String "Creates a ZONED DATETIME given the seconds and nanoseconds since the start of the epoch."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "datetime.fromepochmillis" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "datetime.fromepochmillis(milliseconds :: INTEGER | FLOAT) :: ZONED DATETIME" String "Creates a ZONED DATETIME given the milliseconds since the start of the epoch."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "datetime.realtime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "datetime.realtime(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED DATETIME" String "Returns the current ZONED DATETIME instant using the realtime clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "datetime.statement" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "datetime.statement(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED DATETIME" String "Returns the current ZONED DATETIME instant using the statement clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "datetime.transaction" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "datetime.transaction(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED DATETIME" String "Returns the current ZONED DATETIME instant using the transaction clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "datetime.truncate" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "datetime.truncate(unit :: STRING, input = DEFAULT_TEMPORAL_ARGUMENT :: ANY, fields = null :: MAP) :: ZONED DATETIME" String "Truncates the given temporal value to a ZONED DATETIME instant using the specified unit."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localdatetime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localdatetime(input = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL DATETIME" String "Creates a LOCAL DATETIME instant."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localdatetime.realtime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localdatetime.realtime(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL DATETIME" String "Returns the current LOCAL DATETIME instant using the realtime clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localdatetime.statement" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localdatetime.statement(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL DATETIME" String "Returns the current LOCAL DATETIME instant using the statement clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localdatetime.transaction" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localdatetime.transaction(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL DATETIME" String "Returns the current LOCAL DATETIME instant using the transaction clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localdatetime.truncate" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localdatetime.truncate(unit :: STRING, input = DEFAULT_TEMPORAL_ARGUMENT :: ANY, fields = null :: MAP) :: LOCAL DATETIME" String "Truncates the given temporal value to a LOCAL DATETIME instant using the specified unit."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localtime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localtime(input = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL TIME" String "Creates a LOCAL TIME instant."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localtime.realtime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localtime.realtime(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL TIME" String "Returns the current LOCAL TIME instant using the realtime clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localtime.statement" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localtime.statement(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL TIME" String "Returns the current LOCAL TIME instant using the statement clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localtime.transaction" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localtime.transaction(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: LOCAL TIME" String "Returns the current LOCAL TIME instant using the transaction clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "localtime.truncate" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "localtime.truncate(unit :: STRING, input = DEFAULT_TEMPORAL_ARGUMENT :: ANY, fields = null :: MAP) :: LOCAL TIME" String "Truncates the given temporal value to a LOCAL TIME instant using the specified unit."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "time" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "time(input = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED TIME" String "Creates a ZONED TIME instant."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "time.realtime" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "time.realtime(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED TIME" String "Returns the current ZONED TIME instant using the realtime clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "time.statement" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "time.statement(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED TIME" String "Returns the current ZONED TIME instant using the statement clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "time.transaction" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "time.transaction(timezone = DEFAULT_TEMPORAL_ARGUMENT :: ANY) :: ZONED TIME" String "Returns the current ZONED TIME instant using the transaction clock."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "time.truncate" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "time.truncate(unit :: STRING, input = DEFAULT_TEMPORAL_ARGUMENT :: ANY, fields = null :: MAP) :: ZONED TIME" String "Truncates the given temporal value to a ZONED TIME instant using the specified unit."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Trigonometric" String "trigonometric functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "acos" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "acos(input :: FLOAT) :: FLOAT" String "Returns the arccosine of a FLOAT in radians."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "asin" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "asin(input :: FLOAT) :: FLOAT" String "Returns the arcsine of a FLOAT in radians."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "atan" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "atan(input :: FLOAT) :: FLOAT" String "Returns the arctangent of a FLOAT in radians."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "atan2" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "atan2(y :: FLOAT, x :: FLOAT) :: FLOAT" String "Returns the arctangent2 of a set of coordinates in radians."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "cos" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "cos(input :: FLOAT) :: FLOAT" String "Returns the cosine of a FLOAT."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "cot" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "cot(input :: FLOAT) :: FLOAT" String "Returns the cotangent of a FLOAT."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "degrees" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "degrees(input :: FLOAT) :: FLOAT" String "Converts radians to degrees."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "haversin" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "haversin(input :: FLOAT) :: FLOAT" String "Returns half the versine of a number."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "pi" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "pi() :: FLOAT" String "Returns the mathematical constant pi."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "radians" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "radians(input :: FLOAT) :: FLOAT" String "Converts degrees to radians."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "sin" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "sin(input :: FLOAT) :: FLOAT" String "Returns the sine of a FLOAT."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "tan" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "tan(input :: FLOAT) :: FLOAT" String "Returns the tangent of a FLOAT."]], String -> String -> [CypherFunction] -> CypherLibrary CypherLibrary String "Vector" String "vector functions" [ String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "vector.similarity.cosine" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "vector.similarity.cosine(a :: LIST<INTEGER | FLOAT>, b :: LIST<INTEGER | FLOAT>) :: FLOAT" String "Returns a FLOAT representing the similarity between the argument vectors based on their cosine."], String -> Maybe String -> [CypherFunctionForm] -> CypherFunction CypherFunction String "vector.similarity.euclidean" Maybe String forall a. Maybe a Nothing [String -> String -> CypherFunctionForm CypherFunctionForm String "vector.similarity.euclidean(a :: LIST<INTEGER | FLOAT>, b :: LIST<INTEGER | FLOAT>) :: FLOAT" String "Returns a FLOAT representing the similarity between the argument vectors based on their Euclidean distance."]]]