diff --git a/Language/SQL/SimpleSQL/Parser.lhs b/Language/SQL/SimpleSQL/Parser.lhs
index 8ca9e01..46d2234 100644
--- a/Language/SQL/SimpleSQL/Parser.lhs
+++ b/Language/SQL/SimpleSQL/Parser.lhs
@@ -1441,15 +1441,10 @@ TODO: change style
 
 > statement :: Parser Statement
 > statement = choice
->     [keyword_ "create"
->      *> choice
->         [createSchema
->         ,createTable
->         ]
->     ,keyword_ "drop"
->      *> choice
->         [dropSchema
->         ]
+>     [keyword_ "create" *> choice [createSchema
+>                                  ,createTable]
+>     ,keyword_ "alter" *> choice [alterTable]
+>     ,keyword_ "drop" *> choice [dropSchema]
 >     ,delete
 >     ,truncateSt
 >     ,insert
@@ -1466,11 +1461,14 @@ TODO: change style
 >     CreateTable
 >     <$> names
 >     -- todo: is this order mandatory or is it a perm?
->     <*> parens (commaSep1 (tableConstraintDef <|> columnDef))
+>     <*> parens (commaSep1 (tableConstraintDef
+>                            <|> TableColumnDef <$> columnDef))
+
+> columnDef :: Parser ColumnDef
+> columnDef = ColumnDef <$> name <*> typeName
+>             <*> optionMaybe defaultClause
+>             <*> option [] (many1 colConstraintDef)
 >   where
->     columnDef = ColumnDef <$> name <*> typeName
->                 <*> optionMaybe defaultClause
->                 <*> option [] (many1 colConstraintDef)
 >     defaultClause = choice [
 >         keyword_ "default" >>
 >         DefaultClause <$> valueExpr
@@ -1571,10 +1569,17 @@ TODO: change style
 slightly hacky parser for signed integers
 
 > signedInteger :: Parser Integer
-> signedInteger = do
->     s <- option 1 (1 <$ symbol "+" <|> (-1) <$ symbol "-")
->     d <- unsignedInteger
->     return $ s * d
+> signedInteger =
+>     (*) <$> option 1 (1 <$ symbol "+" <|> (-1) <$ symbol "-")
+>     <*> unsignedInteger
+
+> alterTable :: Parser Statement
+> alterTable = keyword_ "table" >>
+>     AlterTable <$> names <*> choice [addColumnDef]
+>   where
+>     addColumnDef = try (keyword_ "add"
+>                         *> optional (keyword_ "column")) >>
+>                    AddColumnDef <$> columnDef
 
 > dropSchema :: Parser Statement
 > dropSchema = keyword_ "schema" >>
diff --git a/Language/SQL/SimpleSQL/Pretty.lhs b/Language/SQL/SimpleSQL/Pretty.lhs
index 12fd8df..76e4a06 100644
--- a/Language/SQL/SimpleSQL/Pretty.lhs
+++ b/Language/SQL/SimpleSQL/Pretty.lhs
@@ -457,28 +457,10 @@ which have been changed to try to improve the layout of the output.
 >     text "create" <+> text "table" <+> names nm
 >     <+> parens (commaSep $ map cd cds)
 >   where
->     cd (ColumnDef n t mdef cons) =
->       name n <+> typeName t
->       <+> case mdef of
->              Nothing -> empty
->              Just (DefaultClause def) ->
->                  text "default" <+> valueExpr d def
->              Just (GenerationClause e) ->
->                  texts ["generated","always","as"] <+> parens (valueExpr d e)
->              Just (IdentityColumnSpec w o) ->
->                  text "generated"
->                  <+> (case w of
->                          GeneratedDefault -> empty
->                          GeneratedAlways -> text "always"
->                          GeneratedByDefault -> text "by" <+> text "default")
->                  <+> text "as" <+> text "identity"
->                  <+> (case o of
->                          [] -> empty
->                          os -> parens (sep $ map sgo os))
->       <+> sep (map cdef cons)
 >     cd (TableConstraintDef n con) =
 >         maybe empty (\s -> text "constraint" <+> names s) n
 >         <+> ptcon con
+>     cd (TableColumnDef cd') = columnDef d cd'
 >     ptcon (TableUniqueConstraint ns) =
 >          text "unique" <+> parens (commaSep $ map name ns)
 >     ptcon (TablePrimaryKeyConstraint ns) =
@@ -494,40 +476,9 @@ which have been changed to try to improve the layout of the output.
 >         <+> refAct "delete" del
 >     ptcon (TableCheckConstraint v) = text "check" <+> parens (valueExpr d v)
 
->     sgo (SGOStartWith i) = texts ["start",  "with", show i]
->     sgo (SGOIncrementBy i) = texts ["increment", "by", show i]
->     sgo (SGOMaxValue i) = texts ["maxvalue", show i]
->     sgo SGONoMaxValue = texts ["no", "maxvalue"]
->     sgo (SGOMinValue i) = texts ["minvalue", show i]
->     sgo SGONoMinValue = texts ["no", "minvalue"]
->     sgo SGOCycle = text "cycle"
->     sgo SGONoCycle = text "no cycle"
->     cdef (ColConstraintDef cnm con) =
->         maybe empty (\s -> text "constraint" <+> names s) cnm
->         <+> pcon con
->     pcon ColNotNullConstraint = texts ["not","null"]
->     pcon ColUniqueConstraint = text "unique"
->     pcon ColPrimaryKeyConstraint = texts ["primary","key"]
->     pcon (ColCheckConstraint v) = text "check" <+> parens (valueExpr d v)
->     pcon (ColReferencesConstraint t c m u del) =
->         text "references"
->         <+> names t
->         <+> maybe empty (\c' -> parens (name c')) c
->         <+> refMatch m
->         <+> refAct "update" u
->         <+> refAct "delete" del
->     refMatch m = case m of
->                      DefaultReferenceMatch -> empty
->                      MatchFull -> texts ["match", "full"]
->                      MatchPartial -> texts ["match","partial"]
->                      MatchSimple -> texts ["match", "simple"]
->     refAct t a = case a of
->                      DefaultReferentialAction -> empty
->                      RefCascade -> texts ["on", t, "cascade"]
->                      RefSetNull -> texts ["on", t, "set", "null"]
->                      RefSetDefault -> texts ["on", t, "set", "default"]
->                      RefRestrict -> texts ["on", t, "restrict"]
->                      RefNoAction -> texts ["on", t, "no", "action"]
+> statement d (AlterTable t act) =
+>     texts ["alter","table"] <+> names t
+>     <+> alterTableAction d act
 
 > statement _ (DropSchema nm db) =
 >     text "drop" <+> text "schema" <+> names nm <+> dropBehav db
@@ -580,6 +531,70 @@ which have been changed to try to improve the layout of the output.
 > dropBehav Restrict = text "restrict"
 
 
+> columnDef :: Dialect -> ColumnDef -> Doc
+> columnDef d (ColumnDef n t mdef cons) =
+>       name n <+> typeName t
+>       <+> case mdef of
+>              Nothing -> empty
+>              Just (DefaultClause def) ->
+>                  text "default" <+> valueExpr d def
+>              Just (GenerationClause e) ->
+>                  texts ["generated","always","as"] <+> parens (valueExpr d e)
+>              Just (IdentityColumnSpec w o) ->
+>                  text "generated"
+>                  <+> (case w of
+>                          GeneratedDefault -> empty
+>                          GeneratedAlways -> text "always"
+>                          GeneratedByDefault -> text "by" <+> text "default")
+>                  <+> text "as" <+> text "identity"
+>                  <+> (case o of
+>                          [] -> empty
+>                          os -> parens (sep $ map sgo os))
+>       <+> sep (map cdef cons)
+>   where
+>     sgo (SGOStartWith i) = texts ["start",  "with", show i]
+>     sgo (SGOIncrementBy i) = texts ["increment", "by", show i]
+>     sgo (SGOMaxValue i) = texts ["maxvalue", show i]
+>     sgo SGONoMaxValue = texts ["no", "maxvalue"]
+>     sgo (SGOMinValue i) = texts ["minvalue", show i]
+>     sgo SGONoMinValue = texts ["no", "minvalue"]
+>     sgo SGOCycle = text "cycle"
+>     sgo SGONoCycle = text "no cycle"
+>     cdef (ColConstraintDef cnm con) =
+>         maybe empty (\s -> text "constraint" <+> names s) cnm
+>         <+> pcon con
+>     pcon ColNotNullConstraint = texts ["not","null"]
+>     pcon ColUniqueConstraint = text "unique"
+>     pcon ColPrimaryKeyConstraint = texts ["primary","key"]
+>     pcon (ColCheckConstraint v) = text "check" <+> parens (valueExpr d v)
+>     pcon (ColReferencesConstraint tb c m u del) =
+>         text "references"
+>         <+> names tb
+>         <+> maybe empty (\c' -> parens (name c')) c
+>         <+> refMatch m
+>         <+> refAct "update" u
+>         <+> refAct "delete" del
+
+> refMatch :: ReferenceMatch -> Doc
+> refMatch m = case m of
+>                      DefaultReferenceMatch -> empty
+>                      MatchFull -> texts ["match", "full"]
+>                      MatchPartial -> texts ["match","partial"]
+>                      MatchSimple -> texts ["match", "simple"]
+
+> refAct :: String -> ReferentialAction -> Doc
+> refAct t a = case a of
+>                      DefaultReferentialAction -> empty
+>                      RefCascade -> texts ["on", t, "cascade"]
+>                      RefSetNull -> texts ["on", t, "set", "null"]
+>                      RefSetDefault -> texts ["on", t, "set", "default"]
+>                      RefRestrict -> texts ["on", t, "restrict"]
+>                      RefNoAction -> texts ["on", t, "no", "action"]
+
+> alterTableAction :: Dialect -> AlterTableAction -> Doc
+> alterTableAction d (AddColumnDef cd) =
+>     texts ["add", "column"] <+> columnDef d cd
+
 = utils
 
 > commaSep :: [Doc] -> Doc
diff --git a/Language/SQL/SimpleSQL/Syntax.lhs b/Language/SQL/SimpleSQL/Syntax.lhs
index 303c1d8..576d553 100644
--- a/Language/SQL/SimpleSQL/Syntax.lhs
+++ b/Language/SQL/SimpleSQL/Syntax.lhs
@@ -37,6 +37,7 @@
 >     ,InsertSource(..)
 >     ,SetClause(..)
 >     ,TableElement(..)
+>     ,ColumnDef(..)
 >     ,DefaultClause(..)
 >     ,IdentityWhen(..)
 >     ,SequenceGeneratorOption(..)
@@ -45,6 +46,7 @@
 >     ,TableConstraint(..)
 >     ,ReferenceMatch(..)
 >     ,ReferentialAction(..)
+>     ,AlterTableAction(..)
 >      -- * Dialect
 >     ,Dialect(..)
 >      -- * Comment
@@ -402,8 +404,8 @@ I'm not sure if this is valid syntax or not.
 >     CreateSchema [Name] -- XXX
 >   | DropSchema [Name] DropBehaviour -- XXX
 >   | CreateTable [Name] [TableElement]
->   {-  | AlterTable -- XXX
->   | DropTable  -- XXX
+>   | AlterTable [Name] AlterTableAction
+>   {-  | DropTable  -- XXX
 >   | CreateView  -- XXX
 >   | DropView -- XXX
 >   | CreateDomain  -- XXX
@@ -496,11 +498,14 @@ I'm not sure if this is valid syntax or not.
 >     deriving (Eq,Show,Read,Data,Typeable)
 
 > data TableElement =
->     ColumnDef Name TypeName
+>     TableColumnDef ColumnDef
+>   | TableConstraintDef (Maybe [Name]) TableConstraint
+>     deriving (Eq,Show,Read,Data,Typeable)
+
+> data ColumnDef = ColumnDef Name TypeName
 >        (Maybe DefaultClause)
 >        [ColConstraintDef]
 >        -- (Maybe CollateClause)
->   | TableConstraintDef (Maybe [Name]) TableConstraint
 >     deriving (Eq,Show,Read,Data,Typeable)
 
 > data ColConstraintDef =
@@ -546,6 +551,17 @@ I'm not sure if this is valid syntax or not.
 >   | RefNoAction
 >     deriving (Eq,Show,Read,Data,Typeable)
 
+> data AlterTableAction =
+>     AddColumnDef ColumnDef
+>   {-
+>   | AlterColumnDef
+>   | DropColumnDef
+>   | AddTableConstraintDef
+>   | AlterTableConstraintDef
+>   | DropTableConstraintDef
+>   -}
+>     deriving (Eq,Show,Read,Data,Typeable)
+
 > {-data ConstraintCharacteristics =
 >     ConstraintCharacteristics
 >         ConstraintCheckTime
diff --git a/tools/Language/SQL/SimpleSQL/SQL2011Schema.lhs b/tools/Language/SQL/SimpleSQL/SQL2011Schema.lhs
index 1218315..9378406 100644
--- a/tools/Language/SQL/SimpleSQL/SQL2011Schema.lhs
+++ b/tools/Language/SQL/SimpleSQL/SQL2011Schema.lhs
@@ -96,8 +96,8 @@ add schema element support:
 
 >     ,(TestStatement SQL2011 "create table t (a int, b int);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
->        ,ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        ,TableColumnDef $ ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []])
 
 
 <table contents source> ::=
@@ -146,7 +146,7 @@ defintely skip
 
 <typed table element> ::=
     <column options>
-  | <table constraint definition>
+ | <table constraint definition>
   | <self-referencing column specification>
 
 defintely skip
@@ -313,25 +313,25 @@ todo: constraint characteristics
 >     ,(TestStatement SQL2011
 >       "create table t (a int not null);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing ColNotNullConstraint]])
 
 >     ,(TestStatement SQL2011
 >       "create table t (a int constraint a_not_null not null);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef (Just [Name "a_not_null"]) ColNotNullConstraint]])
 
 >     ,(TestStatement SQL2011
 >       "create table t (a int unique);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing ColUniqueConstraint]])
 
 >     ,(TestStatement SQL2011
 >       "create table t (a int primary key);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing ColPrimaryKeyConstraint]])
 
 references t(a,b)
@@ -342,7 +342,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          DefaultReferentialAction DefaultReferentialAction]])
@@ -350,7 +350,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u(a));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] (Just $ Name "a") DefaultReferenceMatch
 >          DefaultReferentialAction DefaultReferentialAction]])
