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

Relude.Debug

Description

This module contains functions for debugging pure functions. You can't use functions like putStrLn for this purpose because they require changes to the type signature, but functions in this module avoid this problem by being pure on their own.

Additionally, these functions produce compile-time warnings, if you leave them in your code. Warnings help you to cleanup all debugging usages before releasing.

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"

The following table briefly shows names and types of all functions in this module.

NameType
traceString -> a -> a
traceShowShow a => a -> b -> b
traceShowIdShow a => a -> a
traceShowWithShow b => (a -> b) -> a -> a
traceIdString -> String
traceM(Applicative f) => String -> f ()
traceShowM(Show a, Applicative f) => a -> f ()

⚠ NOTE: Use these functions only for local debugging purposes. They break referential transparency, they are only useful when you want to observe intermediate values of your pure functions and to understand the behaviour locally. If you want to log debug messages in your application, consider using a logging library instead.

Synopsis

Tracing

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

Warning: trace remains in code

Prints the given String message and returns the passed value of type a.

>>> 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]

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

Warning: traceShow remains in code

Similar to trace but prints a given value with the Show instance instead of a String.

>>> 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]
  • If you want to print a specific String instead, use trace
  • If you want to print and return the same value, use traceShowId
  • If you want to specify a custom printing function, use traceShowWith

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

Warning: traceShowId remains in code

Similar to traceShow but prints the given value itself instead of a separate value.

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

traceShowWith :: Show b => (a -> b) -> a -> a Source #

Warning: 'traceShowWith remains in code

Similar traceShowId, but uses a provided function to convert the argument to a value with the Show constraint.

>>> traceShowWith fst (1, "ABC")
1
(1,"ABC")

In other words, traceShowIdtraceShowWith id.

This function is useful for debugging values that do not have Show instance:

>>> fst $ traceShowWith fst (1, id)
1
1

Since: 1.0.0.0

traceId :: String -> String Source #

Warning: traceId remains in code

Similar to traceShowId but specialised for String.

>>> traceId "hello"
"hello
hello"

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

Warning: traceM remains in code

Trace function to print values while working a pure monad (e.g. Maybe, State, etc.)

>>> :{
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
  • If you want to print a value with the Show instance instead, use traceShowM

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:289: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-1.1.0.0-C4Ifgx5VjPrF7hvzbaqKEV" '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.