universum-1.8.1.1: Custom prelude used in Serokell
Safe HaskellTrustworthy
LanguageHaskell2010

Universum.Debug

Description

Functions for debugging. If you left these functions in your code then warning is generated to remind you about left usages. Also, some functions (and data types) are convenient for prototyping.

Synopsis

Documentation

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
Data Undefined Source # 
Instance details

Defined in Universum.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 #

Bounded Undefined Source # 
Instance details

Defined in Universum.Debug

Enum Undefined Source # 
Instance details

Defined in Universum.Debug

Generic Undefined Source # 
Instance details

Defined in Universum.Debug

Associated Types

type Rep Undefined :: Type -> Type #

Read Undefined Source # 
Instance details

Defined in Universum.Debug

Show Undefined Source # 
Instance details

Defined in Universum.Debug

Eq Undefined Source # 
Instance details

Defined in Universum.Debug

Ord Undefined Source # 
Instance details

Defined in Universum.Debug

type Rep Undefined Source # 
Instance details

Defined in Universum.Debug

type Rep Undefined = D1 ('MetaData "Undefined" "Universum.Debug" "universum-1.8.1.1-LXuA8dJo1HpB0J7TJWAM7h" 'False) (C1 ('MetaCons "Undefined" 'PrefixI 'False) (U1 :: Type -> Type))

error :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => Text -> a Source #

error that takes Text as an argument.

trace :: Text -> a -> a Source #

Warning: trace remains in code

Version of trace that leaves a warning and takes Text.

traceM :: Monad m => Text -> m () Source #

Warning: traceM remains in code

Version of traceM that leaves a warning and takes Text.

traceId :: Text -> Text Source #

Warning: traceId remains in code

Version of traceId that leaves a warning.

traceIdWith :: (a -> Text) -> a -> a Source #

Warning: traceIdWith remains in code

Version of traceId that leaves a warning. Useful to tag printed data, for instance:

traceIdWith (x -> "My data: " <> show x) (veryLargeExpression)

This is especially useful with custom formatters:

traceIdWith (x -> "My data: " <> pretty x) (veryLargeExpression)

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

Warning: traceShow remains in code

Version of traceShow that leaves a warning.

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

Warning: traceShowId remains in code

Version of traceShowId that leaves a warning.

traceShowIdWith :: Show s => (a -> s) -> a -> a Source #

Warning: traceShowIdWith remains in code

Version of traceShowId that leaves a warning. Useful to tag printed data, for instance:

traceShowIdWith ("My data: ", ) (veryLargeExpression)

traceShowM :: (Show a, Monad m) => a -> m () Source #

Warning: traceShowM remains in code

Version of traceShowM that leaves a warning.

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

Warning: undefined function remains in code (or use error)

undefined that leaves a warning in code on every usage.