| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
ConditionalRestriction.Parse.AST
Description
AST for conditional restrictions and incomplete AST for opening hours.
Synopsis
- type Token = String
- newtype ConditionalRestriction = ConditionalRestriction [Expression]
- data Expression = Expression Token [Condition]
- data Condition
- data ComparisonOp
- newtype OpeningHours = OpeningHours [RuleSequence]
- type OHState = Maybe Bool
- data RuleType
- = Normal
- | Additional
- data RuleSequence = RuleSequence RuleType SelectorSequence OHState
- type WeekdaySelector = [WeekdayRange]
- type TimeSelector = [TimeSpan]
- data SelectorSequence
- data WeekdayRange
- data TimeSpan
Documentation
A single token. Is used to represent values of any kind that the parser does not touch.
newtype ConditionalRestriction Source #
AST representation of a conditional restriction.
Constructors
| ConditionalRestriction [Expression] |
Instances
| Show ConditionalRestriction Source # | |
Defined in ConditionalRestriction.Parse.AST Methods showsPrec :: Int -> ConditionalRestriction -> ShowS # show :: ConditionalRestriction -> String # showList :: [ConditionalRestriction] -> ShowS # | |
| Eq ConditionalRestriction Source # | |
Defined in ConditionalRestriction.Parse.AST Methods (==) :: ConditionalRestriction -> ConditionalRestriction -> Bool # (/=) :: ConditionalRestriction -> ConditionalRestriction -> Bool # | |
data Expression Source #
AST representation of a conditional restriction expression, containing a value and conditions for that value
Constructors
| Expression | |
Instances
| Show Expression Source # | |
Defined in ConditionalRestriction.Parse.AST Methods showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
| Eq Expression Source # | |
Defined in ConditionalRestriction.Parse.AST | |
AST representation of a condition.
Constructors
| OH OpeningHours | An |
| Comparison Token ComparisonOp Double | A comparison. Looks something like |
| Absolute Token | An absolute condition, e.g. |
data ComparisonOp Source #
A comparison operator.
Instances
| Show ComparisonOp Source # | |
Defined in ConditionalRestriction.Parse.AST Methods showsPrec :: Int -> ComparisonOp -> ShowS # show :: ComparisonOp -> String # showList :: [ComparisonOp] -> ShowS # | |
| Eq ComparisonOp Source # | |
Defined in ConditionalRestriction.Parse.AST | |
newtype OpeningHours Source #
AST representation of opening hours. Not complete.
Constructors
| OpeningHours [RuleSequence] |
Instances
| Show OpeningHours Source # | |
Defined in ConditionalRestriction.Parse.AST Methods showsPrec :: Int -> OpeningHours -> ShowS # show :: OpeningHours -> String # showList :: [OpeningHours] -> ShowS # | |
| Eq OpeningHours Source # | |
Defined in ConditionalRestriction.Parse.AST | |
type OHState = Maybe Bool Source #
Opening hour state. True/False if known to be open/closed, Nothing if unknown.
Type of opening hour rule.
Constructors
| Normal | First rule or rules separated by ";". |
| Additional | Rules separated by ",". |
data RuleSequence Source #
AST representation of a rule sequence.
Constructors
| RuleSequence RuleType SelectorSequence OHState |
Instances
| Show RuleSequence Source # | |
Defined in ConditionalRestriction.Parse.AST Methods showsPrec :: Int -> RuleSequence -> ShowS # show :: RuleSequence -> String # showList :: [RuleSequence] -> ShowS # | |
| Eq RuleSequence Source # | |
Defined in ConditionalRestriction.Parse.AST | |
type WeekdaySelector = [WeekdayRange] Source #
AST representation of a weekday selector (e.g. "Sa-Di, Th").
type TimeSelector = [TimeSpan] Source #
AST representation of a time selector (e.g. "18:00-20:00, 21:00-03:00").
data SelectorSequence Source #
AST representation of a selector sequence (e.g. "24/7", "We-Su 18:00-20:00").
Constructors
| TwentyFourSeven | |
| WeekdaySel WeekdaySelector | |
| TimeSel TimeSelector | |
| WeekdayTime WeekdaySelector TimeSelector |
Instances
| Show SelectorSequence Source # | |
Defined in ConditionalRestriction.Parse.AST Methods showsPrec :: Int -> SelectorSequence -> ShowS # show :: SelectorSequence -> String # showList :: [SelectorSequence] -> ShowS # | |
| Eq SelectorSequence Source # | |
Defined in ConditionalRestriction.Parse.AST Methods (==) :: SelectorSequence -> SelectorSequence -> Bool # (/=) :: SelectorSequence -> SelectorSequence -> Bool # | |
data WeekdayRange Source #
AST representation of a weekday range.
Instances
| Show WeekdayRange Source # | |
Defined in ConditionalRestriction.Parse.AST Methods showsPrec :: Int -> WeekdayRange -> ShowS # show :: WeekdayRange -> String # showList :: [WeekdayRange] -> ShowS # | |
| Eq WeekdayRange Source # | |
Defined in ConditionalRestriction.Parse.AST | |