hyperbole-0.5.0: Interactive HTML apps using type-safe serverside Haskell
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.Hyperbole.Effect.Session

Synopsis

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

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

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

instance HyperView Content es where
  data Action Content
    = SetColor AppColor
    deriving (Generic, ViewAction)

  update (SetColor clr) = do
    let prefs = Preferences clr
    saveSession prefs
    pure $ el ~ bg prefs.color $ "Custom Background"

modifySession :: (Session a, Default a, Hyperbole :> es) => (a -> a) -> Eff es a Source #

modifySession_ :: (Session a, Default a, Hyperbole :> es) => (a -> a) -> Eff es () Source #

deleteSession :: forall a es. (Session a, Hyperbole :> es) => Eff es () Source #

Remove a single Session from the browser cookies

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

Instances details
Datatype d => GDatatypeName (M1 D d f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Effect.Session

Methods

gDatatypeName :: forall (p :: k0). M1 D d f p -> Text Source #