Copyright | (C) 2017- Mark Andrus Roberts |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Mark Andrus Roberts <markandrusroberts@gmail.com> |
Stability | provisional |
Safe Haskell | None |
Language | Haskell98 |
This module defines all of the SIDs (string identifiers) for Twilio resources in a single place.
Synopsis
- data SID (a :: Alpha) (b :: Alpha) = SID !Word64 !Word64
- class IsSID sid where
- readSID :: forall a b. (IsAlpha a, IsAlpha b) => ReadPrec (SID a b)
- parseSIDFromText :: forall m a b. (MonadPlus m, IsAlpha a, IsAlpha b) => Text -> m (SID a b)
- parseSIDFromJSON :: (MonadPlus m, IsAlpha a, IsAlpha b) => Value -> m (SID a b)
- sidToJSON :: (IsAlpha a, IsAlpha b) => SID a b -> Value
- sidToText :: (IsAlpha a, IsAlpha b) => SID a b -> Text
Documentation
data SID (a :: Alpha) (b :: Alpha) Source #
A SID (string identifier) is a 34-character string. The first two characters are capital letters A through Z; the remaining 32 characters represent a 128-bit natural number in hexadecimal.
Instances
Bounded (SID a b) Source # | |
Eq (SID a b) Source # | |
(Typeable a, Typeable b) => Data (SID a b) Source # | |
Defined in Twilio.Types.SID gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> SID a b -> c (SID a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SID a b) # toConstr :: SID a b -> Constr # dataTypeOf :: SID a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SID a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SID a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> SID a b -> SID a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SID a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SID a b -> r # gmapQ :: (forall d. Data d => d -> u) -> SID a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SID a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SID a b -> m (SID a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SID a b -> m (SID a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SID a b -> m (SID a b) # | |
Ord (SID a b) Source # | |
(IsAlpha a, IsAlpha b) => Read (SID a b) Source # | |
(IsAlpha a, IsAlpha b) => Show (SID a b) Source # | |
Ix (SID a b) Source # | |
Defined in Twilio.Types.SID | |
(IsAlpha a, IsAlpha b) => IsString (SID a b) Source # | |
Defined in Twilio.Types.SID fromString :: String -> SID a b # | |
Generic (SID a b) Source # | |
Hashable (SID a b) Source # | |
Defined in Twilio.Types.SID | |
(IsAlpha a, IsAlpha b) => ToJSON (SID a b) Source # | |
Defined in Twilio.Types.SID | |
(IsAlpha a, IsAlpha b) => FromJSON (SID a b) Source # | |
Binary (SID a b) Source # | |
NFData (SID a b) Source # | |
Defined in Twilio.Types.SID | |
(IsAlpha a, IsAlpha b) => IsSID (SID a b) Source # | |
type Rep (SID a b) Source # | |
Defined in Twilio.Types.SID type Rep (SID a b) = D1 (MetaData "SID" "Twilio.Types.SID" "twilio-0.3.0.0-1lpPNPa4b89HUIQeQ4pFjg" False) (C1 (MetaCons "SID" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64))) |
class IsSID sid where Source #