napkin-0.5.13
Safe HaskellNone
LanguageHaskell2010

Napkin.Types.Core

Synopsis

Documentation

data Name #

Copyright : (c) Soostone Inc, 2020 License : AllRightsReserved Stability : experimental Portability : POSIX

Constructors

Specific String 
Star 

Instances

Instances details
Eq Name # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Data Name # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Name # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Read Name # 
Instance details

Defined in Napkin.Types.Core

Show Name # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name # 
Instance details

Defined in Napkin.Types.Core

Methods

fromString :: String -> Name #

Generic Name # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Name -> () #

Hashable Name # 
Instance details

Defined in Napkin.Types.Core

Methods

hashWithSalt :: Int -> Name -> Int #

hash :: Name -> Int #

ToJSON Name # 
Instance details

Defined in Napkin.Types.Core

FromJSON Name # 
Instance details

Defined in Napkin.Types.Core

IsRef Name # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). Name -> Ref b #

Lift Name # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: Name -> Q Exp #

liftTyped :: Name -> Q (TExp Name) #

RenderSql Name Sqlite # 
Instance details

Defined in Napkin.Render.Sqlite

Methods

renderSql :: Sqlite -> Name -> Doc #

RenderSql Name Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Name -> Doc #

RenderSql Name Postgres # 
Instance details

Defined in Napkin.Render.Postgres

Methods

renderSql :: Postgres -> Name -> Doc #

RenderSql Name BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Name -> Doc #

Lift (NonEmpty Name) # 
Instance details

Defined in Napkin.Types.Core

IsRef [Name] # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). [Name] -> Ref b #

IsRef (NonEmpty Name) # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). NonEmpty Name -> Ref b #

HasDeps (OMap Name SExp) # 
Instance details

Defined in Napkin.Types.Deps

Cons (Ref a) (Ref a) Name Name # 
Instance details

Defined in Napkin.Types.Core

Methods

_Cons :: Prism (Ref a) (Ref a) (Name, Ref a) (Name, Ref a) #

Snoc (Ref a) (Ref a) Name Name # 
Instance details

Defined in Napkin.Types.Core

Methods

_Snoc :: Prism (Ref a) (Ref a) (Ref a, Name) (Ref a, Name) #

type Rep Name # 
Instance details

Defined in Napkin.Types.Core

