diff --git a/Language/SQL/SimpleSQL/Fixity.lhs b/Language/SQL/SimpleSQL/Fixity.lhs
index 2d47201..526f42b 100644
--- a/Language/SQL/SimpleSQL/Fixity.lhs
+++ b/Language/SQL/SimpleSQL/Fixity.lhs
@@ -4,7 +4,7 @@ trees for the operator precedence and associativity (aka 'fixity').
 
 It currently uses haskell-src-exts as a hack, the algorithm from there
 should be ported to work on these trees natively. Maybe it could be
-made generic?
+made generic to use in places other than the scalar expr parser?
 
 > {-# LANGUAGE TupleSections #-}
 > module Language.SQL.SimpleSQL.Fixity
diff --git a/Language/SQL/SimpleSQL/Parser.lhs b/Language/SQL/SimpleSQL/Parser.lhs
index cd5a72d..fa7785d 100644
--- a/Language/SQL/SimpleSQL/Parser.lhs
+++ b/Language/SQL/SimpleSQL/Parser.lhs
@@ -331,7 +331,8 @@ There aren't any multi keyword prefix operators currently supported.
 > prefixUnOpSymbolNames :: [String]
 > prefixUnOpSymbolNames = ["+", "-"]
 
-There aren't any single keyword postfix operators currently supported. Maybe all these 'is's can be left factored?
+There aren't any single keyword postfix operators currently
+supported. Maybe all these 'is's can be left factored?
 
 > postfixOpKeywords :: [String]
 > postfixOpKeywords = ["is null"
@@ -664,8 +665,12 @@ blacklist of keywords which aren't supported as identifiers.
 >     ,"when", "then", "case", "end", "in"
 >     ,"except", "intersect", "union"]
 
-TODO: talk about what must be in the blacklist, and what doesn't need
-to be.
+These blacklisted names are mostly needed when we parse something with
+an optional alias, e.g. select a a from t. If we write select a from
+t, we have to make sure the from isn't parsed as an alias. I'm not
+sure what other places strictly need the blacklist, and in theory it
+could be tuned differently for each place the identifierString/
+identifier parsers are used to only blacklist the bare minimum.
 
 String literals: limited at the moment, no escaping \' or other
 variations.
diff --git a/Language/SQL/SimpleSQL/Pretty.lhs b/Language/SQL/SimpleSQL/Pretty.lhs
index 3140ae6..7d85fb4 100644
--- a/Language/SQL/SimpleSQL/Pretty.lhs
+++ b/Language/SQL/SimpleSQL/Pretty.lhs
@@ -2,7 +2,9 @@
 This is the pretty printer code which takes AST values and turns them
 back into SQL source text. It attempts to format the output nicely.
 
-> -- | These is the pretty printing functions, which produce SQL source from ASTs. The code attempts to format the output in a readable way.
+> -- | These is the pretty printing functions, which produce SQL
+> -- source from ASTs. The code attempts to format the output in a
+> -- readable way.
 > module Language.SQL.SimpleSQL.Pretty
 >     (prettyQueryExpr
 >     ,prettyScalarExpr
@@ -21,7 +23,8 @@ back into SQL source text. It attempts to format the output nicely.
 > prettyScalarExpr :: ScalarExpr -> String
 > prettyScalarExpr = render . scalarExpr
 
-> -- | Convert a list of query exprs to concrete syntax. A semi colon is inserted following each query expr.
+> -- | Convert a list of query exprs to concrete syntax. A semi colon
+> -- is inserted after each query expr.
 > prettyQueryExprs :: [QueryExpr] -> String
 > prettyQueryExprs = render . vcat . map ((<> text ";\n") . queryExpr)
 
@@ -204,7 +207,8 @@ back into SQL source text. It attempts to format the output nicely.
 >               JCross -> text "cross"
 >           ,text "join"]
 >     joinCond (Just (JoinOn e)) = text "on" <+> scalarExpr e
->     joinCond (Just (JoinUsing es)) = text "using" <+> parens (commaSep $ map text es)
+>     joinCond (Just (JoinUsing es)) =
+>         text "using" <+> parens (commaSep $ map text es)
 >     joinCond Nothing = empty
 >     joinCond (Just JoinNatural) = empty
 
@@ -226,7 +230,6 @@ back into SQL source text. It attempts to format the output nicely.
 >     f (e,Asc) = scalarExpr e
 >     f (e,Desc) = scalarExpr e <+> text "desc"
 
-
 = utils
 
 > commaSep :: [Doc] -> Doc
diff --git a/Language/SQL/SimpleSQL/Syntax.lhs b/Language/SQL/SimpleSQL/Syntax.lhs
index 21c9686..6e58c30 100644
--- a/Language/SQL/SimpleSQL/Syntax.lhs
+++ b/Language/SQL/SimpleSQL/Syntax.lhs
@@ -20,99 +20,88 @@
 >     ) where
 
 > -- | Represents a scalar expression
