Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Beam.Haskell.Syntax
Description
Synopsis
- newtype HsDbField = HsDbField {
- buildHsDbField :: Type () -> Type ()
- data HsConstraintDefinition = HsConstraintDefinition {}
- newtype HsEntityName = HsEntityName {}
- data HsImport
- = HsImportAll
- | HsImportSome (Set (ImportSpec ()))
- importSome :: Text -> [ImportSpec ()] -> HsImports
- importTyNamed :: Text -> ImportSpec ()
- importVarNamed :: Text -> ImportSpec ()
- newtype HsImports = HsImports (Map (ModuleName ()) HsImport)
- data HsDataType = HsDataType {}
- data HsType = HsType {
- hsTypeSyntax :: Type ()
- hsTypeImports :: HsImports
- data HsExpr = HsExpr {
- hsExprSyntax :: Exp ()
- hsExprImports :: HsImports
- hsExprConstraints :: [Asst ()]
- hsExprTypeVariables :: Set (Name ())
- data HsColumnSchema = HsColumnSchema {}
- data HsDecl = HsDecl {
- hsDeclSyntax :: Decl ()
- hsDeclImports :: HsImports
- hsDeclExports :: [ExportSpec ()]
- data HsAction = HsAction {
- hsSyntaxMigration :: [(Maybe (Pat ()), HsExpr)]
- hsSyntaxEntities :: [HsEntity]
- newtype HsBackendConstraint = HsBackendConstraint {
- buildHsBackendConstraint :: Type () -> Asst ()
- data HsBeamBackend f
- data HsEntity = HsEntity {}
- newtype HsFieldLookup = HsFieldLookup {
- hsFieldLookup :: Text -> Maybe (Text, Type ())
- newtype HsTableConstraint = HsTableConstraint (Text -> HsFieldLookup -> HsTableConstraintDecls)
- data HsTableConstraintDecls = HsTableConstraintDecls {}
- data HsModule = HsModule {
- hsModuleName :: String
- hsModuleEntities :: [HsEntity]
- hsModuleMigration :: [(Maybe (Pat ()), HsExpr)]
- hsActionsToModule :: String -> [HsAction] -> HsModule
- unqual :: String -> QName ()
- entityDbFieldName :: HsEntity -> String
- derivingDecl :: [InstRule ()] -> Deriving ()
- dataDecl :: DeclHead () -> [QualConDecl ()] -> Maybe (Deriving ()) -> Decl ()
- insDataDecl :: Type () -> [QualConDecl ()] -> Maybe (Deriving ()) -> InstDecl ()
- databaseTypeDecl :: [HsEntity] -> Decl ()
- migrationTypeDecl :: HsBeamBackend HsExpr -> [Type ()] -> Decl ()
- migrationDecl :: HsBeamBackend HsExpr -> [Exp ()] -> [(Maybe (Pat ()), HsExpr)] -> [HsEntity] -> Decl ()
- dbTypeDecl :: HsBeamBackend HsExpr -> Decl ()
- dbDecl :: HsBeamBackend HsExpr -> [HsExpr] -> Decl ()
- renderHsSchema :: HsModule -> Either String String
- data HsNone = HsNone
- data HsMigrateBackend = HsMigrateBackend
- hsMkTableName :: (Char -> Char) -> TableName -> String
- hsTableVarName :: TableName -> String
- hsTableTypeName :: TableName -> String
- hsErrorType :: String -> HsDataType
- tyParens :: Type () -> Type ()
- functionTy :: Type () -> Type () -> Type ()
- tyTuple :: [Type ()] -> Type ()
- tyApp :: Type () -> [Type ()] -> Type ()
- tyConNamed :: String -> Type ()
- tyVarNamed :: String -> Type ()
- combineHsExpr :: (Exp () -> Exp () -> Exp ()) -> HsExpr -> HsExpr -> HsExpr
- hsApp :: HsExpr -> [HsExpr] -> HsExpr
- hsVisibleTyApp :: HsExpr -> Type () -> HsExpr
- hsApApp :: HsExpr -> [HsExpr] -> HsExpr
- hsStr :: Text -> HsExpr
- hsRecCon :: Text -> [(Text, HsExpr)] -> HsExpr
- hsMaybe :: Maybe HsExpr -> HsExpr
- hsVar :: Text -> HsExpr
- hsVarFrom :: Text -> Text -> HsExpr
- hsTyCon :: Text -> HsExpr
- hsInt :: (Integral a, Show a) => a -> HsExpr
- hsOp :: Text -> QOp ()
- hsInstance :: Text -> [Type ()] -> [InstDecl ()] -> Decl ()
- hsDerivingInstance :: Text -> [Type ()] -> Decl ()
- hsList :: [HsExpr] -> HsExpr
- hsTuple :: [HsExpr] -> HsExpr
- inst :: String -> InstRule ()
- beamMigrateSqlBackend :: HsBackendConstraint
Documentation
data HsConstraintDefinition Source #
Constructors
HsConstraintDefinition | |
Fields |
Instances
newtype HsEntityName Source #
Constructors
HsEntityName | |
Fields |
Instances
Eq HsEntityName Source # | |
Defined in Database.Beam.Haskell.Syntax | |
Ord HsEntityName Source # | |
Defined in Database.Beam.Haskell.Syntax Methods compare :: HsEntityName -> HsEntityName -> Ordering # (<) :: HsEntityName -> HsEntityName -> Bool # (<=) :: HsEntityName -> HsEntityName -> Bool # (>) :: HsEntityName -> HsEntityName -> Bool # (>=) :: HsEntityName -> HsEntityName -> Bool # max :: HsEntityName -> HsEntityName -> HsEntityName # min :: HsEntityName -> HsEntityName -> HsEntityName # | |
Show HsEntityName Source # | |
Defined in Database.Beam.Haskell.Syntax Methods showsPrec :: Int -> HsEntityName -> ShowS # show :: HsEntityName -> String # showList :: [HsEntityName] -> ShowS # | |
IsString HsEntityName Source # | |
Defined in Database.Beam.Haskell.Syntax Methods fromString :: String -> HsEntityName # |
Constructors
HsImportAll | |
HsImportSome (Set (ImportSpec ())) |
Instances
Eq HsImport Source # | |
Show HsImport Source # | |
Generic HsImport Source # | |
Semigroup HsImport Source # | |
Monoid HsImport Source # | |
Hashable HsImport Source # | |
Defined in Database.Beam.Haskell.Syntax | |
type Rep HsImport Source # | |
Defined in Database.Beam.Haskell.Syntax type Rep HsImport = D1 (MetaData "HsImport" "Database.Beam.Haskell.Syntax" "beam-migrate-0.5.0.0-Amkz3hN0o3M2sLj2AmgBqU" False) (C1 (MetaCons "HsImportAll" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HsImportSome" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ImportSpec ()))))) |
importSome :: Text -> [ImportSpec ()] -> HsImports Source #
importTyNamed :: Text -> ImportSpec () Source #
importVarNamed :: Text -> ImportSpec () Source #
Constructors
HsImports (Map (ModuleName ()) HsImport) |
data HsDataType Source #
Constructors
HsDataType | |
Instances
Constructors
HsType | |
Fields
|
Instances
Eq HsType Source # | |
Show HsType Source # | |
Generic HsType Source # | |
Hashable HsType Source # | |
Defined in Database.Beam.Haskell.Syntax | |
type Rep HsType Source # | |
Defined in Database.Beam.Haskell.Syntax type Rep HsType = D1 (MetaData "HsType" "Database.Beam.Haskell.Syntax" "beam-migrate-0.5.0.0-Amkz3hN0o3M2sLj2AmgBqU" False) (C1 (MetaCons "HsType" PrefixI True) (S1 (MetaSel (Just "hsTypeSyntax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type ())) :*: S1 (MetaSel (Just "hsTypeImports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HsImports))) |
Constructors
HsExpr | |
Fields
|
Instances
data HsColumnSchema Source #
Constructors
HsColumnSchema | |
Fields
|
Instances
Constructors
HsDecl | |
Fields
|
Constructors
HsAction | |
Fields
|
Instances
newtype HsBackendConstraint Source #
Constructors
HsBackendConstraint | |
Fields
|
data HsBeamBackend f Source #
Constructors
HsBeamBackendSingle HsType f | |
HsBeamBackendConstrained [HsBackendConstraint] | |
HsBeamBackendNone |
Instances
Semigroup (HsBeamBackend f) Source # | |
Defined in Database.Beam.Haskell.Syntax Methods (<>) :: HsBeamBackend f -> HsBeamBackend f -> HsBeamBackend f # sconcat :: NonEmpty (HsBeamBackend f) -> HsBeamBackend f # stimes :: Integral b => b -> HsBeamBackend f -> HsBeamBackend f # | |
Monoid (HsBeamBackend f) Source # | |
Defined in Database.Beam.Haskell.Syntax Methods mempty :: HsBeamBackend f # mappend :: HsBeamBackend f -> HsBeamBackend f -> HsBeamBackend f # mconcat :: [HsBeamBackend f] -> HsBeamBackend f # |
Constructors
HsEntity | |
Fields |
newtype HsFieldLookup Source #
Constructors
HsFieldLookup | |
Fields
|
newtype HsTableConstraint Source #
Constructors
HsTableConstraint (Text -> HsFieldLookup -> HsTableConstraintDecls) |
Instances
IsSql92TableConstraintSyntax HsTableConstraint Source # | |
Defined in Database.Beam.Haskell.Syntax Methods primaryKeyConstraintSyntax :: [Text] -> HsTableConstraint Source # |
data HsTableConstraintDecls Source #
Constructors
HsTableConstraintDecls | |
Fields
|
Instances
Semigroup HsTableConstraintDecls Source # | |
Defined in Database.Beam.Haskell.Syntax Methods (<>) :: HsTableConstraintDecls -> HsTableConstraintDecls -> HsTableConstraintDecls # sconcat :: NonEmpty HsTableConstraintDecls -> HsTableConstraintDecls # stimes :: Integral b => b -> HsTableConstraintDecls -> HsTableConstraintDecls # | |
Monoid HsTableConstraintDecls Source # | |
Defined in Database.Beam.Haskell.Syntax |
Constructors
HsModule | |
Fields
|
entityDbFieldName :: HsEntity -> String Source #
derivingDecl :: [InstRule ()] -> Deriving () Source #
insDataDecl :: Type () -> [QualConDecl ()] -> Maybe (Deriving ()) -> InstDecl () Source #
databaseTypeDecl :: [HsEntity] -> Decl () Source #
migrationTypeDecl :: HsBeamBackend HsExpr -> [Type ()] -> Decl () Source #
migrationDecl :: HsBeamBackend HsExpr -> [Exp ()] -> [(Maybe (Pat ()), HsExpr)] -> [HsEntity] -> Decl () Source #
dbTypeDecl :: HsBeamBackend HsExpr -> Decl () Source #
DDL Syntax definitions
Constructors
HsNone |
Instances
data HsMigrateBackend Source #
Constructors
HsMigrateBackend |
Instances
BeamMigrateOnlySqlBackend HsMigrateBackend Source # | |
Defined in Database.Beam.Haskell.Syntax | |
type BeamSqlBackendSyntax HsMigrateBackend Source # | |
Defined in Database.Beam.Haskell.Syntax |
hsTableVarName :: TableName -> String Source #
hsTableTypeName :: TableName -> String Source #
hsErrorType :: String -> HsDataType Source #
HsSyntax utilities
tyConNamed :: String -> Type () Source #
tyVarNamed :: String -> Type () Source #