queryparser-hive-0.1.0.1: Parsing for Hive SQL queries

Safe HaskellNone
LanguageHaskell2010

Database.Sql.Hive.Type

Documentation

data Hive Source #

Instances

Data Hive Source # 

Methods

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

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

toConstr :: Hive -> Constr #

dataTypeOf :: Hive -> DataType #

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

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

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

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

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

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

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

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

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

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

Dialect Hive Source # 
type DialectColumnDefinitionExtra Hive Source # 
type DialectCreateTableExtra Hive r Source # 

data HiveStatement r a Source #

Instances

ConstrainSASNames Functor r => Functor (HiveStatement r) Source # 

Methods

fmap :: (a -> b) -> HiveStatement r a -> HiveStatement r b #

(<$) :: a -> HiveStatement r b -> HiveStatement r a #

ConstrainSASNames Foldable r => Foldable (HiveStatement r) Source # 

Methods

fold :: Monoid m => HiveStatement r m -> m #

foldMap :: Monoid m => (a -> m) -> HiveStatement r a -> m #

foldr :: (a -> b -> b) -> b -> HiveStatement r a -> b #

foldr' :: (a -> b -> b) -> b -> HiveStatement r a -> b #

foldl :: (b -> a -> b) -> b -> HiveStatement r a -> b #

foldl' :: (b -> a -> b) -> b -> HiveStatement r a -> b #

foldr1 :: (a -> a -> a) -> HiveStatement r a -> a #

foldl1 :: (a -> a -> a) -> HiveStatement r a -> a #

toList :: HiveStatement r a -> [a] #

null :: HiveStatement r a -> Bool #

length :: HiveStatement r a -> Int #

elem :: Eq a => a -> HiveStatement r a -> Bool #

maximum :: Ord a => HiveStatement r a -> a #

minimum :: Ord a => HiveStatement r a -> a #

sum :: Num a => HiveStatement r a -> a #

product :: Num a => HiveStatement r a -> a #

