module Data.BAByNF.ABNF.Core ( rules , ruleRefs , alphaRef , alphaRule , bitRef , bitRule , charRef , charRule , crRef , crRule , crlfRef , crlfRule , ctlRef , ctlRule , digitRef , digitRule , dquoteRef , dquoteRule , hexdigRef , hexdigRule , htabRef , htabRule , lfRef , lfRule , lwspRef , lwspRule , octetRef , octetRule , spRef , spRule , vcharRef , vcharRule , wspRef , wspRule ) where import Data.List qualified as List import Data.BAByNF.Util.Ascii qualified as Ascii import Data.BAByNF.Util.Hex qualified as Hex import Data.BAByNF.ABNF.Model qualified as Model rules :: [Model.Rule] rules :: [Rule] rules = [ Rule alphaRule , Rule bitRule , Rule charRule , Rule crRule , Rule crlfRule , Rule ctlRule , Rule digitRule , Rule dquoteRule , Rule hexdigRule , Rule htabRule , Rule lfRule , Rule lwspRule , Rule octetRule , Rule spRule , Rule vcharRule , Rule wspRule ] ruleRefs :: [Model.Rulename] ruleRefs :: [Rulename] ruleRefs = (Rule -> Rulename) -> [Rule] -> [Rulename] forall a b. (a -> b) -> [a] -> [b] map (\(Model.Rule Rulename r DefinedAs _ Elements _) -> Rulename r) [Rule] rules alphaRef :: Model.Rulename alphaRef :: Rulename alphaRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "ALPHA") alphaRule :: Model.Rule alphaRule :: Rule alphaRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename alphaRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> ([Concatenation] -> Elements) -> [Concatenation] -> Rule forall b c a. (b -> c) -> (a -> b) -> a -> c . Alternation -> Elements Model.Elements (Alternation -> Elements) -> ([Concatenation] -> Alternation) -> [Concatenation] -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Rule) -> [Concatenation] -> Rule forall a b. (a -> b) -> a -> b $ [ [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Concatenation) -> HexVal -> Concatenation forall a b. (a -> b) -> a -> b $ Seq -> Seq -> HexVal Model.RangeHexVal ([Digit] -> Seq Hex.Seq [Digit Hex.X4, Digit Hex.X1]) ([Digit] -> Seq Hex.Seq [Digit Hex.X5, Digit Hex.XA]) , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Concatenation) -> HexVal -> Concatenation forall a b. (a -> b) -> a -> b $ Seq -> Seq -> HexVal Model.RangeHexVal ([Digit] -> Seq Hex.Seq [Digit Hex.X6, Digit Hex.X1]) ([Digit] -> Seq Hex.Seq [Digit Hex.X7, Digit Hex.XA]) ] bitRef :: Model.Rulename bitRef :: Rulename bitRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "BIT") bitRule :: Model.Rule bitRule :: Rule bitRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename bitRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> Alternation -> Elements forall a b. (a -> b) -> a -> b $ [Concatenation] -> Alternation Model.Alternation [ [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char '0' , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char '1' ] charRef :: Model.Rulename charRef :: Rulename charRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "CHAR") charRule :: Model.Rule charRule :: Rule charRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename charRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ Seq -> Seq -> HexVal Model.RangeHexVal ([Digit] -> Seq Hex.Seq [Digit Hex.X0, Digit Hex.X1]) ([Digit] -> Seq Hex.Seq [Digit Hex.X7, Digit Hex.XF]) crRef :: Model.Rulename crRef :: Rulename crRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "CR") crRule :: Model.Rule crRule :: Rule crRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename crRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ [Seq] -> HexVal Model.SeqHexVal [[Digit] -> Seq Hex.Seq [Digit Hex.X0, Digit Hex.XD]] crlfRef :: Model.Rulename crlfRef :: Rulename crlfRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "CRLF") crlfRule :: Model.Rule crlfRule :: Rule crlfRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename crlfRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (Concatenation -> Alternation) -> Concatenation -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (Concatenation -> [Concatenation]) -> Concatenation -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> Elements) -> Concatenation -> Elements forall a b. (a -> b) -> a -> b $ [Repetition] -> Concatenation Model.Concatenation [ Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> Element -> Repetition forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename crRef , Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> Element -> Repetition forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename lfRef ] ctlRef :: Model.Rulename ctlRef :: Rulename ctlRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "CTL") ctlRule :: Model.Rule ctlRule :: Rule ctlRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename ctlRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> Alternation -> Elements forall a b. (a -> b) -> a -> b $ [Concatenation] -> Alternation Model.Alternation [ [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Concatenation) -> HexVal -> Concatenation forall a b. (a -> b) -> a -> b $ Seq -> Seq -> HexVal Model.RangeHexVal ([Digit] -> Seq Hex.Seq [Digit Hex.X0, Digit Hex.X0]) ([Digit] -> Seq Hex.Seq [Digit Hex.X1, Digit Hex.XF]) , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Concatenation) -> HexVal -> Concatenation forall a b. (a -> b) -> a -> b $ [Seq] -> HexVal Model.SeqHexVal [[Digit] -> Seq Hex.Seq [Digit Hex.X7, Digit Hex.XF]] ] digitRef :: Model.Rulename digitRef :: Rulename digitRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "DIGIT") digitRule :: Model.Rule digitRule :: Rule digitRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename digitRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ Seq -> Seq -> HexVal Model.RangeHexVal ([Digit] -> Seq Hex.Seq [Digit Hex.X3, Digit Hex.X0]) ([Digit] -> Seq Hex.Seq [Digit Hex.X3, Digit Hex.X9]) dquoteRef :: Model.Rulename dquoteRef :: Rulename dquoteRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "DQUOTE") dquoteRule :: Model.Rule dquoteRule :: Rule dquoteRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename dquoteRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ [Seq] -> HexVal Model.SeqHexVal [[Digit] -> Seq Hex.Seq [Digit Hex.X2, Digit Hex.X2]] hexdigRef :: Model.Rulename hexdigRef :: Rulename hexdigRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "HEXDIG") hexdigRule :: Model.Rule hexdigRule :: Rule hexdigRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename hexdigRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> Alternation -> Elements forall a b. (a -> b) -> a -> b $ [Concatenation] -> Alternation Model.Alternation [ [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (Element -> [Repetition]) -> Element -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (Element -> Repetition) -> Element -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Concatenation) -> Element -> Concatenation forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename digitRef , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char 'A' , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char 'B' , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char 'C' , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char 'D' , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char 'E' , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (ByteString -> [Repetition]) -> ByteString -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (ByteString -> Repetition) -> ByteString -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (ByteString -> Element) -> ByteString -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . CharVal -> Element Model.CharValElement (CharVal -> Element) -> (ByteString -> CharVal) -> ByteString -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . CaseInsensitiveString -> CharVal Model.CaseInsensitiveCharVal (CaseInsensitiveString -> CharVal) -> (ByteString -> CaseInsensitiveString) -> ByteString -> CharVal forall b c a. (b -> c) -> (a -> b) -> a -> c . QuotedString -> CaseInsensitiveString Model.CaseInsensitiveString (QuotedString -> CaseInsensitiveString) -> (ByteString -> QuotedString) -> ByteString -> CaseInsensitiveString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> QuotedString Model.QuotedString (ByteString -> Concatenation) -> ByteString -> Concatenation forall a b. (a -> b) -> a -> b $ Char -> ByteString Ascii.bs Char 'F' ] htabRef :: Model.Rulename htabRef :: Rulename htabRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "HTAB") htabRule :: Model.Rule htabRule :: Rule htabRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename htabRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ [Seq] -> HexVal Model.SeqHexVal [[Digit] -> Seq Hex.Seq [Digit Hex.X0, Digit Hex.X9]] lfRef :: Model.Rulename lfRef :: Rulename lfRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "LF") lfRule :: Model.Rule lfRule :: Rule lfRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename lfRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ [Seq] -> HexVal Model.SeqHexVal [[Digit] -> Seq Hex.Seq [Digit Hex.X0, Digit Hex.XA]] lwspRef :: Model.Rulename lwspRef :: Rulename lwspRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "LWSP") lwspRule :: Model.Rule lwspRule :: Rule lwspRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename lwspRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (Alternation -> Alternation) -> Alternation -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (Alternation -> [Concatenation]) -> Alternation -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (Alternation -> Concatenation) -> Alternation -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (Alternation -> [Repetition]) -> Alternation -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (Alternation -> Repetition) -> Alternation -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition (Bound -> Bound -> Repeat Model.RangedRepeat Bound Model.UnBound Bound Model.UnBound) (Element -> Repetition) -> (Alternation -> Element) -> Alternation -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . Group -> Element Model.GroupElement (Group -> Element) -> (Alternation -> Group) -> Alternation -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . Alternation -> Group Model.Group (Alternation -> Elements) -> Alternation -> Elements forall a b. (a -> b) -> a -> b $ [Concatenation] -> Alternation Model.Alternation [ [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (Element -> [Repetition]) -> Element -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (Element -> Repetition) -> Element -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Concatenation) -> Element -> Concatenation forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename wspRef , [Repetition] -> Concatenation Model.Concatenation [ Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> Element -> Repetition forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename crlfRef , Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> Element -> Repetition forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename wspRef ] ] octetRef :: Model.Rulename octetRef :: Rulename octetRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "OCTET") octetRule :: Model.Rule octetRule :: Rule octetRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename octetRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ Seq -> Seq -> HexVal Model.RangeHexVal ([Digit] -> Seq Hex.Seq [Digit Hex.X0, Digit Hex.X0]) ([Digit] -> Seq Hex.Seq [Digit Hex.XF, Digit Hex.XF]) spRef :: Model.Rulename spRef :: Rulename spRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "SP") spRule :: Model.Rule spRule :: Rule spRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename spRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ [Seq] -> HexVal Model.SeqHexVal [[Digit] -> Seq Hex.Seq [Digit Hex.X2, Digit Hex.X0]] vcharRef :: Model.Rulename vcharRef :: Rulename vcharRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "VCHAR") vcharRule :: Model.Rule vcharRule :: Rule vcharRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename vcharRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> (HexVal -> Alternation) -> HexVal -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> (HexVal -> [Concatenation]) -> HexVal -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> (HexVal -> Concatenation) -> HexVal -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (HexVal -> [Repetition]) -> HexVal -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (HexVal -> Repetition) -> HexVal -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> (HexVal -> Element) -> HexVal -> Repetition forall b c a. (b -> c) -> (a -> b) -> a -> c . NumVal -> Element Model.NumValElement (NumVal -> Element) -> (HexVal -> NumVal) -> HexVal -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . HexVal -> NumVal Model.HexNumVal (HexVal -> Elements) -> HexVal -> Elements forall a b. (a -> b) -> a -> b $ Seq -> Seq -> HexVal Model.RangeHexVal ([Digit] -> Seq Hex.Seq [Digit Hex.X2, Digit Hex.X1]) ([Digit] -> Seq Hex.Seq [Digit Hex.X7, Digit Hex.XE]) wspRef :: Model.Rulename wspRef :: Rulename wspRef = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "WSP") wspRule :: Model.Rule wspRule :: Rule wspRule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename wspRef DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> Alternation -> Elements forall a b. (a -> b) -> a -> b $ [Concatenation] -> Alternation Model.Alternation [ [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (Element -> [Repetition]) -> Element -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (Element -> Repetition) -> Element -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Concatenation) -> Element -> Concatenation forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename spRef , [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Concatenation) -> (Element -> [Repetition]) -> Element -> Concatenation forall b c a. (b -> c) -> (a -> b) -> a -> c . Repetition -> [Repetition] forall a. a -> [a] List.singleton (Repetition -> [Repetition]) -> (Element -> Repetition) -> Element -> [Repetition] forall b c a. (b -> c) -> (a -> b) -> a -> c . Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Concatenation) -> Element -> Concatenation forall a b. (a -> b) -> a -> b $ Rulename -> Element Model.RulenameElement Rulename htabRef ]