@@ -358,7 +358,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u match full);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing MatchFull
 >          DefaultReferentialAction DefaultReferentialAction]])
@@ -366,7 +366,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u match partial);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing MatchPartial
 >          DefaultReferentialAction DefaultReferentialAction]])
@@ -374,7 +374,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u match simple);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing MatchSimple
 >          DefaultReferentialAction DefaultReferentialAction]])
@@ -382,7 +382,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u on update cascade );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          RefCascade DefaultReferentialAction]])
@@ -390,7 +390,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u on update set null );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          RefSetNull DefaultReferentialAction]])
@@ -398,7 +398,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u on update set default );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          RefSetDefault DefaultReferentialAction]])
@@ -406,7 +406,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u on update no action );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          RefNoAction DefaultReferentialAction]])
@@ -414,7 +414,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u on delete cascade );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          DefaultReferentialAction RefCascade]])
@@ -423,7 +423,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u on update cascade on delete restrict );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          RefCascade RefRestrict]])
@@ -431,7 +431,7 @@ references t(a,b)
 >     ,(TestStatement SQL2011
 >       "create table t (a int references u on delete restrict on update cascade );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing $ ColReferencesConstraint
 >          [Name "u"] Nothing DefaultReferenceMatch
 >          RefCascade RefRestrict]])
