diff --git a/src/Mtlstats/Config.hs b/src/Mtlstats/Config.hs
index e9600be..e02aacc 100644
--- a/src/Mtlstats/Config.hs
+++ b/src/Mtlstats/Config.hs
@@ -19,7 +19,7 @@ along with this program.  If not, see <https://www.gnu.org/licenses/>.
 
 -}
 
-module Mtlstats.Config (myTeam) where
+module Mtlstats.Config where
 
 -- | The name of the team whose stats we're tracking
 myTeam :: String
diff --git a/src/Mtlstats/Events.hs b/src/Mtlstats/Events.hs
index d7d031d..0b1bdc7 100644
--- a/src/Mtlstats/Events.hs
+++ b/src/Mtlstats/Events.hs
@@ -71,7 +71,9 @@ handleEvent e = gets (view progMode) >>= \case
         >>= modify . (progMode.gameStateL.overtimeFlag .~)
       modify updateGameStats
       return True
-    | otherwise -> undefined
+    | otherwise -> do
+      modify $ progMode .~ MainMenu
+      return True
 
 overtimePrompt :: C.Event -> Action (Maybe Bool)
 overtimePrompt (C.EventCharacter c) = case toUpper c of
diff --git a/src/Mtlstats/Report.hs b/src/Mtlstats/Report.hs
new file mode 100644
index 0000000..cf93da5
--- /dev/null
+++ b/src/Mtlstats/Report.hs
@@ -0,0 +1,90 @@
+{- |
+
+mtlstats
+Copyright (C) 2019 Rhéal Lamothe
+<rheal.lamothe@gmail.com>
+
+This program is free software: you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation, either version 3 of the License, or (at
+your option) any later version.
+
+This program is distributed in the hope that it will be useful, but
+WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with this program.  If not, see <https://www.gnu.org/licenses/>.
+
+-}
+
+module Mtlstats.Report (report) where
+
+import Data.Maybe (fromMaybe)
+import Lens.Micro ((^.))
+
+import Mtlstats.Config
+import Mtlstats.Format
+import Mtlstats.Types
+
+-- | Generates the report
+report
+  :: Int
+  -- ^ The number of columns for the report
+  -> ProgState
+  -- ^ The program state
+  -> String
+report width s = unlines $ fromMaybe [] $ do
+  let
+    db     = s^.database
+    gs     = s^.progMode.gameStateL
+    gNum   = db^.dbGames
+    hTeam  = homeTeam gs
+    aTeam  = awayTeam gs
+    hStats = db^.dbHomeGameStats
+    aStats = db^.dbAwayGameStats
+    tStats = addGameStats hStats aStats
+  hScore <- gs^.homeScore
+  aScore <- gs^.awayScore
+  month  <- month <$> gs^.gameMonth
+  day    <- padNum 2 <$> gs^.gameDay
+  year   <- show <$> gs^.gameYear
+  let date = month ++ " " ++ day ++ " " ++ year
+  Just
+    [ overlay
+      ("GAME NUMBER " ++ padNum 2 gNum)
+      (centre width
+        $  aTeam ++ " " ++ show aScore ++ "  AT  "
+        ++ hTeam ++ " " ++ show hScore)
+    , date
+    , centre width "STANDINGS"
+    , ""
+    , centre width
+      $  left 11 myTeam
+      ++ right 2 "G"
+      ++ right 4 "W"
+      ++ right 4 "L"
+      ++ right 4 "OT"
+      ++ right 4 "P"
+    , centre width
+      $  left 11 "HOME"
+      ++ showStats hStats
+    , centre width
+      $ left 11 "ROAD"
+      ++ showStats aStats
+    , centre width
+      $  replicate 11 ' '
+      ++ replicate (2 + 4 * 4) '-'
+    , centre width
+      $  left 11 "TOTALS"
+      ++ showStats tStats
+    ]
+
+showStats :: GameStats -> String
+showStats gs
+  =  right 2 (show $ gmsGames gs)
+  ++ right 4 (show $ gs^.gmsWins)
+  ++ right 4 (show $ gs^.gmsLosses)
+  ++ right 4 (show $ gs^.gmsOvertime)
+  ++ right 4 (show $ gmsPoints gs)
diff --git a/src/Mtlstats/UI.hs b/src/Mtlstats/UI.hs
index 1b1977e..0bffbcd 100644
--- a/src/Mtlstats/UI.hs
+++ b/src/Mtlstats/UI.hs
@@ -28,6 +28,7 @@ import qualified UI.NCurses as C
 import Mtlstats.Format
 import Mtlstats.Menu
 import Mtlstats.Prompt
+import Mtlstats.Report
 import Mtlstats.Types
 
 -- | Drawing function
@@ -49,7 +50,7 @@ draw s = do
         | null $ gs^.homeScore    -> header s >> drawPrompt homeScorePrompt s
         | null $ gs^.awayScore    -> header s >> drawPrompt awayScorePrompt s
         | null $ gs^.overtimeFlag -> header s >> overtimePrompt
-        | otherwise               -> undefined
+        | otherwise               -> showReport s
   C.render
   void $ C.setCursorMode cm
 
@@ -61,3 +62,8 @@ overtimePrompt :: C.Update C.CursorMode
 overtimePrompt = do
   C.drawString "Did the game go into overtime?  (Y/N)"
   return C.CursorInvisible
+
+showReport :: ProgState -> C.Update C.CursorMode
+showReport s = do
+  C.drawString $ report 72 s
+  return C.CursorInvisible