ConstrainSASNames Traversable r => Traversable (HiveStatement r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> HiveStatement r a -> f (HiveStatement r b) #

sequenceA :: Applicative f => HiveStatement r (f a) -> f (HiveStatement r a) #

mapM :: Monad m => (a -> m b) -> HiveStatement r a -> m (HiveStatement r b) #

sequence :: Monad m => HiveStatement r (m a) -> m (HiveStatement r a) #

ConstrainSNames Eq r a => Eq (HiveStatement r a) Source # 

Methods

(==) :: HiveStatement r a -> HiveStatement r a -> Bool #

(/=) :: HiveStatement r a -> HiveStatement r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (HiveStatement r a) Source # 

Methods

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

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

toConstr :: HiveStatement r a -> Constr #

dataTypeOf :: HiveStatement r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (HiveStatement r a) Source # 
Generic (HiveStatement r a) Source # 

Associated Types

type Rep (HiveStatement r a) :: * -> * #

Methods

from :: HiveStatement r a -> Rep (HiveStatement r a) x #

to :: Rep (HiveStatement r a) x -> HiveStatement r a #

(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (HiveStatement r a) Source # 
HasColumnLineage (HiveStatement ResolvedNames Range) Source # 
HasColumns (HiveStatement ResolvedNames a) Source # 

Methods

goColumns :: HiveStatement ResolvedNames a -> Observer #

HasJoins (HiveStatement ResolvedNames a) Source # 
HasTableLineage (HiveStatement ResolvedNames a) Source # 
HasSchemaChange (HiveStatement ResolvedNames a) Source # 
HasTables (HiveStatement ResolvedNames a) Source # 
type Rep (HiveStatement r a) Source # 
type Rep (HiveStatement r a) = D1 * (MetaData "HiveStatement" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "HiveStandardSqlStatement" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Statement Hive r a)))) (C1 * (MetaCons "HiveUseStmt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Use a))))) ((:+:) * (C1 * (MetaCons "HiveAnalyzeStmt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Analyze r a)))) (C1 * (MetaCons "HiveInsertDirectoryStmt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (InsertDirectory r a)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "HiveTruncatePartitionStmt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TruncatePartition r a)))) (C1 * (MetaCons "HiveAlterTableSetLocationStmt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (AlterTableSetLocation r a))))) ((:+:) * (C1 * (MetaCons "HiveAlterPartitionSetLocationStmt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (AlterPartitionSetLocation r a)))) ((:+:) * (C1 * (MetaCons "HiveSetPropertyStmt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SetProperty a)))) (C1 * (MetaCons "HiveUnhandledStatement" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))))))

data SetProperty a Source #

Instances

Functor SetProperty Source # 

Methods

fmap :: (a -> b) -> SetProperty a -> SetProperty b #

(<$) :: a -> SetProperty b -> SetProperty a #

Foldable SetProperty Source # 

Methods

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

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

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

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

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

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

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

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

toList :: SetProperty a -> [a] #

null :: SetProperty a -> Bool #

length :: SetProperty a -> Int #

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

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

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

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

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

Traversable SetProperty Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SetProperty a -> f (SetProperty b) #

sequenceA :: Applicative f => SetProperty (f a) -> f (SetProperty a) #

mapM :: Monad m => (a -> m b) -> SetProperty a -> m (SetProperty b) #

sequence :: Monad m => SetProperty (m a) -> m (SetProperty a) #

Eq a => Eq (SetProperty a) Source # 
Data a => Data (SetProperty a) Source # 

Methods

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

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

toConstr :: SetProperty a -> Constr #

dataTypeOf :: SetProperty a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (SetProperty a) Source # 
Generic (SetProperty a) Source # 

Associated Types

type Rep (SetProperty a) :: * -> * #

Methods

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

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

ToJSON a => ToJSON (SetProperty a) Source # 
type Rep (SetProperty a) Source # 

data SetPropertyDetails a Source #

Instances

Functor SetPropertyDetails Source # 
Foldable SetPropertyDetails Source # 

Methods

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

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

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

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

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

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

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

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

toList :: SetPropertyDetails a -> [a] #

null :: SetPropertyDetails a -> Bool #

length :: SetPropertyDetails a -> Int #

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

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

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

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

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

Traversable SetPropertyDetails Source # 
Eq a => Eq (SetPropertyDetails a) Source # 
Data a => Data (SetPropertyDetails a) Source # 

Methods

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

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

toConstr :: SetPropertyDetails a -> Constr #

dataTypeOf :: SetPropertyDetails a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (SetPropertyDetails a) Source # 
Generic (SetPropertyDetails a) Source # 

Associated Types

type Rep (SetPropertyDetails a) :: * -> * #

ToJSON a => ToJSON (SetPropertyDetails a) Source # 
type Rep (SetPropertyDetails a) Source # 
type Rep (SetPropertyDetails a) = D1 * (MetaData "SetPropertyDetails" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "SetPropertyDetails" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "setPropertyDetailsInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Just Symbol "setPropertyDetailsName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "setPropertyDetailsValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))

data HiveCreateTableExtra r a Source #

Instances

ConstrainSASNames Functor r => Functor (HiveCreateTableExtra r) Source # 
ConstrainSASNames Foldable r => Foldable (HiveCreateTableExtra r) Source # 

Methods

fold :: Monoid m => HiveCreateTableExtra r m -> m #

foldMap :: Monoid m => (a -> m) -> HiveCreateTableExtra r a -> m #

foldr :: (a -> b -> b) -> b -> HiveCreateTableExtra r a -> b #

foldr' :: (a -> b -> b) -> b -> HiveCreateTableExtra r a -> b #

foldl :: (b -> a -> b) -> b -> HiveCreateTableExtra r a -> b #

foldl' :: (b -> a -> b) -> b -> HiveCreateTableExtra r a -> b #

foldr1 :: (a -> a -> a) -> HiveCreateTableExtra r a -> a #

foldl1 :: (a -> a -> a) -> HiveCreateTableExtra r a -> a #

toList :: HiveCreateTableExtra r a -> [a] #

null :: HiveCreateTableExtra r a -> Bool #

length :: HiveCreateTableExtra r a -> Int #

elem :: Eq a => a -> HiveCreateTableExtra r a -> Bool #

maximum :: Ord a => HiveCreateTableExtra r a -> a #

minimum :: Ord a => HiveCreateTableExtra r a -> a #

sum :: Num a => HiveCreateTableExtra r a -> a #

product :: Num a => HiveCreateTableExtra r a -> a #

ConstrainSASNames Traversable r => Traversable (HiveCreateTableExtra r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> HiveCreateTableExtra r a -> f (HiveCreateTableExtra r b) #

sequenceA :: Applicative f => HiveCreateTableExtra r (f a) -> f (HiveCreateTableExtra r a) #

mapM :: Monad m => (a -> m b) -> HiveCreateTableExtra r a -> m (HiveCreateTableExtra r b) #

sequence :: Monad m => HiveCreateTableExtra r (m a) -> m (HiveCreateTableExtra r a) #

ConstrainSNames Eq r a => Eq (HiveCreateTableExtra r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (HiveCreateTableExtra r a) Source # 

Methods

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

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

toConstr :: HiveCreateTableExtra r a -> Constr #

dataTypeOf :: HiveCreateTableExtra r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (HiveCreateTableExtra r a) Source # 
Generic (HiveCreateTableExtra r a) Source # 

Associated Types

type Rep (HiveCreateTableExtra r a) :: * -> * #

(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (HiveCreateTableExtra r a) Source # 
type Rep (HiveCreateTableExtra r a) Source # 
type Rep (HiveCreateTableExtra r a) = D1 * (MetaData "HiveCreateTableExtra" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "HiveCreateTableExtra" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "hiveCreateTableExtraInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "hiveCreateTableExtraTableProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (HiveMetadataProperties a))))))

data HiveMetadataProperties a Source #

Instances

Functor HiveMetadataProperties Source # 
Foldable HiveMetadataProperties Source # 

Methods

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

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

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

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

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

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

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

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

toList :: HiveMetadataProperties a -> [a] #

null :: HiveMetadataProperties a -> Bool #

length :: HiveMetadataProperties a -> Int #

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

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

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

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

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

Traversable HiveMetadataProperties Source # 
Eq a => Eq (HiveMetadataProperties a) Source # 
Data a => Data (HiveMetadataProperties a) Source # 

Methods

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

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

toConstr :: HiveMetadataProperties a -> Constr #

dataTypeOf :: HiveMetadataProperties a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (HiveMetadataProperties a) Source # 
Generic (HiveMetadataProperties a) Source # 
ToJSON a => ToJSON (HiveMetadataProperties a) Source # 
type Rep (HiveMetadataProperties a) Source # 
type Rep (HiveMetadataProperties a) = D1 * (MetaData "HiveMetadataProperties" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "HiveMetadataProperties" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "hiveMetadataPropertiesInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "hiveMetadataPropertiesProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [HiveMetadataProperty a]))))

