{-# LANGUAGE LambdaCase #-} module Data.BAByNF.ABNF.Rules.Alternation ( ref , rule , fromTree ) where import Data.List qualified as List import Data.BAByNF.Util.Ascii qualified as Ascii import Data.BAByNF.Core.Tree (Tree) import Data.BAByNF.Core.Tree qualified as Tree import Data.BAByNF.ABNF.Model qualified as Model import Data.BAByNF.ABNF.Rules.Concatenation qualified as Concatenation import Data.BAByNF.ABNF.Rules.CWsp qualified as CWsp ref :: Model.Rulename ref :: Rulename ref = ByteString -> Rulename Model.Rulename (String -> ByteString Ascii.stringAsBytesUnsafe String "alternation") rule :: Model.Rule rule :: Rule rule = Rulename -> DefinedAs -> Elements -> Rule Model.Rule Rulename ref DefinedAs Model.BasicDefinition (Elements -> Rule) -> Elements -> Rule forall a b. (a -> b) -> a -> b $ Alternation -> Elements Model.Elements (Alternation -> Elements) -> ([Repetition] -> Alternation) -> [Repetition] -> Elements forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> ([Repetition] -> [Concatenation]) -> [Repetition] -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> ([Repetition] -> Concatenation) -> [Repetition] -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Elements) -> [Repetition] -> Elements forall a b. (a -> b) -> a -> b $ [ Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Rulename -> Element Model.RulenameElement Rulename Concatenation.ref) , Repeat -> Element -> Repetition Model.Repetition (Bound -> Bound -> Repeat Model.RangedRepeat Bound Model.UnBound Bound Model.UnBound) (Element -> Repetition) -> Element -> Repetition forall a b. (a -> b) -> a -> b $ Group -> Element Model.GroupElement (Group -> Element) -> ([Repetition] -> Group) -> [Repetition] -> Element forall b c a. (b -> c) -> (a -> b) -> a -> c . Alternation -> Group Model.Group (Alternation -> Group) -> ([Repetition] -> Alternation) -> [Repetition] -> Group forall b c a. (b -> c) -> (a -> b) -> a -> c . [Concatenation] -> Alternation Model.Alternation ([Concatenation] -> Alternation) -> ([Repetition] -> [Concatenation]) -> [Repetition] -> Alternation forall b c a. (b -> c) -> (a -> b) -> a -> c . Concatenation -> [Concatenation] forall a. a -> [a] List.singleton (Concatenation -> [Concatenation]) -> ([Repetition] -> Concatenation) -> [Repetition] -> [Concatenation] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Repetition] -> Concatenation Model.Concatenation ([Repetition] -> Element) -> [Repetition] -> Element forall a b. (a -> b) -> a -> b $ [ Repeat -> Element -> Repetition Model.Repetition (Bound -> Bound -> Repeat Model.RangedRepeat Bound Model.UnBound Bound Model.UnBound) (Rulename -> Element Model.RulenameElement Rulename CWsp.ref) , Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Element -> Repetition) -> Element -> Repetition forall a b. (a -> b) -> a -> b $ 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 -> Element) -> ByteString -> Element forall a b. (a -> b) -> a -> b $ String -> ByteString Ascii.stringAsBytesUnsafe String "/" , Repeat -> Element -> Repetition Model.Repetition (Bound -> Bound -> Repeat Model.RangedRepeat Bound Model.UnBound Bound Model.UnBound) (Rulename -> Element Model.RulenameElement Rulename CWsp.ref) , Repeat -> Element -> Repetition Model.Repetition Repeat Model.NoRepeat (Rulename -> Element Model.RulenameElement Rulename Concatenation.ref) ] ] fromTree :: Tree Model.Rulename -> Either String Model.Alternation fromTree :: Tree Rulename -> Either String Alternation fromTree Tree Rulename tree = let concatTrees :: [Tree Rulename] concatTrees = Rulename -> Tree Rulename -> [Tree Rulename] forall a. a -> Tree a -> [Tree a] Tree.getChildrenWithRef Rulename Concatenation.ref Tree Rulename tree in (Tree Rulename -> Either String Concatenation) -> [Tree Rulename] -> Either String [Concatenation] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] mapM Tree Rulename -> Either String Concatenation Concatenation.fromTree [Tree Rulename] concatTrees Either String [Concatenation] -> ([Concatenation] -> Either String Alternation) -> Either String Alternation forall a b. Either String a -> (a -> Either String b) -> Either String b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \case [] -> String -> Either String Alternation forall a b. a -> Either a b Left String "Alternation.hs: empty alt" lst :: [Concatenation] lst@(Concatenation _:[Concatenation] _) -> Alternation -> Either String Alternation forall a b. b -> Either a b Right (Alternation -> Either String Alternation) -> Alternation -> Either String Alternation forall a b. (a -> b) -> a -> b $ [Concatenation] -> Alternation Model.Alternation [Concatenation] lst