| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Model.Util
- properMutualGroups :: (Ord r, Pretty r, Foldable t) => (a -> Maybe r) -> Map r (t a) -> Either [String] [[r]]
- mutualGroups :: (Ord r, Pretty r, Foldable t) => (a -> Maybe r) -> Map r (t a) -> Either [String] [[r]]
- transitiveClosure :: (Foldable t, Pretty r, Ord r) => (a -> Maybe r) -> Map r (t a) -> r -> Either [String] [r]
- type Errors = [Error]
- toErrors :: Bifunctor p => p a c -> p [a] c
- noErrors :: Errors -> Bool
- errsInContext :: (Convertible ctx String, Bifunctor p) => ctx -> p [String] c -> p [String] c
- inContext :: Convertible ctx String => ctx -> [String] -> [String]
- errorToConvertResult :: (Typeable b, Typeable a, Show a) => (a -> Either Error b) -> a -> ConvertResult b
- errorsToConvertResult :: (Typeable b, Typeable t, Show t) => (t -> Either Errors b) -> t -> ConvertResult b
- convertResultToError :: Bifunctor p => p ConvertError c -> p String c
- convertResultToErrors :: Bifunctor p => p ConvertError c -> p [String] c
- convertOrError :: Convertible a c => a -> Either String c
- class Convertible a b where
- convert :: Convertible a b => a -> b
- type ConvertResult a = Either ConvertError a
- data ConvertError :: * = ConvertError {}
- dotted :: [String] -> String
Dependencies
properMutualGroups :: (Ord r, Pretty r, Foldable t) => (a -> Maybe r) -> Map r (t a) -> Either [String] [[r]] Source #
Return the groups of mutually dependent entities, with more than one component
>>>properMutualGroups Just (M.fromList [("a",["b","c"]),("b",["a","c"]),("c",[])])Right [["b","a"]]
mutualGroups :: (Ord r, Pretty r, Foldable t) => (a -> Maybe r) -> Map r (t a) -> Either [String] [[r]] Source #
Return the groups of mutually dependent entities
>>>mutualGroups Just (M.fromList [("a",["b","c"]),("b",["a","c"]),("c",[])])Right [["c"],["b","a"]]
transitiveClosure :: (Foldable t, Pretty r, Ord r) => (a -> Maybe r) -> Map r (t a) -> r -> Either [String] [r] Source #
Return the transitive closure of an element in a graph of dependencies specified as an adjacency list
>>>transitiveClosure Just (M.fromList [("a",["b","c"]),("b",["b","d","d","c"]),("c",[]),("d",["a"])]) "b"Right ["c","a","d","b"]
>>>transitiveClosure Just (M.fromList [("a",["b","c"]),("b",["b","d","d","c"]),("c",[]),("d",["a"])]) "c"Right ["c"]
Error utilities
errsInContext :: (Convertible ctx String, Bifunctor p) => ctx -> p [String] c -> p [String] c Source #
Prefix errors with a contextual note
inContext :: Convertible ctx String => ctx -> [String] -> [String] Source #
Prefix a list of strings with a contextual note
>>>inContext "0/0" ["Zero denominator"]["In 0/0: Zero denominator"]
errorToConvertResult :: (Typeable b, Typeable a, Show a) => (a -> Either Error b) -> a -> ConvertResult b Source #
errorsToConvertResult :: (Typeable b, Typeable t, Show t) => (t -> Either Errors b) -> t -> ConvertResult b Source #
>>>errorsToConvertResult (const (Left ["Bad format","Invalid value"])) ".." :: ConvertResult IntLeft (ConvertError {convSourceValue = "\"..\"", convSourceType = "[Char]", convDestType = "Int", convErrorMessage = "Bad format, Invalid value"})
convertResultToError :: Bifunctor p => p ConvertError c -> p String c Source #
convertResultToErrors :: Bifunctor p => p ConvertError c -> p [String] c Source #
convertOrError :: Convertible a c => a -> Either String c Source #
>>>convertOrError 'a' :: Either Error WordRight 97
>>>convertOrError (1E50::Double) :: Either Error WordLeft "Convertible: error converting source data 1.0e50 of type Double to type Word: Input value outside of bounds: (0,18446744073709551615)"
Convertible re-exports
class Convertible a b where #
A typeclass that represents something that can be converted.
A Convertible a b instance represents an a that can be converted to a b.
Minimal complete definition
Methods
safeConvert :: a -> ConvertResult b #
Convert a to b, returning Right on success and Left on error.
For a simpler interface, see convert.
Instances
convert :: Convertible a b => a -> b #
Convert from one type of data to another. Raises an exception if there is
an error with the conversion. For a function that does not raise an exception
in that case, see safeConvert.
type ConvertResult a = Either ConvertError a #
The result of a safe conversion via safeConvert.
data ConvertError :: * #
How we indicate that there was an error.
Constructors
| ConvertError | |
Fields | |
Instances
Formatting utilities
dotted :: [String] -> String Source #
Intercalate a dot between the non empty elements of a list of strings.
>>>dotted []""
>>>dotted ["","bc","de"]"bc.de"
>>>dotted ["bc","","de"]"bc.de"