{-# LANGUAGE FlexibleContexts #-} module Saturn.Unstable.Type.Wildcard where import qualified Control.Monad as Monad import qualified Data.Coerce as Coerce import qualified Data.Text.Lazy.Builder as Builder import qualified Text.Parsec as Parsec newtype Wildcard = Wildcard () deriving (Wildcard -> Wildcard -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Wildcard -> Wildcard -> Bool $c/= :: Wildcard -> Wildcard -> Bool == :: Wildcard -> Wildcard -> Bool $c== :: Wildcard -> Wildcard -> Bool Eq, Int -> Wildcard -> ShowS [Wildcard] -> ShowS Wildcard -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Wildcard] -> ShowS $cshowList :: [Wildcard] -> ShowS show :: Wildcard -> String $cshow :: Wildcard -> String showsPrec :: Int -> Wildcard -> ShowS $cshowsPrec :: Int -> Wildcard -> ShowS Show) fromUnit :: () -> Wildcard fromUnit :: () -> Wildcard fromUnit = coerce :: forall a b. Coercible a b => a -> b Coerce.coerce toUnit :: Wildcard -> () toUnit :: Wildcard -> () toUnit = coerce :: forall a b. Coercible a b => a -> b Coerce.coerce parsec :: (Parsec.Stream s m Char) => Parsec.ParsecT s u m Wildcard parsec :: forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Wildcard parsec = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap () -> Wildcard fromUnit forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (f :: * -> *) a. Functor f => f a -> f () Monad.void 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 :: Wildcard -> Builder.Builder toBuilder :: Wildcard -> Builder toBuilder = forall a b. a -> b -> a const forall a b. (a -> b) -> a -> b $ Char -> Builder Builder.singleton Char '*'