type Rep Name = D1 ('MetaData "Name" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "Specific" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Star" 'PrefixI 'False) (U1 :: Type -> Type))

newtype Ref a #

A way to refer to entities like fields, tables, schemas, etc. Namespacing is common so we keep a list here.

Constructors

Ref 

Fields

Instances

Instances details
Lift (Ref a :: Type) # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: Ref a -> Q Exp #

liftTyped :: Ref a -> Q (TExp (Ref a)) #

BeamSqlBackend bk => HasSqlEqualityCheck bk (Ref a) # 
Instance details

Defined in Napkin.Metadata.Instances

HasSqlValueSyntax bk Text => HasSqlValueSyntax bk (Ref a) # 
Instance details

Defined in Napkin.Metadata.Instances

Methods

sqlValueSyntax :: Ref a -> bk #

(BeamMigrateSqlBackend bk, FromBackendRow bk Text) => FromBackendRow bk (Ref a) # 
Instance details

Defined in Napkin.Metadata.Instances

BeamMigrateSqlBackend bk => HasDefaultSqlDataType bk (Ref a) # 
Instance details

Defined in Napkin.Metadata.Instances

BeamSqlBackend bk => DataTypeForBackend bk (Ref b) # 
Instance details

Defined in Napkin.Metadata.Migrations

Methods

dbType :: DataType bk (Ref b) #

Eq (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

(==) :: Ref a -> Ref a -> Bool #

(/=) :: Ref a -> Ref a -> Bool #

(Typeable a, Typeable k) => Data (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Ref a -> Constr #

dataTypeOf :: Ref a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: Ref a -> Ref a -> Ordering #

(<) :: Ref a -> Ref a -> Bool #

(<=) :: Ref a -> Ref a -> Bool #

(>) :: Ref a -> Ref a -> Bool #

(>=) :: Ref a -> Ref a -> Bool #

max :: Ref a -> Ref a -> Ref a #

min :: Ref a -> Ref a -> Ref a #

Read (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Show (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> Ref a -> ShowS #

show :: Ref a -> String #

showList :: [Ref a] -> ShowS #

IsString (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

fromString :: String -> Ref a #

Generic (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep (Ref a) :: Type -> Type #

Methods

from :: Ref a -> Rep (Ref a) x #

to :: Rep (Ref a) x -> Ref a #

Semigroup (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

(<>) :: Ref a -> Ref a -> Ref a #

sconcat :: NonEmpty (Ref a) -> Ref a #

stimes :: Integral b => b -> Ref a -> Ref a #

NFData (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Ref a -> () #

Hashable (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

hashWithSalt :: Int -> Ref a -> Int #

hash :: Ref a -> Int #

ToJSON (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

toJSON :: Ref a -> Value #

toEncoding :: Ref a -> Encoding #

toJSONList :: [Ref a] -> Value #

toEncodingList :: [Ref a] -> Encoding #

ToJSONKey (Ref a) # 
Instance details

Defined in Napkin.Types.Core

FromJSON (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

parseJSON :: Value -> Parser (Ref a) #

parseJSONList :: Value -> Parser [Ref a] #

FromJSONKey (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Buildable (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

build :: Ref a -> Builder #

AsRelation (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

asRelation :: Ref a -> Relation #

IsRef (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). Ref a -> Ref b #

TableRef (Ref Table) # 
Instance details

Defined in Napkin.Types.Core

Methods

tableRef :: Lens' (Ref Table) (Ref Table) #

HasDeps (Ref Table) # 
Instance details

Defined in Napkin.Types.Deps

RenderSql (Ref t) Sqlite # 
Instance details

Defined in Napkin.Render.Sqlite

Methods

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

RenderSql (Ref t) Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

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

RenderSql (Ref t) Postgres # 
Instance details

Defined in Napkin.Render.Postgres

Methods

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

RenderSql (Ref t) BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

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

Cons (Ref a) (Ref a) Name Name # 
Instance details

Defined in Napkin.Types.Core

Methods

_Cons :: Prism (Ref a) (Ref a) (Name, Ref a) (Name, Ref a) #

Snoc (Ref a) (Ref a) Name Name # 
Instance details

Defined in Napkin.Types.Core

Methods

_Snoc :: Prism (Ref a) (Ref a) (Ref a, Name) (Ref a, Name) #

type Rep (Ref a) # 
Instance details

Defined in Napkin.Types.Core

type Rep (Ref a) = D1 ('MetaData "Ref" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'True) (C1 ('MetaCons "Ref" 'PrefixI 'True) (S1 ('MetaSel ('Just "_unRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Name))))

class IsRef a where #

Class of string-like types that can be interpreted as Refs

Methods

ref :: forall b. a -> Ref b #

Instances

Instances details
IsRef String # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). String -> Ref b #

IsRef Text # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). Text -> Ref b #

IsRef Name # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). Name -> Ref b #

IsRef [Name] # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). [Name] -> Ref b #

IsRef (NonEmpty Name) # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). NonEmpty Name -> Ref b #

IsRef (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

ref :: forall k (b :: k). Ref a -> Ref b #

refComponentCount :: Ref a -> Int #

Return the number of Names in the Ref.

textRef :: Text -> Ref a #

nameRef :: Name -> Ref a #

namesRef :: [Name] -> Ref a #

refText :: Ref t -> Text #

retagRef :: Ref t -> Ref a #

appendRef :: Ref a -> Name -> Ref a #

data Table #

Instances

Instances details
Data Table # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Table -> Constr #

dataTypeOf :: Table -> DataType #

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

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

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

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

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

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

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

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

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

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

TableRef (Ref Table) # 
Instance details

Defined in Napkin.Types.Core

Methods

tableRef :: Lens' (Ref Table) (Ref Table) #

HasDeps (Ref Table) # 
Instance details

Defined in Napkin.Types.Deps

data Function #

Instances

Instances details
Data Function # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Function -> Constr #

dataTypeOf :: Function -> DataType #

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

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

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

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

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

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

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

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

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

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

data Selected a #

Select something and give it a name; e.g. (my_field as foo)

Constructors

Selected 

Fields

Instances

Instances details
Foldable Selected # 
Instance details

Defined in Napkin.Types.Core

Methods

fold :: Monoid m => Selected m -> m #

foldMap :: Monoid m => (a -> m) -> Selected a -> m #

foldMap' :: Monoid m => (a -> m) -> Selected a -> m #

foldr :: (a -> b -> b) -> b -> Selected a -> b #

foldr' :: (a -> b -> b) -> b -> Selected a -> b #

foldl :: (b -> a -> b) -> b -> Selected a -> b #

foldl' :: (b -> a -> b) -> b -> Selected a -> b #

foldr1 :: (a -> a -> a) -> Selected a -> a #

foldl1 :: (a -> a -> a) -> Selected a -> a #

toList :: Selected a -> [a] #

null :: Selected a -> Bool #

length :: Selected a -> Int #

elem :: Eq a => a -> Selected a -> Bool #

maximum :: Ord a => Selected a -> a #

minimum :: Ord a => Selected a -> a #

sum :: Num a => Selected a -> a #

product :: Num a => Selected a -> a #

WithName Selected # 
Instance details

Defined in Napkin.Types.Core

Methods

as :: b -> Ref b -> Selected b #

Lift a => Lift (Selected a :: Type) # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: Selected a -> Q Exp #

liftTyped :: Selected a -> Q (TExp (Selected a)) #

Eq a => Eq (Selected a) # 
Instance details

Defined in Napkin.Types.Core

Methods

(==) :: Selected a -> Selected a -> Bool #

(/=) :: Selected a -> Selected a -> Bool #

Data a => Data (Selected a) # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Selected a -> Constr #

dataTypeOf :: Selected a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Selected a) # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: Selected a -> Selected a -> Ordering #

(<) :: Selected a -> Selected a -> Bool #

(<=) :: Selected a -> Selected a -> Bool #

(>) :: Selected a -> Selected a -> Bool #

(>=) :: Selected a -> Selected a -> Bool #

max :: Selected a -> Selected a -> Selected a #

min :: Selected a -> Selected a -> Selected a #

Show a => Show (Selected a) # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> Selected a -> ShowS #

show :: Selected a -> String #

showList :: [Selected a] -> ShowS #

Generic (Selected a) # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep (Selected a) :: Type -> Type #

Methods

from :: Selected a -> Rep (Selected a) x #

to :: Rep (Selected a) x -> Selected a #

NFData a => NFData (Selected a) # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Selected a -> () #

HasDeps a => HasDeps (Selected a) # 
Instance details

Defined in Napkin.Types.Deps

type Rep (Selected a) # 
Instance details

Defined in Napkin.Types.Core

type Rep (Selected a) = D1 ('MetaData "Selected" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "Selected" 'PrefixI 'True) (S1 ('MetaSel ('Just "_selectRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref a)) :*: S1 ('MetaSel ('Just "_selectItem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data Alias a #

Like selected, but aliasing is optional

Constructors

Alias 

Fields

Instances

Instances details
Foldable Alias # 
Instance details

Defined in Napkin.Types.Core

Methods

fold :: Monoid m => Alias m -> m #

foldMap :: Monoid m => (a -> m) -> Alias a -> m #

foldMap' :: Monoid m => (a -> m) -> Alias a -> m #

foldr :: (a -> b -> b) -> b -> Alias a -> b #

foldr' :: (a -> b -> b) -> b -> Alias a -> b #

foldl :: (b -> a -> b) -> b -> Alias a -> b #

foldl' :: (b -> a -> b) -> b -> Alias a -> b #

foldr1 :: (a -> a -> a) -> Alias a -> a #

foldl1 :: (a -> a -> a) -> Alias a -> a #

toList :: Alias a -> [a] #

null :: Alias a -> Bool #

length :: Alias a -> Int #

elem :: Eq a => a -> Alias a -> Bool #

maximum :: Ord a => Alias a -> a #

minimum :: Ord a => Alias a -> a #

sum :: Num a => Alias a -> a #

product :: Num a => Alias a -> a #

WithName Alias # 
Instance details

Defined in Napkin.Types.Core

Methods

as :: b -> Ref b -> Alias b #

Lift a => Lift (Alias a :: Type) # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: Alias a -> Q Exp #

liftTyped :: Alias a -> Q (TExp (Alias a)) #

Eq a => Eq (Alias a) # 
Instance details

Defined in Napkin.Types.Core

Methods

(==) :: Alias a -> Alias a -> Bool #

(/=) :: Alias a -> Alias a -> Bool #

Data a => Data (Alias a) # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Alias a -> Constr #

dataTypeOf :: Alias a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Alias a) # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: Alias a -> Alias a -> Ordering #

(<) :: Alias a -> Alias a -> Bool #

(<=) :: Alias a -> Alias a -> Bool #

(>) :: Alias a -> Alias a -> Bool #

(>=) :: Alias a -> Alias a -> Bool #

max :: Alias a -> Alias a -> Alias a #

min :: Alias a -> Alias a -> Alias a #

Show a => Show (Alias a) # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> Alias a -> ShowS #

show :: Alias a -> String #

showList :: [Alias a] -> ShowS #

Generic (Alias a) # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep (Alias a) :: Type -> Type #

Methods

from :: Alias a -> Rep (Alias a) x #

to :: Rep (Alias a) x -> Alias a #

NFData a => NFData (Alias a) # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Alias a -> () #

RenderSql (Alias SExp) backend => RenderSql [Alias SExp] backend # 
Instance details

Defined in Napkin.Render.Common

Methods

renderSql :: backend -> [Alias SExp] -> Doc #

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

Defined in Napkin.Render.Sqlite

Methods

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

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

Defined in Napkin.Render.Redshift

Methods

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

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

Defined in Napkin.Render.Postgres

Methods

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

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

Defined in Napkin.Render.BigQuery

Methods

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

type Rep (Alias a) # 
Instance details

Defined in Napkin.Types.Core

type Rep (Alias a) = D1 ('MetaData "Alias" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "Alias" 'PrefixI 'True) (S1 ('MetaSel ('Just "_aliasRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Ref a))) :*: S1 ('MetaSel ('Just "_aliasItem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

nonAlias :: a -> Alias a #

class WithName a where #

Methods

as :: b -> Ref b -> a b #

e.g. var "foo" as "bar"

Instances

Instances details
WithName Alias # 
Instance details

Defined in Napkin.Types.Core

Methods

as :: b -> Ref b -> Alias b #

WithName Selected # 
Instance details

Defined in Napkin.Types.Core

Methods

as :: b -> Ref b -> Selected b #

sa :: WithName a => Ref b -> b -> a b #

Flipped as

data StructField #

Instances

Instances details
Eq StructField # 
Instance details

Defined in Napkin.Types.Core

Data StructField # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: StructField -> Constr #

dataTypeOf :: StructField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StructField # 
Instance details

Defined in Napkin.Types.Core

Read StructField # 
Instance details

Defined in Napkin.Types.Core

Show StructField # 
Instance details

Defined in Napkin.Types.Core

Generic StructField # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep StructField :: Type -> Type #

NFData StructField # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: StructField -> () #

Lift StructField # 
Instance details

Defined in Napkin.Types.Core

type Rep StructField # 
Instance details

Defined in Napkin.Types.Core

type Rep StructField = D1 ('MetaData "StructField" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "StructFieldSharp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "StructFieldNamed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Value #

Instances

Instances details
Eq Value # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Data Value # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Value # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: Value -> Value -> Ordering #

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

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

(>) :: Value -> Value -> Bool #

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

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

NFData Value # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Value -> () #

FromField Value # 
Instance details

Defined in Napkin.Run.Sqlite

Val Value # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Value #

Lift Value # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: Value -> Q Exp #

liftTyped :: Value -> Q (TExp Value) #

FromField (Named Value) # 
Instance details

Defined in Napkin.Run.PGCommon

FromRow (Map Text Value) # 
Instance details

Defined in Napkin.Run.PGCommon

type Rep Value # 
Instance details

Defined in Napkin.Types.Core

type Rep Value = D1 ('MetaData "Value" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (((C1 ('MetaCons "VDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "VInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))) :+: (C1 ('MetaCons "VBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "VDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "VDateTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime))))) :+: ((C1 ('MetaCons "VText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "VBinary" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) :+: (C1 ('MetaCons "VInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interval)) :+: (C1 ('MetaCons "VNull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VDatePart" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePart))))))

newtype Interval #

Intervals could internally make use of expressions

Constructors

Interval 

Fields

Instances

Instances details
Eq Interval # 
Instance details

Defined in Napkin.Types.Core

Data Interval # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Interval -> Constr #

dataTypeOf :: Interval -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Interval # 
Instance details

Defined in Napkin.Types.Core

Show Interval # 
Instance details

Defined in Napkin.Types.Core

Generic Interval # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Interval :: Type -> Type #

Methods

from :: Interval -> Rep Interval x #

to :: Rep Interval x -> Interval #

NFData Interval # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Interval -> () #

Lift Interval # 
Instance details

Defined in Napkin.Types.Core

type Rep Interval # 
Instance details

Defined in Napkin.Types.Core

type Rep Interval = D1 ('MetaData "Interval" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'True) (C1 ('MetaCons "Interval" 'PrefixI 'True) (S1 ('MetaSel ('Just "_unInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(SExp, DatePart)])))

data IntInterval #

A simpler sub-variant to Interval that fits certain cases better. Maps onto Interval underneath.

Constructors

IntInterval SExp DatePart 

Instances

Instances details
Eq IntInterval # 
Instance details

Defined in Napkin.Types.Core

Data IntInterval # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: IntInterval -> Constr #

dataTypeOf :: IntInterval -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IntInterval # 
Instance details

Defined in Napkin.Types.Core

Show IntInterval # 
Instance details

Defined in Napkin.Types.Core

Val IntInterval # 
Instance details

Defined in Napkin.Types.Core

data ArrayBase #

BigQuery array index can be 0-based or 1-based

Constructors

ArrayBase0 
ArrayBase1 

Instances

Instances details
Eq ArrayBase # 
Instance details

Defined in Napkin.Types.Core

Data ArrayBase # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: ArrayBase -> Constr #

dataTypeOf :: ArrayBase -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ArrayBase # 
Instance details

Defined in Napkin.Types.Core

Show ArrayBase # 
Instance details

Defined in Napkin.Types.Core

Generic ArrayBase # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep ArrayBase :: Type -> Type #

NFData ArrayBase # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: ArrayBase -> () #

Lift ArrayBase # 
Instance details

Defined in Napkin.Types.Core

type Rep ArrayBase # 
Instance details

Defined in Napkin.Types.Core

type Rep ArrayBase = D1 ('MetaData "ArrayBase" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "ArrayBase0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrayBase1" 'PrefixI 'False) (U1 :: Type -> Type))

data Nullability #

Constructors

Nullable 
NotNull 

Instances

Instances details
Eq Nullability # 
Instance details

Defined in Napkin.Types.Core

Data Nullability # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Nullability -> Constr #

dataTypeOf :: Nullability -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Nullability # 
Instance details

Defined in Napkin.Types.Core

Show Nullability # 
Instance details

Defined in Napkin.Types.Core

Generic Nullability # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Nullability :: Type -> Type #

NFData Nullability # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Nullability -> () #

Lift Nullability # 
Instance details

Defined in Napkin.Types.Core

type Rep Nullability # 
Instance details

Defined in Napkin.Types.Core

type Rep Nullability = D1 ('MetaData "Nullability" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "Nullable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotNull" 'PrefixI 'False) (U1 :: Type -> Type))

data Field #

Constructors

Field Nullability Type 

data SExp #

Instances

Instances details
Eq SExp # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Fractional SExp # 
Instance details

Defined in Napkin.Untyped.Ops

Methods

(/) :: SExp -> SExp -> SExp #

recip :: SExp -> SExp #

fromRational :: Rational -> SExp #

Data SExp # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: SExp -> Constr #

dataTypeOf :: SExp -> DataType #

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

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

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

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

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

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

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

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

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

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

Num SExp # 
Instance details

Defined in Napkin.Untyped.Ops

Methods

(+) :: SExp -> SExp -> SExp #

(-) :: SExp -> SExp -> SExp #

(*) :: SExp -> SExp -> SExp #

negate :: SExp -> SExp #

abs :: SExp -> SExp #

signum :: SExp -> SExp #

fromInteger :: Integer -> SExp #

Ord SExp # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: SExp -> SExp -> Ordering #

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

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

(>) :: SExp -> SExp -> Bool #

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

max :: SExp -> SExp -> SExp #

min :: SExp -> SExp -> SExp #

Show SExp # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> SExp -> ShowS #

show :: SExp -> String #

showList :: [SExp] -> ShowS #

Generic SExp # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep SExp :: Type -> Type #

Methods

from :: SExp -> Rep SExp x #

to :: Rep SExp x -> SExp #

NFData SExp # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: SExp -> () #

HasDeps SExp # 
Instance details

Defined in Napkin.Types.Deps

Lift SExp # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: SExp -> Q Exp #

liftTyped :: SExp -> Q (TExp SExp) #

RenderSql SExp Sqlite # 
Instance details

Defined in Napkin.Render.Sqlite

Methods

renderSql :: Sqlite -> SExp -> Doc #

RenderSql SExp Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> SExp -> Doc #

RenderSql SExp Postgres # 
Instance details

Defined in Napkin.Render.Postgres

Methods

renderSql :: Postgres -> SExp -> Doc #

RenderSql SExp BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> SExp -> Doc #

RenderSql (Alias SExp) backend => RenderSql [Alias SExp] backend # 
Instance details

Defined in Napkin.Render.Common

Methods

renderSql :: backend -> [Alias SExp] -> Doc #

HasDeps (OMap Name SExp) # 
Instance details

Defined in Napkin.Types.Deps

type Rep SExp # 
Instance details

Defined in Napkin.Types.Core

type Rep SExp = D1 ('MetaData "SExp" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (((C1 ('MetaCons "Lit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)) :+: (C1 ('MetaCons "Var" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref SExp))) :+: C1 ('MetaCons "ArraySelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Query)))) :+: (C1 ('MetaCons "ArrayItem" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sExp_ArrayItem_base") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBase) :*: S1 ('MetaSel ('Just "_sExp_ArrayItem_null") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Nullability)) :*: (S1 ('MetaSel ('Just "_sExp_ArrayItem_arr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp) :*: S1 ('MetaSel ('Just "_sExp_ArrayItem_idx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp))) :+: (C1 ('MetaCons "Array" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sExp_Array_itemType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Type)) :*: S1 ('MetaSel ('Just "_sExp_Array_items") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SExp])) :+: C1 ('MetaCons "Struct" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sExp_Struct_types") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (OMap StructField Type))) :*: S1 ('MetaSel ('Just "_sExp_Struct_values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OMap StructField SExp)))))) :+: ((C1 ('MetaCons "FieldAccess" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sExp_fieldAccess_base") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp) :*: S1 ('MetaSel ('Just "_sExp_fieldAccess_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StructField)) :+: (C1 ('MetaCons "Extern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExternFun)) :+: C1 ('MetaCons "Case" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(SExp, SExp)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp)))) :+: (C1 ('MetaCons "ExceptColumns" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ref SExp])) :+: (C1 ('MetaCons "SubQuery" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Query)) :+: C1 ('MetaCons "NativeExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NativeExpr))))))

data NativeExpr #

Instances

Instances details
Eq NativeExpr # 
Instance details

Defined in Napkin.Types.Core

Data NativeExpr # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: NativeExpr -> Constr #

dataTypeOf :: NativeExpr -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NativeExpr # 
Instance details

Defined in Napkin.Types.Core

Show NativeExpr # 
Instance details

Defined in Napkin.Types.Core

Generic NativeExpr # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep NativeExpr :: Type -> Type #

NFData NativeExpr # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: NativeExpr -> () #

Lift NativeExpr # 
Instance details

Defined in Napkin.Types.Core

ToDbBackend anyBackend => RenderSql NativeExpr anyBackend # 
Instance details

Defined in Napkin.Render.Native

Methods

renderSql :: anyBackend -> NativeExpr -> Doc #

type Rep NativeExpr # 
Instance details

Defined in Napkin.Types.Core

type Rep NativeExpr = D1 ('MetaData "NativeExpr" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "PostgresAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "SimpleSQLParserScalarExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScalarExpr)))

var :: Ref a -> SExp #

data NullStrategy #

Constructors

IgnoreNulls 
RespectNulls 

Instances

Instances details
Eq NullStrategy # 
Instance details

Defined in Napkin.Types.Core

Data NullStrategy # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: NullStrategy -> Constr #

dataTypeOf :: NullStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NullStrategy # 
Instance details

Defined in Napkin.Types.Core

Show NullStrategy # 
Instance details

Defined in Napkin.Types.Core

Generic NullStrategy # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep NullStrategy :: Type -> Type #

NFData NullStrategy # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: NullStrategy -> () #

Lift NullStrategy # 
Instance details

Defined in Napkin.Types.Core

type Rep NullStrategy # 
Instance details

Defined in Napkin.Types.Core

type Rep NullStrategy = D1 ('MetaData "NullStrategy" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "IgnoreNulls" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RespectNulls" 'PrefixI 'False) (U1 :: Type -> Type))

data Distinctness #

Constructors

Distinct 
NonDistinct 

Instances

Instances details
Eq Distinctness # 
Instance details

Defined in Napkin.Types.Core

Data Distinctness # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Distinctness -> Constr #

dataTypeOf :: Distinctness -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Distinctness # 
Instance details

Defined in Napkin.Types.Core

Show Distinctness # 
Instance details

Defined in Napkin.Types.Core

Generic Distinctness # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Distinctness :: Type -> Type #

NFData Distinctness # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Distinctness -> () #

Default Distinctness # 
Instance details

Defined in Napkin.Types.Core

Methods

def :: Distinctness #

Lift Distinctness # 
Instance details

Defined in Napkin.Types.Core

type Rep Distinctness # 
Instance details

Defined in Napkin.Types.Core

type Rep Distinctness = D1 ('MetaData "Distinctness" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "Distinct" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NonDistinct" 'PrefixI 'False) (U1 :: Type -> Type))

type Partition = [SExp] #

data WOver #

Instances

Instances details
Eq WOver # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Data WOver # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: WOver -> Constr #

dataTypeOf :: WOver -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WOver # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: WOver -> WOver -> Ordering #

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

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

(>) :: WOver -> WOver -> Bool #

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

max :: WOver -> WOver -> WOver #

min :: WOver -> WOver -> WOver #

Show WOver # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> WOver -> ShowS #

show :: WOver -> String #

showList :: [WOver] -> ShowS #

Generic WOver # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep WOver :: Type -> Type #

Methods

from :: WOver -> Rep WOver x #

to :: Rep WOver x -> WOver #

NFData WOver # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: WOver -> () #

Default WOver # 
Instance details

Defined in Napkin.Types.Core

Methods

def :: WOver #

Lift WOver # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: WOver -> Q Exp #

liftTyped :: WOver -> Q (TExp WOver) #

type Rep WOver # 
Instance details

Defined in Napkin.Types.Core

type Rep WOver = D1 ('MetaData "WOver" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "WOver" 'PrefixI 'True) (S1 ('MetaSel ('Just "_overPartition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Partition) :*: (S1 ('MetaSel ('Just "_overOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Order) :*: S1 ('MetaSel ('Just "_overFrame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WindowFrame)))))

data WindowFrameUnit #

Constructors

WindowRows 
WindowRange 

Instances

Instances details
Eq WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

Data WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: WindowFrameUnit -> Constr #

dataTypeOf :: WindowFrameUnit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

Show WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

Generic WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep WindowFrameUnit :: Type -> Type #

NFData WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: WindowFrameUnit -> () #

Lift WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

type Rep WindowFrameUnit # 
Instance details

Defined in Napkin.Types.Core

type Rep WindowFrameUnit = D1 ('MetaData "WindowFrameUnit" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "WindowRows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WindowRange" 'PrefixI 'False) (U1 :: Type -> Type))

data WindowFun #

Instances

Instances details
Eq WindowFun # 
Instance details

Defined in Napkin.Types.Core

Data WindowFun # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: WindowFun -> Constr #

dataTypeOf :: WindowFun -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WindowFun # 
Instance details

Defined in Napkin.Types.Core

Show WindowFun # 
Instance details

Defined in Napkin.Types.Core

Generic WindowFun # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep WindowFun :: Type -> Type #

NFData WindowFun # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: WindowFun -> () #

Lift WindowFun # 
Instance details

Defined in Napkin.Types.Core

type Rep WindowFun # 
Instance details

Defined in Napkin.Types.Core

data WindowFrame #

Instances

Instances details
Eq WindowFrame # 
Instance details

Defined in Napkin.Types.Core

Data WindowFrame # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: WindowFrame -> Constr #

dataTypeOf :: WindowFrame -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WindowFrame # 
Instance details

Defined in Napkin.Types.Core

Show WindowFrame # 
Instance details

Defined in Napkin.Types.Core

Generic WindowFrame # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep WindowFrame :: Type -> Type #

NFData WindowFrame # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: WindowFrame -> () #

Lift WindowFrame # 
Instance details

Defined in Napkin.Types.Core

type Rep WindowFrame # 
Instance details

Defined in Napkin.Types.Core

data FrameLength #

Instances

Instances details
Eq FrameLength # 
Instance details

Defined in Napkin.Types.Core

Data FrameLength # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: FrameLength -> Constr #

dataTypeOf :: FrameLength -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FrameLength # 
Instance details

Defined in Napkin.Types.Core

Show FrameLength # 
Instance details

Defined in Napkin.Types.Core

Generic FrameLength # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep FrameLength :: Type -> Type #

NFData FrameLength # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: FrameLength -> () #

Lift FrameLength # 
Instance details

Defined in Napkin.Types.Core

type Rep FrameLength # 
Instance details

Defined in Napkin.Types.Core

type Rep FrameLength = D1 ('MetaData "FrameLength" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) ((C1 ('MetaCons "CurrentRow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unbounded" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LimitedPreceding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp)) :+: C1 ('MetaCons "LimitedFollowing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp))))

data FunModifier #

Instances

Instances details
Eq FunModifier # 
Instance details

Defined in Napkin.Types.Core

Data FunModifier # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: FunModifier -> Constr #

dataTypeOf :: FunModifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FunModifier # 
Instance details

Defined in Napkin.Types.Core

Show FunModifier # 
Instance details

Defined in Napkin.Types.Core

Generic FunModifier # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep FunModifier :: Type -> Type #

NFData FunModifier # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: FunModifier -> () #

Lift FunModifier # 
Instance details

Defined in Napkin.Types.Core

type Rep FunModifier # 
Instance details

Defined in Napkin.Types.Core

data ExternFun #

Instances

Instances details
Eq ExternFun # 
Instance details

Defined in Napkin.Types.Core

Data ExternFun # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: ExternFun -> Constr #

dataTypeOf :: ExternFun -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExternFun # 
Instance details

Defined in Napkin.Types.Core

Show ExternFun # 
Instance details

Defined in Napkin.Types.Core

Generic ExternFun # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep ExternFun :: Type -> Type #

NFData ExternFun # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: ExternFun -> () #

Lift ExternFun # 
Instance details

Defined in Napkin.Types.Core

type Rep ExternFun # 
Instance details

Defined in Napkin.Types.Core

type Rep ExternFun = D1 ('MetaData "ExternFun" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) ((C1 ('MetaCons "SimpleExtern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref Function)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SExp])) :+: (C1 ('MetaCons "ModExtern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref Function)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SExp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunModifier]))) :+: C1 ('MetaCons "Cast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: (C1 ('MetaCons "SafeCast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: (C1 ('MetaCons "ExternWindow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WindowFun)) :+: C1 ('MetaCons "ExternRaw" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

data Type #

Instances

Instances details
Eq Type # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Data Type # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Type # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

NFData Type # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Type -> () #

Lift Type # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: Type -> Q Exp #

liftTyped :: Type -> Q (TExp Type) #

type Rep Type # 
Instance details

Defined in Napkin.Types.Core

type Rep Type = D1 ('MetaData "Type" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) ((((C1 ('MetaCons "TySmallInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyInteger" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TyBigInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TyDecimal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyReal" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TyDouble" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyBool" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TyChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TyVarChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyBlob" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "TyUnknown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginTypeName)) :+: C1 ('MetaCons "TyVarCharWithLen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "TyDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TyTimestamp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyDatetime" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TyInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TyLimited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "Ty2DLimited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "TyArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "TyStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OMap StructField Type))))))))

data DatePart #

Instances

Instances details
Eq DatePart # 
Instance details

Defined in Napkin.Types.Core

Data DatePart # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: DatePart -> Constr #

dataTypeOf :: DatePart -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DatePart # 
Instance details

Defined in Napkin.Types.Core

Show DatePart # 
Instance details

Defined in Napkin.Types.Core

Generic DatePart # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep DatePart :: Type -> Type #

Methods

from :: DatePart -> Rep DatePart x #

to :: Rep DatePart x -> DatePart #

NFData DatePart # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: DatePart -> () #

Val DatePart # 
Instance details

Defined in Napkin.Types.Core

Lift DatePart # 
Instance details

Defined in Napkin.Types.Core

type Rep DatePart # 
Instance details

Defined in Napkin.Types.Core

type Rep DatePart = D1 ('MetaData "DatePart" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) ((((C1 ('MetaCons "Millennium" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Century" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Decade" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Epoch" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Year" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Quarter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Month" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Week" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "DayOfWeek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DayOfYear" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Day" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Hour" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Minute" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Second" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Millisecond" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Microsecond" 'PrefixI 'False) (U1 :: Type -> Type)))))

type Order = [OrderPart] #

type GroupBy = [SExp] #

data OrderDir #

Constructors

Asc 
Desc 

Instances

Instances details
Eq OrderDir # 
Instance details

Defined in Napkin.Types.Core

Data OrderDir # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: OrderDir -> Constr #

dataTypeOf :: OrderDir -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrderDir # 
Instance details

Defined in Napkin.Types.Core

Show OrderDir # 
Instance details

Defined in Napkin.Types.Core

Generic OrderDir # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep OrderDir :: Type -> Type #

Methods

from :: OrderDir -> Rep OrderDir x #

to :: Rep OrderDir x -> OrderDir #

NFData OrderDir # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: OrderDir -> () #

Lift OrderDir # 
Instance details

Defined in Napkin.Types.Core

type Rep OrderDir # 
Instance details

Defined in Napkin.Types.Core

type Rep OrderDir = D1 ('MetaData "OrderDir" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "Asc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Desc" 'PrefixI 'False) (U1 :: Type -> Type))

invertOrder :: OrderDir -> OrderDir #

Flip order

data NullOrder #

Constructors

NullsFirst 
NullsLast 

Instances

Instances details
Eq NullOrder # 
Instance details

Defined in Napkin.Types.Core

Data NullOrder # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: NullOrder -> Constr #

dataTypeOf :: NullOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NullOrder # 
Instance details

Defined in Napkin.Types.Core

Show NullOrder # 
Instance details

Defined in Napkin.Types.Core

Generic NullOrder # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep NullOrder :: Type -> Type #

NFData NullOrder # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: NullOrder -> () #

Lift NullOrder # 
Instance details

Defined in Napkin.Types.Core

type Rep NullOrder # 
Instance details

Defined in Napkin.Types.Core

type Rep NullOrder = D1 ('MetaData "NullOrder" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "NullsFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NullsLast" 'PrefixI 'False) (U1 :: Type -> Type))

data OrderPart #

Constructors

OrderPart 

Instances

Instances details
Eq OrderPart # 
Instance details

Defined in Napkin.Types.Core

Data OrderPart # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: OrderPart -> Constr #

dataTypeOf :: OrderPart -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrderPart # 
Instance details

Defined in Napkin.Types.Core

Show OrderPart # 
Instance details

Defined in Napkin.Types.Core

Generic OrderPart # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep OrderPart :: Type -> Type #

NFData OrderPart # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: OrderPart -> () #

Lift OrderPart # 
Instance details

Defined in Napkin.Types.Core

type Rep OrderPart # 
Instance details

Defined in Napkin.Types.Core

type Rep OrderPart = D1 ('MetaData "OrderPart" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "OrderPart" 'PrefixI 'True) (S1 ('MetaSel ('Just "_opExp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExp) :*: (S1 ('MetaSel ('Just "_opOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OrderDir) :*: S1 ('MetaSel ('Just "_opNulls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NullOrder)))))

data Relation #

Constructors

TableRelation (Ref Table) 
QueryRelation Query 
ArrayRelation SExp 
RawRelation [Ref Table] String

Escape hatch: A raw relation with its dependencies. Avoid if possible

Instances

Instances details
Eq Relation # 
Instance details

Defined in Napkin.Types.Core

Data Relation # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Relation -> Constr #

dataTypeOf :: Relation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Relation # 
Instance details

Defined in Napkin.Types.Core

Show Relation # 
Instance details

Defined in Napkin.Types.Core

IsString Relation # 
Instance details

Defined in Napkin.Types.Core

Generic Relation # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Relation :: Type -> Type #

Methods

from :: Relation -> Rep Relation x #

to :: Rep Relation x -> Relation #

NFData Relation # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Relation -> () #

MaybeQuery Relation # 
Instance details

Defined in Napkin.Types.Core

AsRelation Relation # 
Instance details

Defined in Napkin.Types.Core

HasDeps Relation # 
Instance details

Defined in Napkin.Types.Deps

Lift Relation # 
Instance details

Defined in Napkin.Types.Core

RenderSql Relation Sqlite # 
Instance details

Defined in Napkin.Render.Sqlite

Methods

renderSql :: Sqlite -> Relation -> Doc #

RenderSql Relation Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Relation -> Doc #

RenderSql Relation Postgres # 
Instance details

Defined in Napkin.Render.Postgres

Methods

renderSql :: Postgres -> Relation -> Doc #

RenderSql Relation BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Relation -> Doc #

type Rep Relation # 
Instance details

Defined in Napkin.Types.Core

table :: Ref a -> Relation #

treat a reference as relation

data JoinType #

Instances

Instances details
Eq JoinType # 
Instance details

Defined in Napkin.Types.Core

Data JoinType # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: JoinType -> Constr #

dataTypeOf :: JoinType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JoinType # 
Instance details

Defined in Napkin.Types.Core

Show JoinType # 
Instance details

Defined in Napkin.Types.Core

Generic JoinType # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep JoinType :: Type -> Type #

Methods

from :: JoinType -> Rep JoinType x #

to :: Rep JoinType x -> JoinType #

NFData JoinType # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: JoinType -> () #

Lift JoinType # 
Instance details

Defined in Napkin.Types.Core

type Rep JoinType # 
Instance details

Defined in Napkin.Types.Core

type Rep JoinType = D1 ('MetaData "JoinType" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) ((C1 ('MetaCons "JoinLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoinRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "JoinInner" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "JoinCross" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoinOuter" 'PrefixI 'False) (U1 :: Type -> Type))))

data From #

Instances

Instances details
Eq From # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Data From # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: From -> Constr #

dataTypeOf :: From -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord From # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: From -> From -> Ordering #

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

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

(>) :: From -> From -> Bool #

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

max :: From -> From -> From #

min :: From -> From -> From #

Show From # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> From -> ShowS #

show :: From -> String #

showList :: [From] -> ShowS #

Generic From # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep From :: Type -> Type #

Methods

from :: From -> Rep From x #

to :: Rep From x -> From #

NFData From # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: From -> () #

HasDeps From # 
Instance details

Defined in Napkin.Types.Deps

Lift From # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: From -> Q Exp #

liftTyped :: From -> Q (TExp From) #

RenderSql From Sqlite # 
Instance details

Defined in Napkin.Render.Sqlite

Methods

renderSql :: Sqlite -> From -> Doc #

RenderSql From Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> From -> Doc #

RenderSql From Postgres # 
Instance details

Defined in Napkin.Render.Postgres

Methods

renderSql :: Postgres -> From -> Doc #

RenderSql From BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> From -> Doc #

type Rep From # 
Instance details

Defined in Napkin.Types.Core

data UnionType #

Instances

Instances details
Eq UnionType # 
Instance details

Defined in Napkin.Types.Core

Data UnionType # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: UnionType -> Constr #

dataTypeOf :: UnionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UnionType # 
Instance details

Defined in Napkin.Types.Core

Show UnionType # 
Instance details

Defined in Napkin.Types.Core

Generic UnionType # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep UnionType :: Type -> Type #

NFData UnionType # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: UnionType -> () #

Lift UnionType # 
Instance details

Defined in Napkin.Types.Core

type Rep UnionType # 
Instance details

Defined in Napkin.Types.Core

type Rep UnionType = D1 ('MetaData "UnionType" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) ((C1 ('MetaCons "SetUnion" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateUnion" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IntersectUnion" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MinusUnion" 'PrefixI 'False) (U1 :: Type -> Type)))

data RawQuery #

Constructors

RawQuery 

Instances

Instances details
Eq RawQuery # 
Instance details

Defined in Napkin.Types.Core

Data RawQuery # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: RawQuery -> Constr #

dataTypeOf :: RawQuery -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RawQuery # 
Instance details

Defined in Napkin.Types.Core

Show RawQuery # 
Instance details

Defined in Napkin.Types.Core

Generic RawQuery # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep RawQuery :: Type -> Type #

Methods

from :: RawQuery -> Rep RawQuery x #

to :: Rep RawQuery x -> RawQuery #

NFData RawQuery # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: RawQuery -> () #

Lift RawQuery # 
Instance details

Defined in Napkin.Types.Core

type Rep RawQuery # 
Instance details

Defined in Napkin.Types.Core

type Rep RawQuery = D1 ('MetaData "RawQuery" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "RawQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "_rawQuery_deps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ref Table]) :*: S1 ('MetaSel ('Just "_rawQuery_raw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data CteBody #

Instances

Instances details
Eq CteBody # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Data CteBody # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: CteBody -> Constr #

dataTypeOf :: CteBody -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CteBody # 
Instance details

Defined in Napkin.Types.Core

Show CteBody # 
Instance details

Defined in Napkin.Types.Core

Generic CteBody # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep CteBody :: Type -> Type #

Methods

from :: CteBody -> Rep CteBody x #

to :: Rep CteBody x -> CteBody #

NFData CteBody # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: CteBody -> () #

Lift CteBody # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: CteBody -> Q Exp #

liftTyped :: CteBody -> Q (TExp CteBody) #

type Rep CteBody # 
Instance details

Defined in Napkin.Types.Core

data AsStruct #

Constructors

AsStruct 
AsStructNo 
AsValue 

Instances

Instances details
Eq AsStruct # 
Instance details

Defined in Napkin.Types.Core

Data AsStruct # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: AsStruct -> Constr #

dataTypeOf :: AsStruct -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AsStruct # 
Instance details

Defined in Napkin.Types.Core

Read AsStruct # 
Instance details

Defined in Napkin.Types.Core

Show AsStruct # 
Instance details

Defined in Napkin.Types.Core

Generic AsStruct # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep AsStruct :: Type -> Type #

Methods

from :: AsStruct -> Rep AsStruct x #

to :: Rep AsStruct x -> AsStruct #

NFData AsStruct # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: AsStruct -> () #

Lift AsStruct # 
Instance details

Defined in Napkin.Types.Core

type Rep AsStruct # 
Instance details

Defined in Napkin.Types.Core

type Rep AsStruct = D1 ('MetaData "AsStruct" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "AsStruct" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AsStructNo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AsValue" 'PrefixI 'False) (U1 :: Type -> Type)))

data Query #

Constructors

Query 
Union 

Fields

QueryRaw RawQuery

Escape hatch: A raw query with all the dependencies contained therein. Avoid if possible.

NativeQuery NativeQuery 

Instances

Instances details
Eq Query # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

Data Query # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: Query -> Constr #

dataTypeOf :: Query -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Query # 
Instance details

Defined in Napkin.Types.Core

Methods

compare :: Query -> Query -> Ordering #

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

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

(>) :: Query -> Query -> Bool #

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

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

Show Query # 
Instance details

Defined in Napkin.Types.Core

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep Query :: Type -> Type #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

NFData Query # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: Query -> () #

MaybeQuery Query # 
Instance details

Defined in Napkin.Types.Core

Methods

getQuery :: Query -> Maybe Query #

HasDefinition Query # 
Instance details

Defined in Napkin.Types.Core

AsRelation Query # 
Instance details

Defined in Napkin.Types.Core

Methods

asRelation :: Query -> Relation #

HasDeps Query # 
Instance details

Defined in Napkin.Types.Deps

Lift Query # 
Instance details

Defined in Napkin.Types.Core

Methods

lift :: Query -> Q Exp #

liftTyped :: Query -> Q (TExp Query) #

RenderSql Query Sqlite # 
Instance details

Defined in Napkin.Render.Sqlite

Methods

renderSql :: Sqlite -> Query -> Doc #

RenderSql Query Redshift # 
Instance details

Defined in Napkin.Render.Redshift

Methods

renderSql :: Redshift -> Query -> Doc #

RenderSql Query Postgres # 
Instance details

Defined in Napkin.Render.Postgres

Methods

renderSql :: Postgres -> Query -> Doc #

RenderSql Query BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Query -> Doc #

type Rep Query # 
Instance details

Defined in Napkin.Types.Core

type Rep Query = D1 ('MetaData "Query" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) ((C1 ('MetaCons "Query" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_queryWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WithClauses) :*: S1 ('MetaSel ('Just "_querySelect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Alias SExp])) :*: (S1 ('MetaSel ('Just "_queryFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe From)) :*: (S1 ('MetaSel ('Just "_queryWhere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SExp)) :*: S1 ('MetaSel ('Just "_queryHaving") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SExp))))) :*: ((S1 ('MetaSel ('Just "_queryGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GroupBy) :*: (S1 ('MetaSel ('Just "_queryOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Order) :*: S1 ('MetaSel ('Just "_queryLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: (S1 ('MetaSel ('Just "_queryOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "_queryDistinct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Distinctness) :*: S1 ('MetaSel ('Just "_queryAs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AsStruct))))) :+: C1 ('MetaCons "Union" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_unionType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnionType) :*: S1 ('MetaSel ('Just "_unionQuery1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Query)) :*: (S1 ('MetaSel ('Just "_unionQuery2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Query) :*: S1 ('MetaSel ('Just "_unionWiths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WithClauses)))) :+: (C1 ('MetaCons "QueryRaw" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RawQuery)) :+: C1 ('MetaCons "NativeQuery" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NativeQuery))))

data NativeQuery #

Instances

Instances details
Eq NativeQuery # 
Instance details

Defined in Napkin.Types.Core

Data NativeQuery # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: NativeQuery -> Constr #

dataTypeOf :: NativeQuery -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NativeQuery # 
Instance details

Defined in Napkin.Types.Core

Show NativeQuery # 
Instance details

Defined in Napkin.Types.Core

Generic NativeQuery # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep NativeQuery :: Type -> Type #

NFData NativeQuery # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: NativeQuery -> () #

Lift NativeQuery # 
Instance details

Defined in Napkin.Types.Core

ToDbBackend anyBackend => RenderSql NativeQuery anyBackend # 
Instance details

Defined in Napkin.Render.Native

Methods

renderSql :: anyBackend -> NativeQuery -> Doc #

type Rep NativeQuery # 
Instance details

Defined in Napkin.Types.Core

type Rep NativeQuery = D1 ('MetaData "NativeQuery" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "PostgresSelectStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectStmt)) :+: C1 ('MetaCons "SimpleSQLParserQueryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QueryExpr)))

mkUnion :: UnionType -> [Query] -> Query #

Convenience: Combine list of queries via union of the same type

collectUnionQueries :: Query -> NonEmpty Query #

Pull apart any UNIONs and extract a flat list of non-union queries.

data DefinedRelation #

OO-style wrapper for objects that contain a full query definition

Constructors

forall s.(AsRelation s, HasDefinition s) => DefinedRelation s 

Instances

Instances details
AsRelation DefinedRelation # 
Instance details

Defined in Napkin.Types.Core

data DefinedQuery #

Like DefinedRelation, but only requires a defined query.

Constructors

forall s.HasDefinition s => DefinedQuery s 

class AsRelation s where #

Methods

asRelation :: s -> Relation #

Instances

Instances details
AsRelation DefinedRelation # 
Instance details

Defined in Napkin.Types.Core

AsRelation Query # 
Instance details

Defined in Napkin.Types.Core

Methods

asRelation :: Query -> Relation #

AsRelation Relation # 
Instance details

Defined in Napkin.Types.Core

AsRelation (Q a) # 
Instance details

Defined in Napkin.Untyped.Monad

Methods

asRelation :: Q a -> Relation #

AsRelation (CreateViewAs meta) # 
Instance details

Defined in Napkin.Types.Commands

Methods

asRelation :: CreateViewAs meta -> Relation #

AsRelation (CreateTableAs m) # 
Instance details

Defined in Napkin.Types.Commands

AsRelation (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

AsRelation (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types.CreateTableAs

AsRelation (Ref a) # 
Instance details

Defined in Napkin.Types.Core

Methods

asRelation :: Ref a -> Relation #

class HasDefinition s where #

Methods

defQuery :: Lens s s Query Query #

Instances

Instances details
HasDefinition Query # 
Instance details

Defined in Napkin.Types.Core

HasDefinition (Q ()) # 
Instance details

Defined in Napkin.Untyped.Monad

Methods

defQuery :: Lens (Q ()) (Q ()) Query Query #

HasDefinition (CreateTableAs m) # 
Instance details

Defined in Napkin.Types.Commands

HasDefinition (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types.CreateTableAs

class MaybeQuery s where #

Things that may or may not contain an explicit Query inside

Methods

getQuery :: s -> Maybe Query #

Instances

Instances details
MaybeQuery Query # 
Instance details

Defined in Napkin.Types.Core

Methods

getQuery :: Query -> Maybe Query #

MaybeQuery Relation # 
Instance details

Defined in Napkin.Types.Core

MaybeQuery (Q ()) # 
Instance details

Defined in Napkin.Untyped.Monad

Methods

getQuery :: Q () -> Maybe Query #

MaybeQuery (CreateTableAs m) # 
Instance details

Defined in Napkin.Types.Commands

MaybeQuery (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types.CreateTableAs

queryFullySpecified :: Data a => a -> Bool #

Has select * been used anywhere inside this thing? If so, False.

unRef :: forall a a. Iso (Ref a) (Ref a) (NonEmpty Name) (NonEmpty Name) #

selectRef :: forall a. Lens' (Selected a) (Ref a) #

selectItem :: forall a. Lens' (Selected a) a #

aliasRef :: forall a. Lens' (Alias a) (Maybe (Ref a)) #

aliasItem :: forall a. Lens' (Alias a) a #

class Val a where #

Methods

val :: Prism' Value a #

Instances

Instances details
Val Bool # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Bool #

Val Double #

Auto-convert from VInt and VText

Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Double #

Val Int # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Int #

Val Int64 #

Auto-convert from VText

Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Int64 #

Val Integer # 
Instance details

Defined in Napkin.Types.Core

Val ByteString # 
Instance details

Defined in Napkin.Types.Core

Val String # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value String #

Val Text # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Text #

Val UTCTime # 
Instance details

Defined in Napkin.Types.Core

Val Day # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Day #

Val DatePart # 
Instance details

Defined in Napkin.Types.Core

Val IntInterval # 
Instance details

Defined in Napkin.Types.Core

Val Value # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value Value #

Val a => Val (Maybe a) # 
Instance details

Defined in Napkin.Types.Core

Methods

val :: Prism' Value (Maybe a) #

integral :: (Integral a, Integral b) => Iso' a b #

_lit :: Val a => Prism' SExp a #

lit :: Val a => a -> SExp #

interval :: [(Double, DatePart)] -> SExp #

Shorthand for using literal Doubles in making interval expressions.

txt :: String -> SExp #

Monomorphic converter to make it easy to type string literals under OverloadedStrings

fullWindow :: WOver #

Convenient starting point for full window (unbounded) for cases where not specifying window defaults to a partial window. (E.g. BigQuery)

class TableRef a where #

Methods

tableRef :: Lens' a (Ref Table) #

Instances

Instances details
TableRef DeleteFrom # 
Instance details

Defined in Napkin.Types.Commands

TableRef InsertIntoQuery # 
Instance details

Defined in Napkin.Types.Commands

TableRef DropView # 
Instance details

Defined in Napkin.Types.Commands

TableRef (CreateViewAs meta) # 
Instance details

Defined in Napkin.Types.Commands

Methods

tableRef :: Lens' (CreateViewAs meta) (Ref Table) #

TableRef (CreateTableAs m) # 
Instance details

Defined in Napkin.Types.Commands

TableRef (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

tableRef :: Lens' (TableSpec b) (Ref Table) #

TableRef (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types.CreateTableAs

TableRef (Ref Table) # 
Instance details

Defined in Napkin.Types.Core

Methods

tableRef :: Lens' (Ref Table) (Ref Table) #

varAs :: Ref a -> Selected SExp #

Polymorphic to support refs that come out of Relations, etc.

asSelf :: SExp -> Selected SExp #

"Note that this is a partial function and will work only for SExps that are Var's. Please prefer varAs or as when possible

funAs :: (SExp -> b) -> Ref b -> Selected b #

Apply function to a Ref and select it by the same name as the ref. Common use case in SELECT queries.

selectToRef :: Selected SExp -> SExp #

Use the name of a Selected as a reference. Typically when you've computed a field in a subquery or a previous table, and you're now using that computation directly via its name.

refName :: Traversal (Ref a) (Ref a1) String String #

Pull the last name out of a Ref. E.g. if Ref contains a schema.table_name, pull just the table_name out.

refRoot :: Lens' (Ref a) Name #

Get final segments on the ref path and grab the name

refJustRoot :: Ref a -> Ref a #

ne :: Iso' [a] (NonEmpty a) #

atAlias :: (Applicative f, Choice p) => Ref t -> Optic' p f (Alias t) (Alias t) #

scopeRefs :: Data b => Ref t -> b -> b #

Attach all column references within expression to given (table) reference.

modifyExterns :: Data b => (ExternFun -> SExp) -> b -> b #

(^^.) :: Ref Relation -> Name -> SExp infixl 9 #

Attach given name on the relation

data AggLevel #

Constructors

Unit

Expression is at the row level

Agg

Aggregate functions, like sum

Analytic

Analytic level (some backends)

Instances

Instances details
Eq AggLevel # 
Instance details

Defined in Napkin.Types.Core

Data AggLevel # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: AggLevel -> Constr #

dataTypeOf :: AggLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AggLevel # 
Instance details

Defined in Napkin.Types.Core

Show AggLevel # 
Instance details

Defined in Napkin.Types.Core

data UpdateQuery #

Instances

Instances details
Eq UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

Data UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

Methods

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

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

toConstr :: UpdateQuery -> Constr #

dataTypeOf :: UpdateQuery -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

Show UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

Generic UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

Associated Types

type Rep UpdateQuery :: Type -> Type #

NFData UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

Methods

rnf :: UpdateQuery -> () #

HasDeps UpdateQuery # 
Instance details

Defined in Napkin.Types.Deps

Lift UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

(RenderSql SExp b, RenderSql Name b, RenderSql From b, RenderSql (Alias (Ref Table)) b) => RenderSql UpdateQuery b # 
Instance details

Defined in Napkin.Render.Common

Methods

renderSql :: b -> UpdateQuery -> Doc #

Command UpdateQuery () Sqlite # 
Instance details

Defined in Napkin.Run.Sqlite

Command UpdateQuery () Redshift # 
Instance details

Defined in Napkin.Run.Redshift

Command UpdateQuery () Postgres # 
Instance details

Defined in Napkin.Run.Postgres

Command UpdateQuery () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

type Rep UpdateQuery # 
Instance details

Defined in Napkin.Types.Core

type Rep UpdateQuery = D1 ('MetaData "UpdateQuery" "Napkin.Types.Core" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "UpdateQuery" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_updateQueryTarget") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Alias (Ref Table))) :*: S1 ('MetaSel ('Just "_updateQuerySet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OMap Name SExp))) :*: (S1 ('MetaSel ('Just "_updateQueryFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe From)) :*: S1 ('MetaSel ('Just "_updateQueryWhere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SExp)))))