data HiveMetadataProperty a Source #

Instances

Functor HiveMetadataProperty Source # 
Foldable HiveMetadataProperty Source # 

Methods

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

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

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

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

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

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

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

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

toList :: HiveMetadataProperty a -> [a] #

null :: HiveMetadataProperty a -> Bool #

length :: HiveMetadataProperty a -> Int #

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

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

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

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

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

Traversable HiveMetadataProperty Source # 
Eq a => Eq (HiveMetadataProperty a) Source # 
Data a => Data (HiveMetadataProperty a) Source # 

Methods

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

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

toConstr :: HiveMetadataProperty a -> Constr #

dataTypeOf :: HiveMetadataProperty a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (HiveMetadataProperty a) Source # 
Generic (HiveMetadataProperty a) Source # 
ToJSON a => ToJSON (HiveMetadataProperty a) Source # 
type Rep (HiveMetadataProperty a) Source # 
type Rep (HiveMetadataProperty a) = D1 * (MetaData "HiveMetadataProperty" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "HiveMetadataProperty" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "hiveMetadataPropertyInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Just Symbol "hiveMetadataPropertyKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)) (S1 * (MetaSel (Just Symbol "hiveMetadataPropertyValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))))

data Use a Source #

Constructors

UseDatabase (UQSchemaName a) 
UseDefault a 

Instances

Functor Use Source # 

Methods

fmap :: (a -> b) -> Use a -> Use b #

(<$) :: a -> Use b -> Use a #

Foldable Use Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Use a -> [a] #

null :: Use a -> Bool #

length :: Use a -> Int #

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

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

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

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

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

Traversable Use Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Use a -> f (Use b) #

sequenceA :: Applicative f => Use (f a) -> f (Use a) #

mapM :: Monad m => (a -> m b) -> Use a -> m (Use b) #

sequence :: Monad m => Use (m a) -> m (Use a) #

Eq a => Eq (Use a) Source # 

Methods

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

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

Data a => Data (Use a) Source # 

Methods

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

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

toConstr :: Use a -> Constr #

dataTypeOf :: Use a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (Use a) Source # 

Methods

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

show :: Use a -> String #

showList :: [Use a] -> ShowS #

Generic (Use a) Source # 

Associated Types

type Rep (Use a) :: * -> * #

Methods

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

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

ToJSON a => ToJSON (Use a) Source # 

Methods

toJSON :: Use a -> Value #

toEncoding :: Use a -> Encoding #

toJSONList :: [Use a] -> Value #

toEncodingList :: [Use a] -> Encoding #

type Rep (Use a) Source # 
type Rep (Use a) = D1 * (MetaData "Use" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) ((:+:) * (C1 * (MetaCons "UseDatabase" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (UQSchemaName a)))) (C1 * (MetaCons "UseDefault" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

data Analyze r a Source #

Constructors

Analyze 

Fields

Instances

ConstrainSASNames Functor r => Functor (Analyze r) Source # 

Methods

fmap :: (a -> b) -> Analyze r a -> Analyze r b #

(<$) :: a -> Analyze r b -> Analyze r a #

ConstrainSASNames Foldable r => Foldable (Analyze r) Source # 

Methods

fold :: Monoid m => Analyze r m -> m #

foldMap :: Monoid m => (a -> m) -> Analyze r a -> m #

foldr :: (a -> b -> b) -> b -> Analyze r a -> b #

foldr' :: (a -> b -> b) -> b -> Analyze r a -> b #

foldl :: (b -> a -> b) -> b -> Analyze r a -> b #

foldl' :: (b -> a -> b) -> b -> Analyze r a -> b #

foldr1 :: (a -> a -> a) -> Analyze r a -> a #

foldl1 :: (a -> a -> a) -> Analyze r a -> a #

toList :: Analyze r a -> [a] #

null :: Analyze r a -> Bool #

length :: Analyze r a -> Int #

elem :: Eq a => a -> Analyze r a -> Bool #

maximum :: Ord a => Analyze r a -> a #

minimum :: Ord a => Analyze r a -> a #

sum :: Num a => Analyze r a -> a #

product :: Num a => Analyze r a -> a #

ConstrainSASNames Traversable r => Traversable (Analyze r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Analyze r a -> f (Analyze r b) #

sequenceA :: Applicative f => Analyze r (f a) -> f (Analyze r a) #

mapM :: Monad m => (a -> m b) -> Analyze r a -> m (Analyze r b) #

sequence :: Monad m => Analyze r (m a) -> m (Analyze r a) #

ConstrainSNames Eq r a => Eq (Analyze r a) Source # 

Methods

(==) :: Analyze r a -> Analyze r a -> Bool #

(/=) :: Analyze r a -> Analyze r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Analyze r a) Source # 

Methods

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

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

toConstr :: Analyze r a -> Constr #

dataTypeOf :: Analyze r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (Analyze r a) Source # 

Methods

showsPrec :: Int -> Analyze r a -> ShowS #

show :: Analyze r a -> String #

showList :: [Analyze r a] -> ShowS #

Generic (Analyze r a) Source # 

Associated Types

type Rep (Analyze r a) :: * -> * #

Methods

from :: Analyze r a -> Rep (Analyze r a) x #

to :: Rep (Analyze r a) x -> Analyze r a #

(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (Analyze r a) Source # 
type Rep (Analyze r a) Source # 
type Rep (Analyze r a) = D1 * (MetaData "Analyze" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "Analyze" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "analyzeInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "analyzeTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TableName r a)))))

data InsertDirectory r a Source #

Instances

ConstrainSASNames Functor r => Functor (InsertDirectory r) Source # 

Methods

fmap :: (a -> b) -> InsertDirectory r a -> InsertDirectory r b #

(<$) :: a -> InsertDirectory r b -> InsertDirectory r a #

ConstrainSASNames Foldable r => Foldable (InsertDirectory r) Source # 

Methods

fold :: Monoid m => InsertDirectory r m -> m #

foldMap :: Monoid m => (a -> m) -> InsertDirectory r a -> m #

foldr :: (a -> b -> b) -> b -> InsertDirectory r a -> b #

foldr' :: (a -> b -> b) -> b -> InsertDirectory r a -> b #

foldl :: (b -> a -> b) -> b -> InsertDirectory r a -> b #

foldl' :: (b -> a -> b) -> b -> InsertDirectory r a -> b #

foldr1 :: (a -> a -> a) -> InsertDirectory r a -> a #

foldl1 :: (a -> a -> a) -> InsertDirectory r a -> a #

toList :: InsertDirectory r a -> [a] #

null :: InsertDirectory r a -> Bool #

length :: InsertDirectory r a -> Int #

elem :: Eq a => a -> InsertDirectory r a -> Bool #

maximum :: Ord a => InsertDirectory r a -> a #

minimum :: Ord a => InsertDirectory r a -> a #

sum :: Num a => InsertDirectory r a -> a #

product :: Num a => InsertDirectory r a -> a #

ConstrainSASNames Traversable r => Traversable (InsertDirectory r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> InsertDirectory r a -> f (InsertDirectory r b) #

sequenceA :: Applicative f => InsertDirectory r (f a) -> f (InsertDirectory r a) #

mapM :: Monad m => (a -> m b) -> InsertDirectory r a -> m (InsertDirectory r b) #

sequence :: Monad m => InsertDirectory r (m a) -> m (InsertDirectory r a) #

ConstrainSNames Eq r a => Eq (InsertDirectory r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (InsertDirectory r a) Source # 

Methods

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

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

toConstr :: InsertDirectory r a -> Constr #

dataTypeOf :: InsertDirectory r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (InsertDirectory r a) Source # 
Generic (InsertDirectory r a) Source # 

Associated Types

type Rep (InsertDirectory r a) :: * -> * #

Methods

from :: InsertDirectory r a -> Rep (InsertDirectory r a) x #

to :: Rep (InsertDirectory r a) x -> InsertDirectory r a #

(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (InsertDirectory r a) Source # 
HasColumns (InsertDirectory ResolvedNames a) Source # 

Methods

goColumns :: InsertDirectory ResolvedNames a -> Observer #

HasTables (InsertDirectory ResolvedNames a) Source # 
type Rep (InsertDirectory r a) Source # 
type Rep (InsertDirectory r a) = D1 * (MetaData "InsertDirectory" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "InsertDirectory" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "insertDirectoryInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "insertDirectoryLocale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (InsertDirectoryLocale a)))) ((:*:) * (S1 * (MetaSel (Just Symbol "insertDirectoryPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Location a))) (S1 * (MetaSel (Just Symbol "insertDirectoryQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))))

data Location a Source #

Constructors

HDFSPath a ByteString 

Instances

Functor Location Source # 

Methods

fmap :: (a -> b) -> Location a -> Location b #

(<$) :: a -> Location b -> Location a #

Foldable Location Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Location a -> [a] #

null :: Location a -> Bool #

length :: Location a -> Int #

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

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

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

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

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

Traversable Location Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Location a -> f (Location b) #

sequenceA :: Applicative f => Location (f a) -> f (Location a) #

mapM :: Monad m => (a -> m b) -> Location a -> m (Location b) #

sequence :: Monad m => Location (m a) -> m (Location a) #

Eq a => Eq (Location a) Source # 

Methods

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

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

Data a => Data (Location a) Source # 

Methods

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

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

toConstr :: Location a -> Constr #

dataTypeOf :: Location a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (Location a) Source # 

Methods

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

show :: Location a -> String #

showList :: [Location a] -> ShowS #

Generic (Location a) Source # 

Associated Types

type Rep (Location a) :: * -> * #

Methods

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

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

ToJSON a => ToJSON (Location a) Source # 
HasInfo (Location a) Source # 

Associated Types

type Info (Location a) :: * #

Methods

getInfo :: Location a -> Info (Location a) #

type Rep (Location a) Source # 
type Rep (Location a) = D1 * (MetaData "Location" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "HDFSPath" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString))))
type Info (Location a) Source # 
type Info (Location a) = a

