Monadify deSugar/DsGRHSs: use do, return, applicative, standard monad functions
[ghc-hetmet.git] / compiler / deSugar / DsGRHSs.lhs
index 4daab97..db5cc0c 100644 (file)
@@ -33,6 +33,8 @@ import PrelNames
 import Name
 import SrcLoc
 
+import Control.Monad ((>=>))
+
 \end{code}
 
 @dsGuarded@ is used for both @case@ expressions and pattern bindings.
@@ -49,9 +51,9 @@ necessary.  The type argument gives the type of the @ei@.
 \begin{code}
 dsGuarded :: GRHSs Id -> Type -> DsM CoreExpr
 
-dsGuarded grhss rhs_ty
-  = dsGRHSs PatBindRhs [] grhss rhs_ty                                 `thenDs` \ match_result ->
-    mkErrorAppDs nON_EXHAUSTIVE_GUARDS_ERROR_ID rhs_ty ""      `thenDs` \ error_expr ->
+dsGuarded grhss rhs_ty = do
+    match_result <- dsGRHSs PatBindRhs [] grhss rhs_ty
+    error_expr <- mkErrorAppDs nON_EXHAUSTIVE_GUARDS_ERROR_ID rhs_ty ""
     extractMatchResult match_result error_expr
 \end{code}
 
@@ -63,7 +65,7 @@ dsGRHSs :: HsMatchContext Name -> [Pat Id]    -- These are to build a MatchContext
        -> Type                                 -- Type of RHS
        -> DsM MatchResult
 dsGRHSs hs_ctx pats grhssa@(GRHSs grhss binds) rhs_ty = do
-    match_results <- mappM (dsGRHS hs_ctx pats rhs_ty) grhss
+    match_results <- mapM (dsGRHS hs_ctx pats rhs_ty) grhss
     let 
        match_result1 = foldr1 combineMatchResults match_results
        match_result2 = adjustMatchResultDs 
@@ -71,7 +73,7 @@ dsGRHSs hs_ctx pats grhssa@(GRHSs grhss binds) rhs_ty = do
                                  match_result1
                -- NB: nested dsLet inside matchResult
     --
-    returnDs match_result2
+    return match_result2
 
 dsGRHS hs_ctx pats rhs_ty (L loc (GRHS guards rhs))
   = matchGuards (map unLoc guards) hs_ctx rhs rhs_ty
@@ -106,25 +108,25 @@ matchGuards [] ctx rhs rhs_ty
        --      wrapping the 'otherwise' in empty HsTyApp or HsWrap constructors
        --      If it does, you'll get bogus overlap warnings
 matchGuards (ExprStmt e _ _ : stmts) ctx rhs rhs_ty
-  | Just addTicks <- isTrueLHsExpr e
-  = matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
-    returnDs (adjustMatchResultDs addTicks match_result)
-matchGuards (ExprStmt expr _ _ : stmts) ctx rhs rhs_ty
-  = matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
-    dsLExpr expr                       `thenDs` \ pred_expr ->
-    returnDs (mkGuardedMatchResult pred_expr match_result)
-
-matchGuards (LetStmt binds : stmts) ctx rhs rhs_ty
-  = matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
-    returnDs (adjustMatchResultDs (dsLocalBinds binds) match_result)
+  | Just addTicks <- isTrueLHsExpr e = do
+    match_result <- matchGuards stmts ctx rhs rhs_ty
+    return (adjustMatchResultDs addTicks match_result)
+matchGuards (ExprStmt expr _ _ : stmts) ctx rhs rhs_ty = do
+    match_result <- matchGuards stmts ctx rhs rhs_ty
+    pred_expr <- dsLExpr expr
+    return (mkGuardedMatchResult pred_expr match_result)
+
+matchGuards (LetStmt binds : stmts) ctx rhs rhs_ty = do
+    match_result <- matchGuards stmts ctx rhs rhs_ty
+    return (adjustMatchResultDs (dsLocalBinds binds) match_result)
        -- NB the dsLet occurs inside the match_result
        -- Reason: dsLet takes the body expression as its argument
        --         so we can't desugar the bindings without the
        --         body expression in hand
 
-matchGuards (BindStmt pat bind_rhs _ _ : stmts) ctx rhs rhs_ty
-  = matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
-    dsLExpr bind_rhs                   `thenDs` \ core_rhs ->
+matchGuards (BindStmt pat bind_rhs _ _ : stmts) ctx rhs rhs_ty = do
+    match_result <- matchGuards stmts ctx rhs rhs_ty
+    core_rhs <- dsLExpr bind_rhs
     matchSinglePat core_rhs ctx pat rhs_ty match_result
 
 isTrueLHsExpr :: LHsExpr Id -> Maybe (CoreExpr -> DsM CoreExpr)
@@ -136,19 +138,15 @@ isTrueLHsExpr :: LHsExpr Id -> Maybe (CoreExpr -> DsM CoreExpr)
 -- The arguments to Just are any HsTicks that we have found,
 -- because we still want to tick then, even it they are aways evaluted.
 isTrueLHsExpr (L _ (HsVar v)) |  v `hasKey` otherwiseIdKey
-                             || v `hasKey` getUnique trueDataConId     
-                                      = Just returnDs
+                              || v `hasKey` getUnique trueDataConId
+                                      = Just return
        -- trueDataConId doesn't have the same unique as trueDataCon
-isTrueLHsExpr (L loc (HsTick    ix frees e)) 
-    | Just ticks <- isTrueLHsExpr e   = Just (\ e1 -> 
-                            ticks e1 `thenDs` \ e2 -> 
-                            mkTickBox ix frees e2)
+isTrueLHsExpr (L loc (HsTick    ix frees e))
+    | Just ticks <- isTrueLHsExpr e   = Just (ticks >=> mkTickBox ix frees)
    -- This encodes that the result is constant True for Hpc tick purposes;
    -- which is specifically what isTrueLHsExpr is trying to find out.
 isTrueLHsExpr (L loc (HsBinTick ixT _ e))
-    | Just ticks <- isTrueLHsExpr e   = Just (\ e1 -> 
-                            ticks e1 `thenDs` \ e2 -> 
-                            mkTickBox ixT [] e2)
+    | Just ticks <- isTrueLHsExpr e   = Just (ticks >=> mkTickBox ixT [])
 isTrueLHsExpr (L _ (HsPar e))         = isTrueLHsExpr e
 isTrueLHsExpr other = Nothing
 \end{code}