universum-1.0.0: 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

Bounded Undefined Source # 
Enum Undefined Source # 
Eq Undefined Source # 
Data Undefined Source # 

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 :: (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 # 
Read Undefined Source # 
Show Undefined Source # 
Generic Undefined Source # 

Associated Types

type Rep Undefined :: * -> * #

type Rep Undefined Source # 
type Rep Undefined = D1 (MetaData "Undefined" "Universum.Debug" "universum-1.0.0-DBFfqwqIraF5jHeOCd7s0l" False) (C1 (MetaCons "Undefined" PrefixI False) U1)

error :: forall r. forall a. HasCallStack => Text -> a Source #

error that takes Text as an argument.

trace :: Print b => b -> a -> a Source #

Warning: trace remains in code

Generalized over string version of trace that leaves warnings.

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

Warning: traceM remains in code

Version of traceM that leaves warning and takes Text.

traceId :: Text -> Text Source #

Warning: traceId remains in code

Version of traceId that leaves warning and takes Text.

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

Warning: traceShow remains in code

Version of traceShow that leaves warning.

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

Warning: traceShowId remains in code

Version of traceShow that leaves warning.

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

Warning: traceShowM remains in code

Version of traceShowM that leaves warning.

undefined :: forall r. forall a. HasCallStack => a Source #

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

undefined that leaves warning in code on every usage.