{-# LANGUAGE NoImplicitPrelude #-} module Stack.Types.AllowNewerDeps ( AllowNewerDeps (..) ) where import Data.Aeson.Types ( FromJSON (..) ) import qualified Distribution.PackageDescription as C import Generics.Deriving.Monoid ( mappenddefault, memptydefault ) import Stack.Prelude newtype AllowNewerDeps = AllowNewerDeps [PackageName] deriving (AllowNewerDeps -> AllowNewerDeps -> Bool (AllowNewerDeps -> AllowNewerDeps -> Bool) -> (AllowNewerDeps -> AllowNewerDeps -> Bool) -> Eq AllowNewerDeps forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: AllowNewerDeps -> AllowNewerDeps -> Bool == :: AllowNewerDeps -> AllowNewerDeps -> Bool $c/= :: AllowNewerDeps -> AllowNewerDeps -> Bool /= :: AllowNewerDeps -> AllowNewerDeps -> Bool Eq, (forall x. AllowNewerDeps -> Rep AllowNewerDeps x) -> (forall x. Rep AllowNewerDeps x -> AllowNewerDeps) -> Generic AllowNewerDeps forall x. Rep AllowNewerDeps x -> AllowNewerDeps forall x. AllowNewerDeps -> Rep AllowNewerDeps x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. AllowNewerDeps -> Rep AllowNewerDeps x from :: forall x. AllowNewerDeps -> Rep AllowNewerDeps x $cto :: forall x. Rep AllowNewerDeps x -> AllowNewerDeps to :: forall x. Rep AllowNewerDeps x -> AllowNewerDeps Generic, Eq AllowNewerDeps Eq AllowNewerDeps -> (AllowNewerDeps -> AllowNewerDeps -> Ordering) -> (AllowNewerDeps -> AllowNewerDeps -> Bool) -> (AllowNewerDeps -> AllowNewerDeps -> Bool) -> (AllowNewerDeps -> AllowNewerDeps -> Bool) -> (AllowNewerDeps -> AllowNewerDeps -> Bool) -> (AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps) -> (AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps) -> Ord AllowNewerDeps AllowNewerDeps -> AllowNewerDeps -> Bool AllowNewerDeps -> AllowNewerDeps -> Ordering AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: AllowNewerDeps -> AllowNewerDeps -> Ordering compare :: AllowNewerDeps -> AllowNewerDeps -> Ordering $c< :: AllowNewerDeps -> AllowNewerDeps -> Bool < :: AllowNewerDeps -> AllowNewerDeps -> Bool $c<= :: AllowNewerDeps -> AllowNewerDeps -> Bool <= :: AllowNewerDeps -> AllowNewerDeps -> Bool $c> :: AllowNewerDeps -> AllowNewerDeps -> Bool > :: AllowNewerDeps -> AllowNewerDeps -> Bool $c>= :: AllowNewerDeps -> AllowNewerDeps -> Bool >= :: AllowNewerDeps -> AllowNewerDeps -> Bool $cmax :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps max :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps $cmin :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps min :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps Ord, ReadPrec [AllowNewerDeps] ReadPrec AllowNewerDeps Int -> ReadS AllowNewerDeps ReadS [AllowNewerDeps] (Int -> ReadS AllowNewerDeps) -> ReadS [AllowNewerDeps] -> ReadPrec AllowNewerDeps -> ReadPrec [AllowNewerDeps] -> Read AllowNewerDeps forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a $creadsPrec :: Int -> ReadS AllowNewerDeps readsPrec :: Int -> ReadS AllowNewerDeps $creadList :: ReadS [AllowNewerDeps] readList :: ReadS [AllowNewerDeps] $creadPrec :: ReadPrec AllowNewerDeps readPrec :: ReadPrec AllowNewerDeps $creadListPrec :: ReadPrec [AllowNewerDeps] readListPrec :: ReadPrec [AllowNewerDeps] Read, Int -> AllowNewerDeps -> ShowS [AllowNewerDeps] -> ShowS AllowNewerDeps -> String (Int -> AllowNewerDeps -> ShowS) -> (AllowNewerDeps -> String) -> ([AllowNewerDeps] -> ShowS) -> Show AllowNewerDeps forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> AllowNewerDeps -> ShowS showsPrec :: Int -> AllowNewerDeps -> ShowS $cshow :: AllowNewerDeps -> String show :: AllowNewerDeps -> String $cshowList :: [AllowNewerDeps] -> ShowS showList :: [AllowNewerDeps] -> ShowS Show) instance Semigroup AllowNewerDeps where <> :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps (<>) = AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps forall a. (Generic a, Monoid' (Rep a)) => a -> a -> a mappenddefault instance Monoid AllowNewerDeps where mappend :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps mappend = AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps forall a. Semigroup a => a -> a -> a (<>) mempty :: AllowNewerDeps mempty = AllowNewerDeps forall a. (Generic a, Monoid' (Rep a)) => a memptydefault instance FromJSON AllowNewerDeps where parseJSON :: Value -> Parser AllowNewerDeps parseJSON = ([String] -> AllowNewerDeps) -> Parser [String] -> Parser AllowNewerDeps forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ([PackageName] -> AllowNewerDeps AllowNewerDeps ([PackageName] -> AllowNewerDeps) -> ([String] -> [PackageName]) -> [String] -> AllowNewerDeps forall b c a. (b -> c) -> (a -> b) -> a -> c . (String -> PackageName) -> [String] -> [PackageName] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap String -> PackageName C.mkPackageName) (Parser [String] -> Parser AllowNewerDeps) -> (Value -> Parser [String]) -> Value -> Parser AllowNewerDeps forall b c a. (b -> c) -> (a -> b) -> a -> c . Value -> Parser [String] forall a. FromJSON a => Value -> Parser a parseJSON