@@ -443,7 +443,7 @@ options
 >     ,(TestStatement SQL2011
 >       "create table t (a int check (a>5));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing
 >         [ColConstraintDef Nothing
 >          (ColCheckConstraint $ BinOp (Iden [Name "a"]) [Name ">"] (NumLit "5"))]])
 
@@ -457,17 +457,17 @@ options
 
 >     ,(TestStatement SQL2011 "create table t (a int generated as identity);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"])
 >         (Just $ IdentityColumnSpec GeneratedDefault []) []])
 
 >     ,(TestStatement SQL2011 "create table t (a int generated always as identity);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"])
 >         (Just $ IdentityColumnSpec GeneratedAlways []) []])
 
 >     ,(TestStatement SQL2011 "create table t (a int generated by default as identity);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"])
 >         (Just $ IdentityColumnSpec GeneratedByDefault []) []])
 
 
@@ -475,7 +475,7 @@ options
 >       "create table t (a int generated as identity\n\
 >       \  ( start with 5 increment by 5 maxvalue 500 minvalue 5 cycle ));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"])
 >         (Just $ IdentityColumnSpec GeneratedDefault
 >          [SGOStartWith 5
 >          ,SGOIncrementBy 5
@@ -487,7 +487,7 @@ options
 >       "create table t (a int generated as identity\n\
 >       \  ( start with -4 no maxvalue no minvalue no cycle ));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"])
 >         (Just $ IdentityColumnSpec GeneratedDefault
 >          [SGOStartWith (-4)
 >          ,SGONoMaxValue
@@ -515,8 +515,8 @@ generated always (valueexpr)
 >       "create table t (a int, \n\
 >       \                a2 int generated always as (a * 2));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
->        ,ColumnDef (Name "a2") (TypeName [Name "int"])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        ,TableColumnDef $ ColumnDef (Name "a2") (TypeName [Name "int"])
 >         (Just $ GenerationClause
 >          (BinOp (Iden [Name "a"]) [Name "*"] (NumLit "2"))) []])
 
