Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- cn :: v -> CN v
- unCN :: CN p -> p
- type CN = CollectErrors NumErrors
- newtype NumErrors = NumErrors (Set NumErrorLevel)
- type NumErrorLevel = (NumError, ErrorCertaintyLevel)
- data NumError
- data ErrorCertaintyLevel
- noValueNumErrorCertain :: NumError -> CN v
- noValueNumErrorPotential :: NumError -> CN v
- removeValueErrorCertain :: CN t -> NumError -> CN t
- removeValueErrorPotential :: CN t -> NumError -> CN t
- prependErrorCertain :: NumError -> CN t -> CN t
- prependErrorPotential :: NumError -> CN t -> CN t
- class CanClearPotentialErrors cnt where
- clearPotentialErrors :: cnt -> cnt
- liftCN :: (a -> CN c) -> CN a -> CN c
- lift2CN :: (a -> b -> CN c) -> CN a -> CN b -> CN c
- lift1TCN :: (a -> b -> CN c) -> CN a -> b -> CN c
- liftT1CN :: (a -> b -> CN c) -> a -> CN b -> CN c
- type CanTakeCNErrors = CanTakeErrors NumErrors
Documentation
type CN = CollectErrors NumErrors Source #
Instances
type NumErrorLevel = (NumError, ErrorCertaintyLevel) Source #
Instances
Eq NumError Source # | |
Ord NumError Source # | |
Defined in Numeric.CollectErrors.Type | |
Show NumError Source # | |
Generic NumError Source # | |
NFData NumError Source # | |
Defined in Numeric.CollectErrors.Type | |
CanTestErrorsCertain NumErrorLevel Source # | |
Defined in Numeric.CollectErrors.Type hasCertainError :: NumErrorLevel -> Bool Source # | |
type Rep NumError Source # | |
Defined in Numeric.CollectErrors.Type type Rep NumError = D1 ('MetaData "NumError" "Numeric.CollectErrors.Type" "collect-errors-0.1.5.0-DAyNZ8BMV4w4yqJNdU6hiq" 'False) (C1 ('MetaCons "DivByZero" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OutOfDomain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "NumError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
data ErrorCertaintyLevel Source #
Instances
noValueNumErrorCertain :: NumError -> CN v Source #
Construct an empty wrapper indicating that given error has certainly occurred.
noValueNumErrorPotential :: NumError -> CN v Source #
Construct an empty wrapper indicating that given error may have occurred.
class CanClearPotentialErrors cnt where Source #
clearPotentialErrors :: cnt -> cnt Source #
If there is a value, remove any potential errors that are associated with it.
Instances
CanClearPotentialErrors t => CanClearPotentialErrors [t] Source # | |
Defined in Numeric.CollectErrors.Type clearPotentialErrors :: [t] -> [t] Source # | |
CanClearPotentialErrors (CN t) Source # | |
Defined in Numeric.CollectErrors.Type clearPotentialErrors :: CN t -> CN t Source # | |
(CanClearPotentialErrors t1, CanClearPotentialErrors t2) => CanClearPotentialErrors (t1, t2) Source # | |
Defined in Numeric.CollectErrors.Type clearPotentialErrors :: (t1, t2) -> (t1, t2) Source # |
type CanTakeCNErrors = CanTakeErrors NumErrors Source #