data InsertDirectoryLocale a Source #

Instances

Functor InsertDirectoryLocale Source # 
Foldable InsertDirectoryLocale Source # 

Methods

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

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

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

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

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

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

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

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

toList :: InsertDirectoryLocale a -> [a] #

null :: InsertDirectoryLocale a -> Bool #

length :: InsertDirectoryLocale a -> Int #

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

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

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

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

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

Traversable InsertDirectoryLocale Source # 
Eq a => Eq (InsertDirectoryLocale a) Source # 
Data a => Data (InsertDirectoryLocale a) Source # 

Methods

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

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

toConstr :: InsertDirectoryLocale a -> Constr #

dataTypeOf :: InsertDirectoryLocale a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (InsertDirectoryLocale a) Source # 
Generic (InsertDirectoryLocale a) Source # 
ToJSON a => ToJSON (InsertDirectoryLocale a) Source # 
type Rep (InsertDirectoryLocale a) Source # 
type Rep (InsertDirectoryLocale a) = D1 * (MetaData "InsertDirectoryLocale" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) ((:+:) * (C1 * (MetaCons "InsertDirectoryLocal" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) (C1 * (MetaCons "InsertDirectoryHDFS" PrefixI False) (U1 *)))

data StaticPartitionSpecItem r a Source #

Constructors

StaticPartitionSpecItem a (ColumnRef r a) (Constant a) 

Instances

ConstrainSASNames Functor r => Functor (StaticPartitionSpecItem r) Source # 
ConstrainSASNames Foldable r => Foldable (StaticPartitionSpecItem r) Source # 

Methods

fold :: Monoid m => StaticPartitionSpecItem r m -> m #

foldMap :: Monoid m => (a -> m) -> StaticPartitionSpecItem r a -> m #

foldr :: (a -> b -> b) -> b -> StaticPartitionSpecItem r a -> b #

foldr' :: (a -> b -> b) -> b -> StaticPartitionSpecItem r a -> b #

foldl :: (b -> a -> b) -> b -> StaticPartitionSpecItem r a -> b #

foldl' :: (b -> a -> b) -> b -> StaticPartitionSpecItem r a -> b #

foldr1 :: (a -> a -> a) -> StaticPartitionSpecItem r a -> a #

foldl1 :: (a -> a -> a) -> StaticPartitionSpecItem r a -> a #

toList :: StaticPartitionSpecItem r a -> [a] #

null :: StaticPartitionSpecItem r a -> Bool #

length :: StaticPartitionSpecItem r a -> Int #

elem :: Eq a => a -> StaticPartitionSpecItem r a -> Bool #

maximum :: Ord a => StaticPartitionSpecItem r a -> a #

minimum :: Ord a => StaticPartitionSpecItem r a -> a #

sum :: Num a => StaticPartitionSpecItem r a -> a #

product :: Num a => StaticPartitionSpecItem r a -> a #

ConstrainSASNames Traversable r => Traversable (StaticPartitionSpecItem r) Source # 
ConstrainSNames Eq r a => Eq (StaticPartitionSpecItem r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (StaticPartitionSpecItem r a) Source # 

Methods

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

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

toConstr :: StaticPartitionSpecItem r a -> Constr #

dataTypeOf :: StaticPartitionSpecItem r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (StaticPartitionSpecItem r a) Source # 
Generic (StaticPartitionSpecItem r a) Source # 
(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (StaticPartitionSpecItem r a) Source # 
type Rep (StaticPartitionSpecItem r a) Source # 
type Rep (StaticPartitionSpecItem r a) = D1 * (MetaData "StaticPartitionSpecItem" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "StaticPartitionSpecItem" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ColumnRef r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Constant a))))))

