{-# 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 forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Field -> Field -> Bool $c/= :: Field -> Field -> Bool == :: Field -> Field -> Bool $c== :: Field -> Field -> Bool Eq, Int -> Field -> ShowS [Field] -> ShowS Field -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Field] -> ShowS $cshowList :: [Field] -> ShowS show :: Field -> String $cshow :: Field -> String showsPrec :: Int -> Field -> ShowS $cshowsPrec :: Int -> Field -> ShowS Show) fromEither :: Either Wildcard.Wildcard (NonEmpty.NonEmpty Element.Element) -> Field fromEither :: Either Wildcard (NonEmpty Element) -> Field fromEither = coerce :: 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 = coerce :: 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> 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 forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Wildcard Wildcard.parsec (forall s u (m :: * -> *) a sep. ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m (NonEmpty a) Parsec.sepByNE forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Element Element.parsec forall a b. (a -> b) -> a -> b $ 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 = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either Wildcard -> Builder Wildcard.toBuilder ( forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m Foldable.fold forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. a -> NonEmpty a -> NonEmpty a NonEmpty.intersperse (Char -> Builder Builder.singleton Char ',') forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Element -> Builder Element.toBuilder ) 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 = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (forall a b. a -> b -> a const Bool True) (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool all forall a b. (a -> b) -> a -> b $ (Word8, Word8) -> Element -> Bool Element.isValid (Word8, Word8) tuple) 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 = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (forall a b. a -> b -> a const forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Ord a => [a] -> Set a Set.fromList forall a b. (a -> b) -> a -> b $ forall a. Enum a => (a, a) -> [a] Tuple.toSequence (Word8, Word8) tuple) (forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a Set.unions forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Element -> Set Word8 Element.expand) forall b c a. (b -> c) -> (a -> b) -> a -> c . Field -> Either Wildcard (NonEmpty Element) toEither isWildcard :: Field -> Bool isWildcard :: Field -> Bool isWildcard = forall a b. Either a b -> Bool Either.isLeft forall b c a. (b -> c) -> (a -> b) -> a -> c . Field -> Either Wildcard (NonEmpty Element) toEither