Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Web.Hyperbole.Effect.Session
Synopsis
- class Session a where
- sessionKey :: Key
- cookiePath :: Maybe Path
- toCookie :: a -> CookieValue
- parseCookie :: CookieValue -> Either String a
- session :: (Session a, Default a, Hyperbole :> es) => Eff es a
- lookupSession :: forall a es. (Session a, Hyperbole :> es) => Eff es (Maybe a)
- saveSession :: forall a es. (Session a, Hyperbole :> es) => a -> Eff es ()
- modifySession :: (Session a, Default a, Hyperbole :> es) => (a -> a) -> Eff es a
- modifySession_ :: (Session a, Default a, Hyperbole :> es) => (a -> a) -> Eff es ()
- deleteSession :: forall a es. (Session a, Hyperbole :> es) => Eff es ()
- parseSession :: (Session a, Hyperbole :> es) => Key -> CookieValue -> Eff es a
- setCookie :: (ToParam a, Hyperbole :> es) => Cookie -> Eff es ()
- modifyCookies :: Hyperbole :> es => (Cookies -> Cookies) -> Eff es ()
- sessionCookies :: Hyperbole :> es => Eff es Cookies
- clientSessionCookies :: Hyperbole :> es => Eff es Cookies
- requestSessionCookies :: Hyperbole :> es => Eff es Cookies
- sessionCookie :: forall a. Session a => a -> Cookie
- genericTypeName :: forall a. (Generic a, GDatatypeName (Rep a)) => Text
- class GDatatypeName f where
- gDatatypeName :: f p -> Text
Documentation
class Session a where Source #
Configure a data type to persist in the session
as a cookie. These are type-indexed, so only one of each can exist in the session
data Preferences = Preferences
{ color :: AppColor
}
deriving (Generic, ToEncoded, FromEncoded, Session
)
instance Default Preferences where
def = Preferences White
Minimal complete definition
Nothing
Methods
sessionKey :: Key Source #
Unique key for this Session Type. Defaults to the datatypeName
default sessionKey :: (Generic a, GDatatypeName (Rep a)) => Key Source #
cookiePath :: Maybe Path Source #
By default Sessions are persisted only to the current page. Set to `Just "/"` to make an instance available application-wide
default cookiePath :: Maybe Path Source #
toCookie :: a -> CookieValue Source #
Encode type to a a cookie value
default toCookie :: ToEncoded a => a -> CookieValue Source #
parseCookie :: CookieValue -> Either String a Source #
Decode from a cookie value. Defaults to FromJSON
default parseCookie :: FromEncoded a => CookieValue -> Either String a Source #
Instances
Session AuthFlow Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods sessionKey :: Key Source # cookiePath :: Maybe Path Source # toCookie :: AuthFlow -> CookieValue Source # parseCookie :: CookieValue -> Either String AuthFlow Source # | |
Session Authenticated Source # | |
Defined in Web.Hyperbole.Effect.OAuth2 Methods sessionKey :: Key Source # cookiePath :: Maybe Path Source # toCookie :: Authenticated -> CookieValue Source # parseCookie :: CookieValue -> Either String Authenticated Source # |
session :: (Session a, Default a, Hyperbole :> es) => Eff es a Source #
Load data from a browser cookie. If it doesn't exist, the Default
instance is used
data Preferences = Preferences { color :: AppColor } deriving (Generic, ToEncoded, FromEncoded,Session
) instance Default Preferences where def = Preferences White page :: (Hyperbole
:> es) =>Page
es '[Content] page = do prefs <- session @Preferences pure $el
~ bg prefs.color $ "Custom Background"
lookupSession :: forall a es. (Session a, Hyperbole :> es) => Eff es (Maybe a) Source #
Return a session if it exists
saveSession :: forall a es. (Session a, Hyperbole :> es) => a -> Eff es () Source #
Persist datatypes in browser cookies
data Preferences = Preferences { color :: AppColor } deriving (Generic, ToEncoded, FromEncoded,Session
) instance Default Preferences where def = Preferences White instanceHyperView
Content es where dataAction
Content = SetColor AppColor deriving (Generic,ViewAction
)update
(SetColor clr) = do let prefs = Preferences clr saveSession prefs pure $el
~ bg prefs.color $ "Custom Background"
deleteSession :: forall a es. (Session a, Hyperbole :> es) => Eff es () Source #
Remove a single Session
from the browser cookies
parseSession :: (Session a, Hyperbole :> es) => Key -> CookieValue -> Eff es a Source #
setCookie :: (ToParam a, Hyperbole :> es) => Cookie -> Eff es () Source #
save a single datatype to a specific key in the session
modifyCookies :: Hyperbole :> es => (Cookies -> Cookies) -> Eff es () Source #
Modify the client cookies
sessionCookies :: Hyperbole :> es => Eff es Cookies Source #
Return all the cookies, both those sent in the request and others added by the page
clientSessionCookies :: Hyperbole :> es => Eff es Cookies Source #
Return the session from the Client cookies
requestSessionCookies :: Hyperbole :> es => Eff es Cookies Source #
Return the session from the Request
cookies
sessionCookie :: forall a. Session a => a -> Cookie Source #
genericTypeName :: forall a. (Generic a, GDatatypeName (Rep a)) => Text Source #
generic datatype name
class GDatatypeName f where Source #
Methods
gDatatypeName :: f p -> Text Source #
Instances
Datatype d => GDatatypeName (M1 D d f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Effect.Session |