data DynamicPartitionSpecItem r a Source #

Constructors

DynamicPartitionSpecItem a (ColumnRef r a) 

Instances

ConstrainSASNames Functor r => Functor (DynamicPartitionSpecItem r) Source # 
ConstrainSASNames Foldable r => Foldable (DynamicPartitionSpecItem r) Source # 

Methods

fold :: Monoid m => DynamicPartitionSpecItem r m -> m #

foldMap :: Monoid m => (a -> m) -> DynamicPartitionSpecItem r a -> m #

foldr :: (a -> b -> b) -> b -> DynamicPartitionSpecItem r a -> b #

foldr' :: (a -> b -> b) -> b -> DynamicPartitionSpecItem r a -> b #

foldl :: (b -> a -> b) -> b -> DynamicPartitionSpecItem r a -> b #

foldl' :: (b -> a -> b) -> b -> DynamicPartitionSpecItem r a -> b #

foldr1 :: (a -> a -> a) -> DynamicPartitionSpecItem r a -> a #

foldl1 :: (a -> a -> a) -> DynamicPartitionSpecItem r a -> a #

toList :: DynamicPartitionSpecItem r a -> [a] #

null :: DynamicPartitionSpecItem r a -> Bool #

length :: DynamicPartitionSpecItem r a -> Int #

