Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Web.Hyperbole.Data.Encoded
Synopsis
- newtype ConName = ConName {}
- data Encoded = Encoded ConName [ParamValue]
- encode :: ToEncoded a => a -> Text
- decode :: FromEncoded a => Text -> Maybe a
- decodeEither :: FromEncoded a => Text -> Either String a
- encodedToText :: Encoded -> Text
- encodedParseText :: Text -> Either String Encoded
- genericToEncoded :: (Generic a, GToEncoded (Rep a)) => a -> Encoded
- genericParseEncoded :: (Generic a, GFromEncoded (Rep a)) => Encoded -> Either String a
- genericDecode :: (Generic a, GFromEncoded (Rep a)) => Text -> Maybe a
- class ToEncoded a where
- class FromEncoded a where
- parseEncoded :: Encoded -> Either String a
- fromResult :: Result a -> Either String a
- paramParser :: Parser ParamValue
- decodeParam :: Text -> ParamValue
- desanitizeParamText :: Text -> Text
- encodeParam :: ParamValue -> Text
- class GToEncoded f where
- gToEncoded :: f p -> Encoded
- class GFromEncoded f where
- gParseEncoded :: Encoded -> Either String (f p, [ParamValue])
Documentation
Pretty Human Readable top-levelencoding for ViewAction and ViewId For simple Sum and Product types it is equivalent to the Show/Read instance
MyConstructor 1 2 3
Constructors
Encoded ConName [ParamValue] |
decodeEither :: FromEncoded a => Text -> Either String a Source #
encodedToText :: Encoded -> Text Source #
Basic Encoding
genericToEncoded :: (Generic a, GToEncoded (Rep a)) => a -> Encoded Source #
genericParseEncoded :: (Generic a, GFromEncoded (Rep a)) => Encoded -> Either String a Source #
genericDecode :: (Generic a, GFromEncoded (Rep a)) => Text -> Maybe a Source #
class ToEncoded a where Source #
Custom Encoding for embedding into web documents. Noteably used for ViewId
and ViewAction
Minimal complete definition
Nothing
Methods
class FromEncoded a where Source #
Custom Encoding for embedding into web documents. Noteably used for ViewId
and ViewAction
Minimal complete definition
Nothing
Methods
parseEncoded :: Encoded -> Either String a Source #
default parseEncoded :: (Generic a, GFromEncoded (Rep a)) => Encoded -> Either String a Source #
Instances
FromEncoded Encoded Source # | |
Defined in Web.Hyperbole.Data.Encoded | |
FromEncoded AuthFlow Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 | |
FromEncoded Authenticated Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods parseEncoded :: Encoded -> Either String Authenticated Source # | |
FromJSON a => FromEncoded (JSON a) Source # | |
Defined in Web.Hyperbole.Data.JSON |
decodeParam :: Text -> ParamValue Source #
desanitizeParamText :: Text -> Text Source #
encodeParam :: ParamValue -> Text Source #
class GToEncoded f where Source #
Methods
gToEncoded :: f p -> Encoded Source #
Instances
GToEncoded (U1 :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.Encoded Methods gToEncoded :: forall (p :: k0). U1 p -> Encoded Source # | |
(GToEncoded f, GToEncoded g) => GToEncoded (f :*: g :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.Encoded Methods gToEncoded :: forall (p :: k0). (f :*: g) p -> Encoded Source # | |
(GToEncoded f, GToEncoded g) => GToEncoded (f :+: g :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.Encoded Methods gToEncoded :: forall (p :: k0). (f :+: g) p -> Encoded Source # | |
ToParam a => GToEncoded (K1 R a :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.Encoded | |
(Constructor c, GToEncoded f) => GToEncoded (M1 C c f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.Encoded | |
GToEncoded f => GToEncoded (M1 D d f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.Encoded | |
GToEncoded f => GToEncoded (M1 S s f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Data.Encoded |
class GFromEncoded f where Source #
Methods
gParseEncoded :: Encoded -> Either String (f p, [ParamValue]) Source #