@@ -43,9 +43,13 @@ withScopedTmpName l f = do
4343 local (\ r -> DesugarReader $ readerNameDepth r + 1 ) $
4444 f $ Ident l $ " $gen" ++ show n
4545
46- desugar :: Module l -> IO (Either CompileError (Module l ))
46+
47+ -- | Top level, desugar a whole module possibly returning errors
48+ desugar :: Module l -> IO (Either CompileError (Module l ))
4749desugar md = runDesugar (desugarModule md)
4850
51+ -- | Desugaring
52+
4953desugarModule :: Module l -> Desugar (Module l )
5054desugarModule m = case m of
5155 Module l h ps is decls -> Module l h ps is <$> mapM desugarDecl decls
@@ -82,13 +86,16 @@ desugarGuardedRhs g = case g of
8286
8387desugarExp :: Exp l -> Desugar (Exp l )
8488desugarExp ex = case ex of
89+ -- (a `f`) => (\b -> f a b)
8590 LeftSection l e q -> desugarExp =<<
8691 (withScopedTmpName l $ \ v ->
8792 return $ Lambda l [PVar l v] (InfixApp l e q (Var l (UnQual l v))))
93+ -- (`f` b) => (\a -> f a b)
8894 RightSection l q e -> desugarExp =<<
8995 (withScopedTmpName l $ \ tmp ->
9096 return (Lambda l [PVar l tmp] (InfixApp l (Var l (UnQual l tmp)) q e)))
9197
98+ -- Check for TupleCon
9299 Var _ q -> return $ desugarVar ex q
93100 Con _ q -> return $ desugarVar ex q
94101
@@ -135,6 +142,7 @@ desugarExp ex = case ex of
135142 CorePragma {} -> return ex
136143 SCCPragma {} -> return ex
137144
145+ -- | Convert do notation into binds and thens.
138146desugarStmt' :: Maybe (Exp l ) -> (Stmt l ) -> Maybe (Exp l )
139147desugarStmt' inner stmt =
140148 maybe initStmt subsequentStmt inner
@@ -163,7 +171,7 @@ desugarStmt' inner stmt =
163171
164172desugarPat :: Pat l -> Desugar (Pat l )
165173desugarPat pt = case pt of
166- -- Remove parens
174+ -- (p) => p
167175 PParen _ p -> desugarPat p
168176
169177 PVar l n -> return $ PVar l (desugarName n)
@@ -185,8 +193,10 @@ desugarPat pt = case pt of
185193
186194desugarPatField :: PatField l -> Desugar (PatField l )
187195desugarPatField pf = case pf of
188- PFieldPat l q p -> PFieldPat l (desugarQName q) <$> desugarPat p
196+ -- {a} => {a=a} for R{a}
189197 PFieldPun l n -> let dn = desugarName n in desugarPatField $ PFieldPat l (UnQual l dn) (PVar l dn)
198+
199+ PFieldPat l q p -> PFieldPat l (desugarQName q) <$> desugarPat p
190200 PFieldWildcard l -> return $ PFieldWildcard l
191201
192202desugarGuardedAlts :: GuardedAlts l -> Desugar (GuardedAlts l )
@@ -246,7 +256,7 @@ desugarVar e q = case q of
246256 Special _ t@ TupleCon {} -> fromMaybe e $ desugarTupleCon t
247257 _ -> e
248258
249- -- | Turn a tuple constructor into a normal lambda expression.
259+ -- | (,) => \x y -> (x,y)
250260desugarTupleCon :: SpecialCon l -> Maybe (Exp l )
251261desugarTupleCon s = case s of
252262 TupleCon l b n -> Just $ Lambda l params body
0 commit comments