elem :: Eq a => a -> DynamicPartitionSpecItem r a -> Bool #

maximum :: Ord a => DynamicPartitionSpecItem r a -> a #

minimum :: Ord a => DynamicPartitionSpecItem r a -> a #

sum :: Num a => DynamicPartitionSpecItem r a -> a #

product :: Num a => DynamicPartitionSpecItem r a -> a #

ConstrainSASNames Traversable r => Traversable (DynamicPartitionSpecItem r) Source # 
ConstrainSNames Eq r a => Eq (DynamicPartitionSpecItem r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (DynamicPartitionSpecItem r a) Source # 

Methods

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

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

toConstr :: DynamicPartitionSpecItem r a -> Constr #

dataTypeOf :: DynamicPartitionSpecItem r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (DynamicPartitionSpecItem r a) Source # 
Generic (DynamicPartitionSpecItem r a) Source # 
type Rep (DynamicPartitionSpecItem r a) Source # 
type Rep (DynamicPartitionSpecItem r a) = D1 * (MetaData "DynamicPartitionSpecItem" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "DynamicPartitionSpecItem" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ColumnRef r a)))))

data TruncatePartition r a Source #

Instances

ConstrainSASNames Functor r => Functor (TruncatePartition r) Source # 

Methods

fmap :: (a -> b) -> TruncatePartition r a -> TruncatePartition r b #