@@ -543,7 +543,7 @@ generated always (valueexpr)
 
 >     ,(TestStatement SQL2011 "create table t (a int default 0);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"])
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"])
 >         (Just $ DefaultClause $ NumLit "0") []])
 
 
@@ -576,14 +576,14 @@ generated always (valueexpr)
 >     ,(TestStatement SQL2011
 >       "create table t (a int, unique (a));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef Nothing $ TableUniqueConstraint [Name "a"]
 >         ])
 
 >     ,(TestStatement SQL2011
 >       "create table t (a int, constraint a_unique unique (a));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef (Just [Name "a_unique"]) $
 >             TableUniqueConstraint [Name "a"]
 >         ])
@@ -593,8 +593,8 @@ todo: test permutations of column defs and table constraints
 >     ,(TestStatement SQL2011
 >       "create table t (a int, b int, unique (a,b));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
->        ,ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        ,TableColumnDef $ ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef Nothing $
 >             TableUniqueConstraint [Name "a", Name "b"]
 >         ])
@@ -602,8 +602,8 @@ todo: test permutations of column defs and table constraints
 >     ,(TestStatement SQL2011
 >       "create table t (a int, b int, primary key (a,b));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
->        ,ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        ,TableColumnDef $ ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef Nothing $
 >             TablePrimaryKeyConstraint [Name "a", Name "b"]
 >         ])
