| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Rest.Types.Error
- data DataError
- newtype DomainReason a = DomainReason {
- reason :: a
- data Status a b
- fromEither :: Either a b -> Status a b
- toEither :: Status a b -> Either a b
- type Reason_ = Reason ()
- data Reason a
- data SomeReason where
- SomeReason :: (XmlPickler e, JSONSchema e, ToJSON e) => Reason e -> SomeReason
- class ToResponseCode a where
- toResponseCode :: a -> Int
Documentation
Constructors
| ParseError String | |
| PrintError String | |
| MissingField String | |
| UnsupportedFormat String |
newtype DomainReason a Source
Constructors
| DomainReason | |
Fields
| |
Instances
| Functor DomainReason | |
| Foldable DomainReason | |
| Traversable DomainReason | |
| Eq a => Eq (DomainReason a) | |
| Show a => Show (DomainReason a) | |
| Generic (DomainReason a) | |
| ToJSON a => ToJSON (DomainReason a) | |
| FromJSON a => FromJSON (DomainReason a) | |
| XmlPickler a => XmlPickler (DomainReason a) | |
| JSONSchema a => JSONSchema (DomainReason a) | |
| type Rep (DomainReason a) |
Instances
| Functor (Status a) | |
| Foldable (Status a) | |
| Traversable (Status a) | |
| (Eq a, Eq b) => Eq (Status a b) | |
| (Show a, Show b) => Show (Status a b) | |
| Generic (Status a b) | |
| (ToJSON a, ToJSON b) => ToJSON (Status a b) | |
| (FromJSON a, FromJSON b) => FromJSON (Status a b) | |
| (XmlPickler a, XmlPickler b) => XmlPickler (Status a b) | |
| (JSONSchema a, JSONSchema b) => JSONSchema (Status a b) | |
| Regular (Status a b) | |
| Typeable (* -> * -> *) Status | |
| type Rep (Status a b) | |
| type PF (Status a b) |
fromEither :: Either a b -> Status a b Source
Constructors
Instances
| Functor Reason | |
| Foldable Reason | |
| Traversable Reason | |
| Eq a => Eq (Reason a) | |
| Show a => Show (Reason a) | |
| Generic (Reason a) | |
| ToJSON e => ToJSON (Reason e) | |
| FromJSON e => FromJSON (Reason e) | |
| XmlPickler e => XmlPickler (Reason e) | |
| JSONSchema e => JSONSchema (Reason e) | |
| Error (Reason e) | |
| Regular (Reason a) | |
| ToResponseCode a => ToResponseCode (Reason a) | |
| Typeable (* -> *) Reason | |
| type Rep (Reason a) | |
| type PF (Reason e) |
data SomeReason where Source
Constructors
| SomeReason :: (XmlPickler e, JSONSchema e, ToJSON e) => Reason e -> SomeReason |
class ToResponseCode a where Source
The response code that should be given for a type. This is currently only used for errors.
Methods
toResponseCode :: a -> Int Source
Instances
| ToResponseCode () | |
| ToResponseCode a => ToResponseCode (Reason a) |