Safe Haskell | None |
---|---|
Language | Haskell2010 |
Web.Sprinkles.Rule
Synopsis
- data RuleTarget p
- = TemplateTarget p
- | RedirectTarget p
- | StaticTarget (Maybe p)
- | JSONTarget
- type Seconds = Integer
- data ClientCacheSetting
- data SessionDirective
- data Rule = Rule {}
- makeRulePathsAbsolute :: FilePath -> Rule -> Rule
- orElse :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a)
- expandRuleTarget :: HashMap Text (GVal (Run SourcePos IO Text)) -> RuleTarget Replacement -> IO (RuleTarget Text)
- expandReplacementBackend :: HashMap Text (GVal (Run SourcePos IO Text)) -> BackendSpec -> IO BackendSpec
- data NonMatchReason
- (<|+>) :: Ord e => Either e a -> Either e a -> Either e a
- matchMethod :: Set Method -> Method -> Maybe Method
- matchRule :: Rule -> Method -> [Text] -> QueryText -> Either NonMatchReason (HashMap Text MatchedText)
- applyRule :: Rule -> Method -> [Text] -> QueryText -> Either NonMatchReason (Rule, HashMap Text MatchedText)
- applyRules :: [Rule] -> Method -> [Text] -> QueryText -> Either NonMatchReason (Rule, HashMap Text MatchedText)
Documentation
data RuleTarget p Source #
Constructors
TemplateTarget p | |
RedirectTarget p | |
StaticTarget (Maybe p) | |
JSONTarget |
Instances
Eq p => Eq (RuleTarget p) Source # | |
Defined in Web.Sprinkles.Rule | |
Show p => Show (RuleTarget p) Source # | |
Defined in Web.Sprinkles.Rule Methods showsPrec :: Int -> RuleTarget p -> ShowS # show :: RuleTarget p -> String # showList :: [RuleTarget p] -> ShowS # |
data ClientCacheSetting Source #
Constructors
NoCache | |
CacheForever | |
MaxAge Seconds |
Instances
Eq ClientCacheSetting Source # | |
Defined in Web.Sprinkles.Rule Methods (==) :: ClientCacheSetting -> ClientCacheSetting -> Bool # (/=) :: ClientCacheSetting -> ClientCacheSetting -> Bool # | |
Show ClientCacheSetting Source # | |
Defined in Web.Sprinkles.Rule Methods showsPrec :: Int -> ClientCacheSetting -> ShowS # show :: ClientCacheSetting -> String # showList :: [ClientCacheSetting] -> ShowS # | |
FromJSON ClientCacheSetting Source # | |
Defined in Web.Sprinkles.Rule Methods parseJSON :: Value -> Parser ClientCacheSetting # parseJSONList :: Value -> Parser [ClientCacheSetting] # |
data SessionDirective Source #
Describes if and how to initialize a session for a request.
Constructors
AcceptSession | Accept if given, but do not require |
IgnoreSession | Ignore all sessions |
CreateNewSession | Always create a new session |
RequireSession | Require a session, fail if none exists |
Instances
Eq SessionDirective Source # | |
Defined in Web.Sprinkles.Rule Methods (==) :: SessionDirective -> SessionDirective -> Bool # (/=) :: SessionDirective -> SessionDirective -> Bool # | |
Show SessionDirective Source # | |
Defined in Web.Sprinkles.Rule Methods showsPrec :: Int -> SessionDirective -> ShowS # show :: SessionDirective -> String # showList :: [SessionDirective] -> ShowS # | |
FromJSON SessionDirective Source # | |
Defined in Web.Sprinkles.Rule Methods parseJSON :: Value -> Parser SessionDirective # parseJSONList :: Value -> Parser [SessionDirective] # |
Constructors
Rule | |
expandRuleTarget :: HashMap Text (GVal (Run SourcePos IO Text)) -> RuleTarget Replacement -> IO (RuleTarget Text) Source #
expandReplacementBackend :: HashMap Text (GVal (Run SourcePos IO Text)) -> BackendSpec -> IO BackendSpec Source #
data NonMatchReason Source #
Constructors
PathNotMatched | |
MethodNotMatched |
Instances
(<|+>) :: Ord e => Either e a -> Either e a -> Either e a Source #
Alternative-like monoid append operator for Eithers over orderable Lefts. The behavior is almost exactly like Alternative proper, except that when both sides fail, the larger failure value prevails.
In other words:
Left 3 |+ Left 2 == Left 3 Left 2 |+ Left 3 == Left 3 Left 2 |+ Right Hello == Right Hello Right Hello |+ Left 2 == Right Hello Right Hello |+ Right Hello == Right Hello
matchRule :: Rule -> Method -> [Text] -> QueryText -> Either NonMatchReason (HashMap Text MatchedText) Source #
applyRule :: Rule -> Method -> [Text] -> QueryText -> Either NonMatchReason (Rule, HashMap Text MatchedText) Source #
applyRules :: [Rule] -> Method -> [Text] -> QueryText -> Either NonMatchReason (Rule, HashMap Text MatchedText) Source #