(<$) :: a -> TruncatePartition r b -> TruncatePartition r a #

ConstrainSASNames Foldable r => Foldable (TruncatePartition r) Source # 

Methods

fold :: Monoid m => TruncatePartition r m -> m #

foldMap :: Monoid m => (a -> m) -> TruncatePartition r a -> m #

foldr :: (a -> b -> b) -> b -> TruncatePartition r a -> b #

foldr' :: (a -> b -> b) -> b -> TruncatePartition r a -> b #

foldl :: (b -> a -> b) -> b -> TruncatePartition r a -> b #

foldl' :: (b -> a -> b) -> b -> TruncatePartition r a -> b #

foldr1 :: (a -> a -> a) -> TruncatePartition r a -> a #

foldl1 :: (a -> a -> a) -> TruncatePartition r a -> a #

toList :: TruncatePartition r a -> [a] #

null :: TruncatePartition r a -> Bool #

length :: TruncatePartition r a -> Int #

elem :: Eq a => a -> TruncatePartition r a -> Bool #

maximum :: Ord a => TruncatePartition r a -> a #

minimum :: Ord a => TruncatePartition r a -> a #

sum :: Num a => TruncatePartition r a -> a #

product :: Num a => TruncatePartition r a -> a #

ConstrainSASNames Traversable r => Traversable (TruncatePartition r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TruncatePartition r a -> f (TruncatePartition r b) #

sequenceA :: Applicative f => TruncatePartition r (f a) -> f (TruncatePartition r a) #

mapM :: Monad m => (a -> m b) -> TruncatePartition r a -> m (TruncatePartition r b) #

sequence :: Monad m => TruncatePartition r (m a) -> m (TruncatePartition r a) #

ConstrainSNames Eq r a => Eq (TruncatePartition r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (TruncatePartition r a) Source # 

Methods

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

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

toConstr :: TruncatePartition r a -> Constr #

dataTypeOf :: TruncatePartition r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (TruncatePartition r a) Source # 
Generic (TruncatePartition r a) Source # 

Associated Types

type Rep (TruncatePartition r a) :: * -> * #

(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (TruncatePartition r a) Source # 
HasInfo (TruncatePartition r a) Source # 

Associated Types

type Info (TruncatePartition r a) :: * #

HasTables (TruncatePartition ResolvedNames a) Source # 
type Rep (TruncatePartition r a) Source # 
type Rep (TruncatePartition r a) = D1 * (MetaData "TruncatePartition" "Database.Sql.Hive.Type" "queryparser-hive-0.1.0.1-8OiXrdWtC4FBsYNs8R3c1t" False) (C1 * (MetaCons "TruncatePartition" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "truncatePartitionInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "truncatePartitionTruncate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Truncate r a)))))
type Info (TruncatePartition r a) Source # 
type Info (TruncatePartition r a) = a

