relude-0.4.0: Custom prelude from Kowainik

Copyright(c) 2016 Stephen Diehl
(c) 20016-2018 Serokell
(c) 2018 Kowainik
LicenseMIT
MaintainerKowainik <xrom.xkov@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010

Relude.Debug

Contents

Description

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

Synopsis

Tracing

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

Warning: trace remains in code

Version of trace that leaves warning.

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

Warning: traceM remains in code

Version of traceM that leaves warning.

traceId :: String -> String Source #

Warning: traceId remains in code

Version of traceId that leaves warning.

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 traceShowId that leaves warning.

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

Warning: traceShowM remains in code

Version of traceShowM that leaves warning.

Imprecise error

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

error that takes Text as an argument.

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 # 
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 :: (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.4.0-Lxt6LRLYnzv5tbWxOcbEci" 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.