Error 'Oops! Entered absent arg' when building code with -O2
Summary
I have a code snippet that should pretty-print some data types as a table to terminal. Unfortunately, when compiling the code with optimizations enabled (-O2
option), I see the following runtime error:
Main: Oops! Entered absent arg moduleLen Int
I tried to minimize my example as much as I could, and below is the code that triggers the error:
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -O2 #-}
module Main (main) where
import Data.IORef (IORef, newIORef, readIORef)
import Data.Semigroup (Max (..))
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
data LogRecord = LogRecord
{ logRecordModule :: !Text
, logRecordLine :: !Int
} deriving stock (Eq, Ord)
-- | Single text row in results
data Row = Row
{ rowModule :: !Text
, rowLine :: !Text
}
prettyPrintLogStats :: [LogRecord] -> Text
prettyPrintLogStats rawResults = Text.unlines $ columnsToRows columns
where
columns :: [Row]
columns = map toRow rawResults
columnsToRows :: [Row] -> [Text]
columnsToRows rows = map toRow rows
where
moduleLen, lineLen :: Int
(Max moduleLen, Max lineLen) = foldMap
(\Row{..} ->
( Max $ Text.length rowModule
, Max $ Text.length rowLine
)
)
rows
pad :: Int -> Text -> Text
pad len = Text.justifyLeft len ' '
toRow :: Row -> Text
toRow Row{..} =
"| " <> pad moduleLen rowModule
<> " | " <> pad lineLen rowLine
<> " |"
toRow :: LogRecord -> Row
toRow LogRecord{..} = Row
{ rowModule = logRecordModule
, rowLine = Text.pack $ show logRecordLine
}
dumpLogsTimings :: IORef [LogRecord] -> IO ()
dumpLogsTimings timingsRef = do
timings <- readIORef timingsRef
Text.putStrLn $ prettyPrintLogStats timings
main :: IO ()
main = do
let timings = [LogRecord "" 0]
timingsRef <- newIORef timings
dumpLogsTimings timingsRef
If you look at generated core, you can actually see that absentError
is evaluated when it should not:
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
lvl12 :: Addr#
lvl12 = "lineLen Int"#
-- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0}
lineLen :: Int
lineLen = absentError lvl12
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
lvl13 :: Addr#
lvl13 = "moduleLen Int"#
-- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0}
moduleLen :: Int
moduleLen = absentError lvl13
A few additional notes:
- Removing
IORef
makes the error disappear. - Replacing a pair with a custom data type doesn't help. The error becomes even more mysterious:
Main: Oops! Entered absent arg lvl Int
lvl
in the code)
Steps to reproduce
- Build the above
Main.hs
:ghc Main.hs
- Run it:
./Main
Expected behavior
No runtime errors.
Environment
- GHC version used: GHC 8.10.1 (also reproducible with GHC 8.8.3)
Optional:
- Operating System: RH6
- System Architecture: x86_64
cc @adamse