-> data ScalarExpr = -- | a numeric literal optional decimal point, e+-
->                   -- integral exponent, e.g
->                   --
->                   -- * 10
->                   --
->                   -- * 10.
->                   --
->                   -- * .1
->                   --
->                   -- * 10.1
->                   --
->                   -- * 1e5
->                   --
->                   -- * 12.34e-6
->                   NumLit String
-
->                   -- | string literal, currently only basic strings
->                   -- between single quotes without escapes (no
->                   -- single quotes in strings then)
->                 | StringLit String
->                   -- | text of interval literal, units of interval
->                   -- precision, e.g. interval 3 days (3)
->                 | IntervalLit String
->                               String
->                               (Maybe Int)
->                   -- | identifier without dots
->                 | Iden String
->                   -- | identifier with one dot
->                 | Iden2 String String
->                   -- | star
->                 | Star
->                   -- | star with qualifier, e.g t.*
->                 | Star2 String
->                   -- | function application (anything that looks
->                   -- like c style function application syntactically)
->                 | App String [ScalarExpr]
->                   -- | aggregate application, which adds distinct or
->                   -- all, and order by, to regular function
->                   -- application
->                 | AggregateApp String (Maybe Duplicates)
->                                [ScalarExpr]
->                                [(ScalarExpr,Direction)]
->                   -- | window application, which adds over
->                   -- (partition by a order by b) to regular function
->                   -- application. Explicit frames are not currently
->                   -- supported
->                 | WindowApp String [ScalarExpr] [ScalarExpr] [(ScalarExpr,Direction)]
->                   -- | Infix binary operators. This is used for
->                   -- symbol operators (a + b), keyword operators (a
->                   -- and b) and multiple keyword operators (a is
->                   -- similar to b)
->                 | BinOp ScalarExpr String ScalarExpr
->                   -- | Prefix unary operators. This is used for
->                   -- symbol operators, keyword operators and
->                   -- multiple keyword operators
->                 | PrefixOp String ScalarExpr
->                   -- | Postfix unary operators. This is used for
->                   -- symbol operators, keyword operators and multiple
->                   -- keyword operators
->                 | PostfixOp String ScalarExpr
->                   -- | Used for ternary, mixfix and other non
->                   -- orthodox operators, including the function
->                   -- looking calls which use keywords instead of
->                   -- commas to separate the arguments,
->                   -- e.g. substring(t from 1 to 5)
->                 | SpecialOp String [ScalarExpr]
->                   -- | case expression. both flavours
->                   -- supported. Multiple condition when branches not
->                   -- currently supported (case when a=4,b=5 then x
->                   -- end)
->                 | Case (Maybe ScalarExpr) -- test value
->                        [(ScalarExpr,ScalarExpr)] -- when branches
->                        (Maybe ScalarExpr) -- else value
->                 | Parens ScalarExpr
->                   -- | cast(a as typename)
->                 | Cast ScalarExpr TypeName
->                   -- | prefix 'typed literal', e.g. int '42'
->                 | CastOp TypeName String
->                   -- | exists, all, any, some subqueries
->                 | SubQueryExpr SubQueryExprType QueryExpr
->                   -- | in list literal and in subquery, if the bool
->                   -- is false it means not in was used ('a not in
->                   -- (1,2)')
->                 | In Bool -- true if in, false if not in
->                      ScalarExpr InThing
->                   deriving (Eq,Show,Read)
+> data ScalarExpr
+>     = -- | a numeric literal optional decimal point, e+-
+>       -- integral exponent, e.g
+>       --
+>       -- * 10
+>       --
+>       -- * 10.
+>       --
+>       -- * .1
+>       --
+>       -- * 10.1
+>       --
+>       -- * 1e5
+>       --
+>       -- * 12.34e-6
+>       NumLit String
+>       -- | string literal, currently only basic strings between
+>       -- single quotes without escapes (no single quotes in strings
+>       -- then)
+>     | StringLit String
+>       -- | text of interval literal, units of interval precision,
+>       -- e.g. interval 3 days (3)
+>     | IntervalLit String String (Maybe Int)
+>       -- | identifier without dots
+>     | Iden String
+>       -- | identifier with one dot
+>     | Iden2 String String
+>       -- | star
+>     | Star
+>       -- | star with qualifier, e.g t.*
+>     | Star2 String
+>       -- | function application (anything that looks like c style
+>       -- function application syntactically)
+>     | App String [ScalarExpr]
+>       -- | aggregate application, which adds distinct or all, and
+>       -- order by, to regular function application
+>     | AggregateApp String (Maybe Duplicates)
+>                    [ScalarExpr]
+>                    [(ScalarExpr,Direction)]
+>       -- | window application, which adds over (partition by a order
+>       -- by b) to regular function application. Explicit frames are
+>       -- not currently supported
+>     | WindowApp String [ScalarExpr] [ScalarExpr] [(ScalarExpr,Direction)]
+>       -- | Infix binary operators. This is used for symbol operators
+>       -- (a + b), keyword operators (a and b) and multiple keyword
+>       -- operators (a is similar to b)
+>     | BinOp ScalarExpr String ScalarExpr
+>       -- | Prefix unary operators. This is used for symbol
+>       -- operators, keyword operators and multiple keyword operators
+>     | PrefixOp String ScalarExpr
+>       -- | Postfix unary operators. This is used for symbol
+>       -- operators, keyword operators and multiple keyword operators
+>     | PostfixOp String ScalarExpr
+>       -- | Used for ternary, mixfix and other non orthodox
+>       -- operators, including the function looking calls which use
+>       -- keywords instead of commas to separate the arguments,
+>       -- e.g. substring(t from 1 to 5)
+>     | SpecialOp String [ScalarExpr]
+>       -- | case expression. both flavours supported. Multiple
+>       -- condition when branches not currently supported (case when
+>       -- a=4,b=5 then x end)
+>     | Case (Maybe ScalarExpr) -- test value
+>            [(ScalarExpr,ScalarExpr)] -- when branches
+>            (Maybe ScalarExpr) -- else value
+>     | Parens ScalarExpr
+>       -- | cast(a as typename)
+>     | Cast ScalarExpr TypeName
+>       -- | prefix 'typed literal', e.g. int '42'
+>     | CastOp TypeName String
+>       -- | exists, all, any, some subqueries
+>     | SubQueryExpr SubQueryExprType QueryExpr
+>       -- | in list literal and in subquery, if the bool is false it
+>       -- means not in was used ('a not in (1,2)')
+>     | In Bool ScalarExpr InThing
+>       deriving (Eq,Show,Read)
 
 > -- | Represents a type name, used in casts.
 > data TypeName = TypeName String deriving (Eq,Show,Read)
 
 
 > -- | Used for 'expr in (scalar expression list)', and 'expr in
-> -- | (subquery)' syntax
+> -- (subquery)' syntax
 > data InThing = InList [ScalarExpr]
 >              | InQueryExpr QueryExpr
 >              deriving (Eq,Show,Read)
@@ -146,7 +135,8 @@
 > data QueryExpr
 >     = Select
 >       {qeDuplicates :: Duplicates
->       ,qeSelectList :: [(Maybe String,ScalarExpr)] -- ^ the column aliases and the expressions
+>       ,qeSelectList :: [(Maybe String,ScalarExpr)]
+>        -- ^ the column aliases and the expressions
 >       ,qeFrom :: [TableRef]
 >       ,qeWhere :: Maybe ScalarExpr
 >       ,qeGroupBy :: [ScalarExpr]
@@ -167,8 +157,7 @@
 
 TODO: add queryexpr parens to deal with e.g.
 (select 1 union select 2) union select 3
-I'm not sure if this is valid syntax or not
-
+I'm not sure if this is valid syntax or not.
 
 > -- | represents the Distinct or All keywords, which can be used
 > -- before a select list, in an aggregate/window function
@@ -182,7 +171,8 @@ I'm not sure if this is valid syntax or not
 > -- | Corresponding, an option for the set operators
 > data Corresponding = Corresponding | Respectively deriving (Eq,Show,Read)
 
-> -- | helper/'default' value for query exprs to make creating query expr values a little easier
+> -- | helper/'default' value for query exprs to make creating query
+> -- expr values a little easier
 > makeSelect :: QueryExpr
 > makeSelect = Select {qeDuplicates = All
 >                     ,qeSelectList = []
diff --git a/TODO b/TODO
index 3c6b71d..e1b75cd 100644
--- a/TODO
+++ b/TODO
@@ -1,9 +1,6 @@
 
-
 first release:
 
-check the pretty printer on the tpch queries
-fix the fixity issue
 add automated tests to cabal
 do code documentation and haddock
   check the order of exports, imports and functions/cases in the files