data AlterTableSetLocation r a Source #

Instances

ConstrainSASNames Functor r => Functor (AlterTableSetLocation r) Source # 
ConstrainSASNames Foldable r => Foldable (AlterTableSetLocation r) Source # 

Methods

fold :: Monoid m => AlterTableSetLocation r m -> m #

foldMap :: Monoid m => (a -> m) -> AlterTableSetLocation r a -> m #

foldr :: (a -> b -> b) -> b -> AlterTableSetLocation r a -> b #

foldr' :: (a -> b -> b) -> b -> AlterTableSetLocation r a -> b #

foldl :: (b -> a -> b) -> b -> AlterTableSetLocation r a -> b #

foldl' :: (b -> a -> b) -> b -> AlterTableSetLocation r a -> b #

foldr1 :: (a -> a -> a) -> AlterTableSetLocation r a -> a #

foldl1 :: (a -> a -> a) -> AlterTableSetLocation r a -> a #

toList :: AlterTableSetLocation r a -> [a] #

null :: AlterTableSetLocation r a -> Bool #

length :: AlterTableSetLocation r a -> Int #

elem :: Eq a => a -> AlterTableSetLocation r a -> Bool #

maximum :: Ord a => AlterTableSetLocation r a -> a #

minimum :: Ord a => AlterTableSetLocation r a -> a #

sum :: Num a => AlterTableSetLocation r a -> a #

product :: Num a => AlterTableSetLocation r a -> a #

ConstrainSASNames Traversable r => Traversable (AlterTableSetLocation r) Source # 
ConstrainSNames Eq r a => Eq (AlterTableSetLocation r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (AlterTableSetLocation r a) Source # 

Methods

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

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

toConstr :: AlterTableSetLocation r a -> Constr #

dataTypeOf :: AlterTableSetLocation r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (AlterTableSetLocation r a) Source # 
(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (AlterTableSetLocation r a) Source # 
HasTables (AlterTableSetLocation ResolvedNames a) Source # 

data AlterPartitionSetLocation r a Source #

Instances

ConstrainSASNames Functor r => Functor (AlterPartitionSetLocation r) Source # 
ConstrainSASNames Foldable r => Foldable (AlterPartitionSetLocation r) Source # 

Methods

fold :: Monoid m => AlterPartitionSetLocation r m -> m #

foldMap :: Monoid m => (a -> m) -> AlterPartitionSetLocation r a -> m #

foldr :: (a -> b -> b) -> b -> AlterPartitionSetLocation r a -> b #

foldr' :: (a -> b -> b) -> b -> AlterPartitionSetLocation r a -> b #

foldl :: (b -> a -> b) -> b -> AlterPartitionSetLocation r a -> b #

foldl' :: (b -> a -> b) -> b -> AlterPartitionSetLocation r a -> b #

foldr1 :: (a -> a -> a) -> AlterPartitionSetLocation r a -> a #

foldl1 :: (a -> a -> a) -> AlterPartitionSetLocation r a -> a #

toList :: AlterPartitionSetLocation r a -> [a] #

null :: AlterPartitionSetLocation r a -> Bool #

length :: AlterPartitionSetLocation r a -> Int #

elem :: Eq a => a -> AlterPartitionSetLocation r a -> Bool #

maximum :: Ord a => AlterPartitionSetLocation r a -> a #

minimum :: Ord a => AlterPartitionSetLocation r a -> a #

sum :: Num a => AlterPartitionSetLocation r a -> a #

product :: Num a => AlterPartitionSetLocation r a -> a #

ConstrainSASNames Traversable r => Traversable (AlterPartitionSetLocation r) Source # 
ConstrainSNames Eq r a => Eq (AlterPartitionSetLocation r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (AlterPartitionSetLocation r a) Source # 

Methods

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

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

toConstr :: AlterPartitionSetLocation r a -> Constr #

dataTypeOf :: AlterPartitionSetLocation r a -> DataType #

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

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

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

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

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

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

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

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

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

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

ConstrainSNames Show r a => Show (AlterPartitionSetLocation r a) Source # 
(ConstrainSNames ToJSON r a, ToJSON a) => ToJSON (AlterPartitionSetLocation r a) Source #