| Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2019 Kowainik | 
|---|---|
| License | MIT | 
| Maintainer | Kowainik <xrom.xkov@gmail.com> | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
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.
Use these functions only for debugging purposes. They break referential trasparency, they are only useful when you want to observe intermediate values of your pure functions.
Synopsis
- trace :: String -> a -> a
- traceM :: Applicative f => String -> f ()
- traceId :: String -> String
- traceShow :: Show a => a -> b -> b
- traceShowId :: Show a => a -> a
- traceShowM :: (Show a, Applicative f) => a -> f ()
- error :: forall (r :: RuntimeRep) (a :: TYPE r) (t :: Type). (HasCallStack, IsText t) => t -> a
- data Undefined = Undefined
- undefined :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => a
Tracing
traceM :: Applicative f => String -> f () Source #
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:204: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 ...
Instances
| Bounded Undefined Source # | |
| Enum Undefined Source # | |
| Defined in Relude.Debug Methods succ :: Undefined -> Undefined # pred :: Undefined -> Undefined # fromEnum :: Undefined -> Int # enumFrom :: Undefined -> [Undefined] # enumFromThen :: Undefined -> Undefined -> [Undefined] # enumFromTo :: Undefined -> Undefined -> [Undefined] # enumFromThenTo :: Undefined -> Undefined -> Undefined -> [Undefined] # | |
| Eq Undefined Source # | |
| Data Undefined Source # | |
| 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 # | |
| Read Undefined Source # | |
| Show Undefined Source # | |
| Generic Undefined Source # | |
| type Rep Undefined Source # | |
undefined :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => a Source #