{-# LANGUAGE FunctionalDependencies #-} module HaskellCI.Config.Empty where import HaskellCI.Prelude import qualified Distribution.FieldGrammar as C import qualified Distribution.Fields as C import HaskellCI.OptionsGrammar newtype EmptyGrammar s a = EG { forall s a. EmptyGrammar s a -> Either (NonEmpty FieldName) a runEG :: Either (NonEmpty C.FieldName) a } deriving (forall a b. (a -> b) -> EmptyGrammar s a -> EmptyGrammar s b) -> (forall a b. a -> EmptyGrammar s b -> EmptyGrammar s a) -> Functor (EmptyGrammar s) forall a b. a -> EmptyGrammar s b -> EmptyGrammar s a forall a b. (a -> b) -> EmptyGrammar s a -> EmptyGrammar s b forall s a b. a -> EmptyGrammar s b -> EmptyGrammar s a forall s a b. (a -> b) -> EmptyGrammar s a -> EmptyGrammar s b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f $cfmap :: forall s a b. (a -> b) -> EmptyGrammar s a -> EmptyGrammar s b fmap :: forall a b. (a -> b) -> EmptyGrammar s a -> EmptyGrammar s b $c<$ :: forall s a b. a -> EmptyGrammar s b -> EmptyGrammar s a <$ :: forall a b. a -> EmptyGrammar s b -> EmptyGrammar s a Functor instance Applicative (EmptyGrammar s) where pure :: forall a. a -> EmptyGrammar s a pure a x = Either (NonEmpty FieldName) a -> EmptyGrammar s a forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (a -> Either (NonEmpty FieldName) a forall a b. b -> Either a b Right a x) EG Either (NonEmpty FieldName) (a -> b) f <*> :: forall a b. EmptyGrammar s (a -> b) -> EmptyGrammar s a -> EmptyGrammar s b <*> EG Either (NonEmpty FieldName) a x = Either (NonEmpty FieldName) b -> EmptyGrammar s b forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (Either (NonEmpty FieldName) (a -> b) -> Either (NonEmpty FieldName) a -> Either (NonEmpty FieldName) b forall {a} {t} {b}. Semigroup a => Either a (t -> b) -> Either a t -> Either a b apVal Either (NonEmpty FieldName) (a -> b) f Either (NonEmpty FieldName) a x) where apVal :: Either a (t -> b) -> Either a t -> Either a b apVal (Right t -> b g) (Right t y) = b -> Either a b forall a b. b -> Either a b Right (t -> b g t y) apVal (Right t -> b _) (Left a y) = a -> Either a b forall a b. a -> Either a b Left a y apVal (Left a g) (Right t _) = a -> Either a b forall a b. a -> Either a b Left a g apVal (Left a g) (Left a y) = a -> Either a b forall a b. a -> Either a b Left (a g a -> a -> a forall a. Semigroup a => a -> a -> a <> a y) instance C.FieldGrammar Typeable EmptyGrammar where blurFieldGrammar :: forall a b d. ALens' a b -> EmptyGrammar b d -> EmptyGrammar a d blurFieldGrammar ALens' a b _ = EmptyGrammar b d -> EmptyGrammar a d forall a b. Coercible a b => a -> b coerce uniqueFieldAla :: forall b a s. (Typeable b, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> EmptyGrammar s a uniqueFieldAla FieldName fn a -> b _ ALens' s a _ = Either (NonEmpty FieldName) a -> EmptyGrammar s a forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (NonEmpty FieldName -> Either (NonEmpty FieldName) a forall a b. a -> Either a b Left (FieldName -> NonEmpty FieldName forall a. a -> NonEmpty a forall (f :: * -> *) a. Applicative f => a -> f a pure FieldName fn)) booleanFieldDef :: forall s. FieldName -> ALens' s Bool -> Bool -> EmptyGrammar s Bool booleanFieldDef FieldName _ ALens' s Bool _ Bool def = Either (NonEmpty FieldName) Bool -> EmptyGrammar s Bool forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (Bool -> Either (NonEmpty FieldName) Bool forall a b. b -> Either a b Right Bool def) optionalFieldAla :: forall b a s. (Typeable b, Newtype a b) => FieldName -> (a -> b) -> ALens' s (Maybe a) -> EmptyGrammar s (Maybe a) optionalFieldAla FieldName _ a -> b _ ALens' s (Maybe a) _ = Either (NonEmpty FieldName) (Maybe a) -> EmptyGrammar s (Maybe a) forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (Maybe a -> Either (NonEmpty FieldName) (Maybe a) forall a b. b -> Either a b Right Maybe a forall a. Maybe a Nothing) optionalFieldDefAla :: forall b a s. (Typeable b, Newtype a b, Eq a) => FieldName -> (a -> b) -> ALens' s a -> a -> EmptyGrammar s a optionalFieldDefAla FieldName _ a -> b _ ALens' s a _ a def = Either (NonEmpty FieldName) a -> EmptyGrammar s a forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (a -> Either (NonEmpty FieldName) a forall a b. b -> Either a b Right a def) monoidalFieldAla :: forall b a s. (Typeable b, Monoid a, Newtype a b) => FieldName -> (a -> b) -> ALens' s a -> EmptyGrammar s a monoidalFieldAla FieldName _ a -> b _ ALens' s a _ = Either (NonEmpty FieldName) a -> EmptyGrammar s a forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (a -> Either (NonEmpty FieldName) a forall a b. b -> Either a b Right a forall a. Monoid a => a mempty) freeTextField :: forall s. FieldName -> ALens' s (Maybe String) -> EmptyGrammar s (Maybe String) freeTextField FieldName _ ALens' s (Maybe String) _ = Either (NonEmpty FieldName) (Maybe String) -> EmptyGrammar s (Maybe String) forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (Maybe String -> Either (NonEmpty FieldName) (Maybe String) forall a b. b -> Either a b Right Maybe String forall a. Maybe a Nothing) freeTextFieldDef :: forall s. FieldName -> ALens' s String -> EmptyGrammar s String freeTextFieldDef FieldName _ ALens' s String _ = Either (NonEmpty FieldName) String -> EmptyGrammar s String forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (String -> Either (NonEmpty FieldName) String forall a b. b -> Either a b Right String "") freeTextFieldDefST :: forall s. FieldName -> ALens' s ShortText -> EmptyGrammar s ShortText freeTextFieldDefST FieldName _ ALens' s ShortText _ = Either (NonEmpty FieldName) ShortText -> EmptyGrammar s ShortText forall s a. Either (NonEmpty FieldName) a -> EmptyGrammar s a EG (ShortText -> Either (NonEmpty FieldName) ShortText forall a b. b -> Either a b Right (String -> ShortText forall a. IsString a => String -> a fromString String "")) prefixedFields :: forall s. FieldName -> ALens' s [(String, String)] -> EmptyGrammar s [(String, String)] prefixedFields FieldName _ ALens' s [(String, String)] _ = [(String, String)] -> EmptyGrammar s [(String, String)] forall a. a -> EmptyGrammar s a forall (f :: * -> *) a. Applicative f => a -> f a pure [] knownField :: forall s. FieldName -> EmptyGrammar s () knownField FieldName _ = () -> EmptyGrammar s () forall a. a -> EmptyGrammar s a forall (f :: * -> *) a. Applicative f => a -> f a pure () deprecatedSince :: forall s a. CabalSpecVersion -> String -> EmptyGrammar s a -> EmptyGrammar s a deprecatedSince CabalSpecVersion _ String _ = EmptyGrammar s a -> EmptyGrammar s a forall a. a -> a id availableSince :: forall a s. CabalSpecVersion -> a -> EmptyGrammar s a -> EmptyGrammar s a availableSince CabalSpecVersion _ a _ = EmptyGrammar s a -> EmptyGrammar s a forall a. a -> a id removedIn :: forall s a. CabalSpecVersion -> String -> EmptyGrammar s a -> EmptyGrammar s a removedIn CabalSpecVersion _ String _ = EmptyGrammar s a -> EmptyGrammar s a forall a. a -> a id hiddenField :: forall s a. EmptyGrammar s a -> EmptyGrammar s a hiddenField = EmptyGrammar s a -> EmptyGrammar s a forall a. a -> a id instance OptionsGrammar Typeable EmptyGrammar