{-# LANGUAGE FlexibleContexts #-} module Saturn.Unstable.Type.Field where import qualified Data.Coerce as Coerce import qualified Data.Either as Either import qualified Data.Foldable as Foldable import qualified Data.List.NonEmpty as NonEmpty import qualified Data.Set as Set import qualified Data.Text.Lazy.Builder as Builder import qualified Data.Word as Word import qualified Saturn.Unstable.Extra.Parsec as Parsec import qualified Saturn.Unstable.Extra.Tuple as Tuple import qualified Saturn.Unstable.Type.Element as Element import qualified Saturn.Unstable.Type.Wildcard as Wildcard import qualified Text.Parsec as Parsec newtype Field = Field (Either Wildcard.Wildcard (NonEmpty.NonEmpty Element.Element)) deriving (Field -> Field -> Bool (Field -> Field -> Bool) -> (Field -> Field -> Bool) -> Eq Field forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Field -> Field -> Bool == :: Field -> Field -> Bool $c/= :: Field -> Field -> Bool /= :: Field -> Field -> Bool Eq, Int -> Field -> ShowS [Field] -> ShowS Field -> String (Int -> Field -> ShowS) -> (Field -> String) -> ([Field] -> ShowS) -> Show Field forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Field -> ShowS showsPrec :: Int -> Field -> ShowS $cshow :: Field -> String show :: Field -> String $cshowList :: [Field] -> ShowS showList :: [Field] -> ShowS Show) fromEither :: Either Wildcard.Wildcard (NonEmpty.NonEmpty Element.Element) -> Field fromEither :: Either Wildcard (NonEmpty Element) -> Field fromEither = Either Wildcard (NonEmpty Element) -> Field forall a b. Coercible a b => a -> b Coerce.coerce toEither :: Field -> Either Wildcard.Wildcard (NonEmpty.NonEmpty Element.Element) toEither :: Field -> Either Wildcard (NonEmpty Element) toEither = Field -> Either Wildcard (NonEmpty Element) forall a b. Coercible a b => a -> b Coerce.coerce parsec :: (Parsec.Stream s m Char) => Parsec.ParsecT s u m Field parsec :: forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Field parsec = Either Wildcard (NonEmpty Element) -> Field fromEither (Either Wildcard (NonEmpty Element) -> Field) -> ParsecT s u m (Either Wildcard (NonEmpty Element)) -> ParsecT s u m Field forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ParsecT s u m Wildcard -> ParsecT s u m (NonEmpty Element) -> ParsecT s u m (Either Wildcard (NonEmpty Element)) forall s u (m :: * -> *) a b. ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m (Either a b) Parsec.either ParsecT s u m Wildcard forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Wildcard Wildcard.parsec (ParsecT s u m Element -> ParsecT s u m Char -> ParsecT s u m (NonEmpty Element) forall s u (m :: * -> *) a sep. ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m (NonEmpty a) Parsec.sepByNE ParsecT s u m Element forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Element Element.parsec (ParsecT s u m Char -> ParsecT s u m (NonEmpty Element)) -> ParsecT s u m Char -> ParsecT s u m (NonEmpty Element) forall a b. (a -> b) -> a -> b $ Char -> ParsecT s u m Char forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char ',') toBuilder :: Field -> Builder.Builder toBuilder :: Field -> Builder toBuilder = (Wildcard -> Builder) -> (NonEmpty Element -> Builder) -> Either Wildcard (NonEmpty Element) -> Builder forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either Wildcard -> Builder Wildcard.toBuilder ( NonEmpty Builder -> Builder forall m. Monoid m => NonEmpty m -> m forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m Foldable.fold (NonEmpty Builder -> Builder) -> (NonEmpty Element -> NonEmpty Builder) -> NonEmpty Element -> Builder forall b c a. (b -> c) -> (a -> b) -> a -> c . Builder -> NonEmpty Builder -> NonEmpty Builder forall a. a -> NonEmpty a -> NonEmpty a NonEmpty.intersperse (Char -> Builder Builder.singleton Char ',') (NonEmpty Builder -> NonEmpty Builder) -> (NonEmpty Element -> NonEmpty Builder) -> NonEmpty Element -> NonEmpty Builder forall b c a. (b -> c) -> (a -> b) -> a -> c . (Element -> Builder) -> NonEmpty Element -> NonEmpty Builder forall a b. (a -> b) -> NonEmpty a -> NonEmpty b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Element -> Builder Element.toBuilder ) (Either Wildcard (NonEmpty Element) -> Builder) -> (Field -> Either Wildcard (NonEmpty Element)) -> Field -> Builder forall b c a. (b -> c) -> (a -> b) -> a -> c . Field -> Either Wildcard (NonEmpty Element) toEither isValid :: (Word.Word8, Word.Word8) -> Field -> Bool isValid :: (Word8, Word8) -> Field -> Bool isValid (Word8, Word8) tuple = (Wildcard -> Bool) -> (NonEmpty Element -> Bool) -> Either Wildcard (NonEmpty Element) -> Bool forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (Bool -> Wildcard -> Bool forall a b. a -> b -> a const Bool True) ((Element -> Bool) -> NonEmpty Element -> Bool forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool all ((Element -> Bool) -> NonEmpty Element -> Bool) -> (Element -> Bool) -> NonEmpty Element -> Bool forall a b. (a -> b) -> a -> b $ (Word8, Word8) -> Element -> Bool Element.isValid (Word8, Word8) tuple) (Either Wildcard (NonEmpty Element) -> Bool) -> (Field -> Either Wildcard (NonEmpty Element)) -> Field -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . Field -> Either Wildcard (NonEmpty Element) toEither expand :: (Word.Word8, Word.Word8) -> Field -> Set.Set Word.Word8 expand :: (Word8, Word8) -> Field -> Set Word8 expand (Word8, Word8) tuple = (Wildcard -> Set Word8) -> (NonEmpty Element -> Set Word8) -> Either Wildcard (NonEmpty Element) -> Set Word8 forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (Set Word8 -> Wildcard -> Set Word8 forall a b. a -> b -> a const (Set Word8 -> Wildcard -> Set Word8) -> ([Word8] -> Set Word8) -> [Word8] -> Wildcard -> Set Word8 forall b c a. (b -> c) -> (a -> b) -> a -> c . [Word8] -> Set Word8 forall a. Ord a => [a] -> Set a Set.fromList ([Word8] -> Wildcard -> Set Word8) -> [Word8] -> Wildcard -> Set Word8 forall a b. (a -> b) -> a -> b $ (Word8, Word8) -> [Word8] forall a. Enum a => (a, a) -> [a] Tuple.toSequence (Word8, Word8) tuple) (NonEmpty (Set Word8) -> Set Word8 forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a Set.unions (NonEmpty (Set Word8) -> Set Word8) -> (NonEmpty Element -> NonEmpty (Set Word8)) -> NonEmpty Element -> Set Word8 forall b c a. (b -> c) -> (a -> b) -> a -> c . (Element -> Set Word8) -> NonEmpty Element -> NonEmpty (Set Word8) forall a b. (a -> b) -> NonEmpty a -> NonEmpty b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Element -> Set Word8 Element.expand) (Either Wildcard (NonEmpty Element) -> Set Word8) -> (Field -> Either Wildcard (NonEmpty Element)) -> Field -> Set Word8 forall b c a. (b -> c) -> (a -> b) -> a -> c . Field -> Either Wildcard (NonEmpty Element) toEither isWildcard :: Field -> Bool isWildcard :: Field -> Bool isWildcard = Either Wildcard (NonEmpty Element) -> Bool forall a b. Either a b -> Bool Either.isLeft (Either Wildcard (NonEmpty Element) -> Bool) -> (Field -> Either Wildcard (NonEmpty Element)) -> Field -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . Field -> Either Wildcard (NonEmpty Element) toEither