{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
#if MIN_VERSION_base(4,9,0)
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
#endif

module Protolude.Panic (
  FatalError(FatalError, fatalErrorMessage),
  panic,
) where

import Protolude.Base (Show)
import Protolude.CallStack (HasCallStack)
import Data.Text (Text)
import Data.Typeable (Typeable)
import Control.Exception as X

-- | Uncatchable exceptions thrown and never caught.
newtype FatalError = FatalError { FatalError -> Text
fatalErrorMessage :: Text }
  deriving (Int -> FatalError -> ShowS
[FatalError] -> ShowS
FatalError -> String
(Int -> FatalError -> ShowS)
-> (FatalError -> String)
-> ([FatalError] -> ShowS)
-> Show FatalError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FatalError] -> ShowS
$cshowList :: [FatalError] -> ShowS
show :: FatalError -> String
$cshow :: FatalError -> String
showsPrec :: Int -> FatalError -> ShowS
$cshowsPrec :: Int -> FatalError -> ShowS
Show, Typeable)

instance Exception FatalError

panic :: HasCallStack => Text -> a
panic :: Text -> a
panic Text
a = FatalError -> a
forall a e. Exception e => e -> a
throw (Text -> FatalError
FatalError Text
a)