| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Web.Hyperbole.Effect.GenRandom
Documentation
data GenRandom (a :: Type -> Type) b where Source #
Constructors
| GenRandom :: forall b (a :: Type -> Type). Random b => (b, b) -> GenRandom a b | |
| GenRandomToken :: forall {k} (a :: Type -> Type) (a1 :: k). Int -> GenRandom a (Token a1) | |
| GenRandomList :: forall b (a :: Type -> Type). Random b => [b] -> GenRandom a b |
Instances
| type DispatchOf GenRandom Source # | |
Defined in Web.Hyperbole.Effect.GenRandom | |
genRandomToken :: forall {k} (es :: [Effect]) (a :: k). GenRandom :> es => Int -> Eff es (Token a) Source #
newtype Token (a :: k) Source #
Instances
| FromJSON (Token a) Source # | |
Defined in Web.Hyperbole.Effect.GenRandom | |
| ToJSON (Token a) Source # | |
| Read (Token a) Source # | |
| Show (Token a) Source # | |
| Eq (Token a) Source # | |
| FromParam (Token a) Source # | |
Defined in Web.Hyperbole.Effect.GenRandom Methods parseParam :: ParamValue -> Either String (Token a) Source # decodeFormValue :: Maybe Text -> Either String (Token a) Source # | |
| ToParam (Token a) Source # | |
Defined in Web.Hyperbole.Effect.GenRandom Methods toParam :: Token a -> ParamValue Source # | |