Copyright | (c) Aaron Allen 2020 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Aaron Allen <aaronallen8455@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Typson.Pathing
Contents
Description
Synopsis
- data key :-> path
- type family TypeAtPath (obj :: Type) (tree :: Tree) (path :: k) :: Type where ...
- typeAtPath :: proxy path -> repr tree obj -> Proxy (TypeAtPath obj tree path)
- data PathComponent
- class ReflectPath path where
- reflectPath :: proxy path -> NonEmpty PathComponent
- sqlPath :: ReflectPath path => proxy path -> String
Pathing
Components for constructing JSON paths for queries.
data key :-> path infixr 4 Source #
A type operator for building a JSON query path from multiple components.
type MyQuery = "foo" :-> "bar" :-> 2 :-> "baz"
Instances
(ReflectPath key, ReflectPath path) => ReflectPath (key :-> path :: Type) Source # | |
Defined in Typson.Pathing Methods reflectPath :: proxy (key :-> path) -> NonEmpty PathComponent Source # |
type family TypeAtPath (obj :: Type) (tree :: Tree) (path :: k) :: Type where ... Source #
Determine the type of the query result for a path into a JSON schema.
Nullability is propagated so that the result will be wrapped with Maybe
if
one or more components of the path are nullable.
Equations
TypeAtPath obj ('Node aggr ('Edge fieldName q field subTree ': rest)) fieldName = ApQuantity q field | |
TypeAtPath (f obj) ('IndexedNode k subTree) (key :: k) = ApQuantity 'Nullable obj | |
TypeAtPath (f obj) ('IndexedNode k subTree) ((key :: k) :-> nextKey) = ApQuantity 'Nullable (TypeAtPath obj subTree nextKey) | |
TypeAtPath obj ('IndexedNode k subTree) key = TypeError (((((('Text "Invalid JSON path: expected a " :<>: 'ShowType k) :<>: 'Text " index for ") :<>: 'ShowType obj) :<>: 'Text " but got \"") :<>: 'ShowType key) :<>: 'Text "\".") | |
TypeAtPath obj ('Node aggr ('Edge fieldName q field subFields ': rest)) (fieldName :-> nextKey) = ApQuantity q (TypeAtPath field subFields nextKey) | |
TypeAtPath obj ('Node aggr ('Edge fieldName q field subFields ': rest)) key = TypeAtPath obj ('Node aggr rest) key | |
TypeAtPath obj tree (key :: Symbol) = TypeError (MissingKey obj key) | |
TypeAtPath obj tree ((key :: Symbol) :-> path) = TypeError (MissingKey obj key) | |
TypeAtPath obj tree (idx :-> nextKey) = TypeError (InvalidKey idx obj) | |
TypeAtPath obj tree idx = TypeError (InvalidKey idx obj) |
Arguments
:: proxy path | A path proxy |
-> repr tree obj | Schema for the type being queried |
-> Proxy (TypeAtPath obj tree path) |
Get the result type for a query at a given path.
Path Reflection
class ReflectPath path where Source #
Methods
reflectPath :: proxy path -> NonEmpty PathComponent Source #
Reflect a type-level path to it's value level PathComponent
s.
Instances
KnownNat idx => ReflectPath (idx :: Nat) Source # | |
Defined in Typson.Pathing Methods reflectPath :: proxy idx -> NonEmpty PathComponent Source # | |
KnownSymbol key => ReflectPath (key :: Symbol) Source # | |
Defined in Typson.Pathing Methods reflectPath :: proxy key -> NonEmpty PathComponent Source # | |
(ReflectPath key, ReflectPath path) => ReflectPath (key :-> path :: Type) Source # | |
Defined in Typson.Pathing Methods reflectPath :: proxy (key :-> path) -> NonEmpty PathComponent Source # |
sqlPath :: ReflectPath path => proxy path -> String Source #
Reflect a path as an SQL JSON path string