libjwt-typed-0.2: A Haskell implementation of JSON Web Token (JWT)
Safe HaskellNone
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • ScopedTypeVariables
  • DataKinds
  • DefaultSignatures
  • DerivingStrategies
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • TypeApplications

Libjwt.Flag

Description

Support for simple sum types.

Synopsis

Documentation

newtype Flag a Source #

Value that is encoded and decoded as AFlag

Flags provide a way to automatically encode and decode simple sum types.

data Scope = Login | Extended | UserRead | UserWrite | AccountRead | AccountWrite
 deriving stock (Show, Eq, Generic)

instance AFlag Scope

mkPayload = jwtPayload
    (withIssuer "myApp" <> withRecipient "https://myApp.com" <> setTtl 300)
    ( #user_name ->> "John Doe"
    , #is_root ->> False
    , #user_id ->> (12345 :: Int)
    , #scope ->> Flag Login
    )

Constructors

Flag 

Fields

Instances

Instances details
AFlag a => JwtRep ASCII (Flag a) Source # 
Instance details

Defined in Libjwt.Classes

Methods

rep :: Flag a -> ASCII Source #

unRep :: ASCII -> Maybe (Flag a) Source #

Eq a => Eq (Flag a) Source # 
Instance details

Defined in Libjwt.Flag

Methods

(==) :: Flag a -> Flag a -> Bool #

(/=) :: Flag a -> Flag a -> Bool #

Show a => Show (Flag a) Source # 
Instance details

Defined in Libjwt.Flag

Methods

showsPrec :: Int -> Flag a -> ShowS #

show :: Flag a -> String #

showList :: [Flag a] -> ShowS #

AFlag a => AFlag (Flag a) Source # 
Instance details

Defined in Libjwt.Flag

AFlag a => JsonParser (Flag a) Source # 
Instance details

Defined in Libjwt.Classes

AFlag a => JsonBuilder (Flag a) Source # 
Instance details

Defined in Libjwt.Classes

class AFlag a where Source #

Types that can be used as flags . That is, they support conversion to/from ASCII values, for example, simple sum types are good candidates that can even be generically derived

data Scope = Login | Extended | UserRead | UserWrite | AccountRead | AccountWrite
 deriving stock (Show, Eq, Generic)

instance AFlag Scope
>>> getFlagValue UserWrite
ASCII {getASCII = "userWrite"}
>>> setFlagValue (ASCII "userWrite") :: Maybe Scope
Just UserWrite

Minimal complete definition

Nothing

Methods

getFlagValue :: a -> ASCII Source #

default getFlagValue :: (Generic a, GFlag (Rep a)) => a -> ASCII Source #

setFlagValue :: ASCII -> Maybe a Source #

default setFlagValue :: (Generic a, GFlag (Rep a)) => ASCII -> Maybe a Source #

Instances

Instances details
AFlag a => AFlag (Flag a) Source # 
Instance details

Defined in Libjwt.Flag