relude-0.7.0.0: Safe, performant, user-friendly and lightweight Haskell Standard Library
Copyright(c) 2016 Stephen Diehl
(c) 2016-2018 Serokell
(c) 2018-2020 Kowainik
LicenseMIT
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellTrustworthy
LanguageHaskell2010

Relude.Debug

Description

Functions for debugging and prototyping. If you leave these functions in your code then a warning is generated to remind you about left usages.

ghci> foo = trace "I forgot trace in code"

<interactive>:4:7: warning: [-Wdeprecations]
    In the use of ‘trace’ (imported from Relude):
    "trace remains in code"

⚠ NOTE: Use these functions only for debugging purposes. They break referential transparency, they are only useful when you want to observe intermediate values of your pure functions.

Synopsis

Tracing

trace :: String -> a -> a Source #

Warning: trace remains in code

Version of trace that leaves warning.

>>> increment l = map (+1) l
>>> increment [2, 3, 4]
[3,4,5]
>>> increment l = trace ("incrementing each value of: " ++ show l) (map (+1) l)
>>> increment [2, 3, 4]
incrementing each value of: [2,3,4]
[3,4,5]

traceM :: Applicative f => String -> f () Source #

Warning: traceM remains in code

Version of traceM that leaves warning.

>>> :{
let action :: Maybe Int
    action = do
        x <- Just 3
        traceM ("x: " ++ show x)
        y <- pure 12
        traceM ("y: " ++ show y)
        pure (x*2 + y)
in action
:}
x: 3
y: 12
Just 18

traceId :: String -> String Source #

Warning: traceId remains in code

Version of traceId that leaves warning.

>>> traceId "hello"
"hello
hello"

traceShow :: Show a => a -> b -> b Source #

Warning: traceShow remains in code

Version of traceShow that leaves warning.

>>> increment l = map (+1) l
>>> increment [2, 3, 4]
[3,4,5]
>>> increment l = traceShow l (map (+1) l)
>>> increment [2, 3, 4]
[2,3,4]
[3,4,5]

traceShowId :: Show a => a -> a Source #

Warning: traceShowId remains in code

Version of traceShowId that leaves warning.

>>> traceShowId (1+2+3, "hello" ++ "world")
(6,"helloworld")
(6,"helloworld")

traceShowM :: (Show a, Applicative f) => a -> f () Source #

Warning: traceShowM remains in code

Like traceM, but uses show on the argument to convert it to a String.

>>> :{
let action :: Maybe Int
    action = do
        x <- Just 3
        traceShowM x
        y <- pure 12
        traceShowM y
        pure (x*2 + y)
in action
:}
3
12
Just 18

Imprecise error

error :: forall (r :: RuntimeRep) (a :: TYPE r) (t :: Type). (HasCallStack, IsText t) => t -> a Source #

Throw pure errors. Use this function only to when you are sure that this branch of code execution is not possible. DO NOT USE error as a normal error handling mechanism.

>>> error "oops"
*** Exception: oops
CallStack (from HasCallStack):
  error, called at src/Relude/Debug.hs:218:11 in ...
...

⚠️CAUTION⚠️ Unlike Prelude version, error takes Text as an argument. In case it used by mistake, the user will see the following:

>>> error ("oops" :: String)
...
... 'error' expects 'Text' but was given 'String'.
      Possible fixes:
          * Make sure OverloadedStrings extension is enabled
          * Use 'error (toText msg)' instead of 'error msg'
...
>>> error False
...
... 'error' works with 'Text'
      But given: Bool
...

data Undefined Source #

Warning: Undefined type remains in code

Similar to undefined but data type.

Constructors

Undefined

Warning: Undefined type remains in code

Instances

Instances details
Bounded Undefined Source # 
Instance details

Defined in Relude.Debug

Enum Undefined Source # 
Instance details

Defined in Relude.Debug

Eq Undefined Source # 
Instance details

Defined in Relude.Debug

Data Undefined Source # 
Instance details

Defined in Relude.Debug

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Undefined -> c Undefined #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Undefined #

toConstr :: Undefined -> Constr #

dataTypeOf :: Undefined -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Undefined) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Undefined) #

gmapT :: (forall b. Data b => b -> b) -> Undefined -> Undefined #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Undefined -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Undefined -> r #

gmapQ :: (forall d. Data d => d -> u) -> Undefined -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Undefined -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Undefined -> m Undefined #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Undefined -> m Undefined #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Undefined -> m Undefined #

Ord Undefined Source # 
Instance details

Defined in Relude.Debug

Read Undefined Source # 
Instance details

Defined in Relude.Debug

Show Undefined Source # 
Instance details

Defined in Relude.Debug

Generic Undefined Source # 
Instance details

Defined in Relude.Debug

Associated Types

type Rep Undefined :: Type -> Type #

type Rep Undefined Source # 
Instance details

Defined in Relude.Debug

type Rep Undefined = D1 ('MetaData "Undefined" "Relude.Debug" "relude-0.7.0.0-inplace" 'False) (C1 ('MetaCons "Undefined" 'PrefixI 'False) (U1 :: Type -> Type))

undefined :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => a Source #

Warning: undefined function remains in code

undefined that leaves warning in code on every usage.