Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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 -> HsBeamBackend () -> [Type ()] -> Decl ()
- migrationDecl :: HsBeamBackend HsExpr -> [Exp ()] -> [(Maybe (Pat ()), HsExpr)] -> [HsEntity] -> Decl ()
- dbTypeDecl :: HsBeamBackend HsExpr -> HsBeamBackend () -> Decl ()
- dbDecl :: HsBeamBackend HsExpr -> HsBeamBackend () -> [HsExpr] -> Decl ()
- renderHsSchema :: HsModule -> Either String String
- data HsNone = HsNone
- 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 ()
- sql92SaneDdlCommandSyntax :: HsBackendConstraint
Documentation
data HsConstraintDefinition Source #
newtype HsEntityName Source #
HsImportAll | |
HsImportSome (Set (ImportSpec ())) |
importSome :: Text -> [ImportSpec ()] -> HsImports Source #
importTyNamed :: Text -> ImportSpec () Source #
importVarNamed :: Text -> ImportSpec () Source #
HsImports (Map (ModuleName ()) HsImport) |
data HsDataType Source #
HsType | |
|
HsExpr | |
|
data HsColumnSchema Source #
HsDecl | |
|
HsAction | |
|
newtype HsBackendConstraint Source #
HsBackendConstraint | |
|
data HsBeamBackend f Source #
Semigroup (HsBeamBackend f) Source # | |
Monoid (HsBeamBackend f) Source # | |
newtype HsFieldLookup Source #
HsFieldLookup | |
|
newtype HsTableConstraint Source #
HsModule | |
|
entityDbFieldName :: HsEntity -> String Source #
derivingDecl :: [InstRule ()] -> Deriving () Source #
insDataDecl :: Type () -> [QualConDecl ()] -> Maybe (Deriving ()) -> InstDecl () Source #
databaseTypeDecl :: [HsEntity] -> Decl () Source #
migrationTypeDecl :: HsBeamBackend HsExpr -> HsBeamBackend () -> [Type ()] -> Decl () Source #
migrationDecl :: HsBeamBackend HsExpr -> [Exp ()] -> [(Maybe (Pat ()), HsExpr)] -> [HsEntity] -> Decl () Source #
dbTypeDecl :: HsBeamBackend HsExpr -> HsBeamBackend () -> Decl () Source #
dbDecl :: HsBeamBackend HsExpr -> HsBeamBackend () -> [HsExpr] -> Decl () Source #
DDL Syntax definitions
hsErrorType :: String -> HsDataType Source #
HsSyntax utilities
tyConNamed :: String -> Type () Source #
tyVarNamed :: String -> Type () Source #