@@ -627,8 +627,8 @@ defintely skip
 >       "create table t (a int, b int,\n\
 >       \                foreign key (a,b) references u(c,d) match full on update cascade on delete restrict );"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
->        ,ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        ,TableColumnDef $ ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef Nothing $
 >             TableReferencesConstraint
 >                 [Name "a", Name "b"]
@@ -641,7 +641,7 @@ defintely skip
 >       "create table t (a int,\n\
 >       \                constraint tfku1 foreign key (a) references u);"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef (Just [Name "tfku1"]) $
 >             TableReferencesConstraint
 >                 [Name "a"]
@@ -709,8 +709,8 @@ defintely skip
 >       "create table t (a int, b int, \n\
 >       \                check (a > b));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
->        ,ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        ,TableColumnDef $ ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef Nothing $
 >             TableCheckConstraint
 >             (BinOp (Iden [Name "a"]) [Name ">"] (Iden [Name "b"]))
@@ -721,8 +721,8 @@ defintely skip
 >       "create table t (a int, b int, \n\
 >       \                constraint agtb check (a > b));"
 >      $ CreateTable [Name "t"]
->        [ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
->        ,ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
+>        [TableColumnDef $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        ,TableColumnDef $ ColumnDef (Name "b") (TypeName [Name "int"]) Nothing []
 >        ,TableConstraintDef (Just [Name "agtb"]) $
 >             TableCheckConstraint
 >             (BinOp (Iden [Name "a"]) [Name ">"] (Iden [Name "b"]))
@@ -758,6 +758,13 @@ alter table t add column a int
 alter table t add a int
 alter table t add a int unique not null check (a>0)
 
+>     ,(TestStatement SQL2011
+>       "alter table t add column a int"
+>      $ AlterTable [Name "t"] $ AddColumnDef
+>        $ ColumnDef (Name "a") (TypeName [Name "int"]) Nothing []
+>        )
+
+
 11.12 <alter column definition>
 
 <alter column definition> ::=