{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Stack.Types.ApplyGhcOptions
( ApplyGhcOptions (..)
) where
import Data.Aeson.Types ( FromJSON (..), withText )
import Stack.Prelude
data ApplyGhcOptions
= AGOTargets
| AGOLocals
| AGOEverything
deriving (ApplyGhcOptions
ApplyGhcOptions -> ApplyGhcOptions -> Bounded ApplyGhcOptions
forall a. a -> a -> Bounded a
$cminBound :: ApplyGhcOptions
minBound :: ApplyGhcOptions
$cmaxBound :: ApplyGhcOptions
maxBound :: ApplyGhcOptions
Bounded, Int -> ApplyGhcOptions
ApplyGhcOptions -> Int
ApplyGhcOptions -> [ApplyGhcOptions]
ApplyGhcOptions -> ApplyGhcOptions
ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
ApplyGhcOptions
-> ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
(ApplyGhcOptions -> ApplyGhcOptions)
-> (ApplyGhcOptions -> ApplyGhcOptions)
-> (Int -> ApplyGhcOptions)
-> (ApplyGhcOptions -> Int)
-> (ApplyGhcOptions -> [ApplyGhcOptions])
-> (ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions])
-> (ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions])
-> (ApplyGhcOptions
-> ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions])
-> Enum ApplyGhcOptions
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ApplyGhcOptions -> ApplyGhcOptions
succ :: ApplyGhcOptions -> ApplyGhcOptions
$cpred :: ApplyGhcOptions -> ApplyGhcOptions
pred :: ApplyGhcOptions -> ApplyGhcOptions
$ctoEnum :: Int -> ApplyGhcOptions
toEnum :: Int -> ApplyGhcOptions
$cfromEnum :: ApplyGhcOptions -> Int
fromEnum :: ApplyGhcOptions -> Int
$cenumFrom :: ApplyGhcOptions -> [ApplyGhcOptions]
enumFrom :: ApplyGhcOptions -> [ApplyGhcOptions]
$cenumFromThen :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
enumFromThen :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
$cenumFromTo :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
enumFromTo :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
$cenumFromThenTo :: ApplyGhcOptions
-> ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
enumFromThenTo :: ApplyGhcOptions
-> ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
Enum, ApplyGhcOptions -> ApplyGhcOptions -> Bool
(ApplyGhcOptions -> ApplyGhcOptions -> Bool)
-> (ApplyGhcOptions -> ApplyGhcOptions -> Bool)
-> Eq ApplyGhcOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
== :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c/= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
/= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
Eq, Eq ApplyGhcOptions
Eq ApplyGhcOptions
-> (ApplyGhcOptions -> ApplyGhcOptions -> Ordering)
-> (ApplyGhcOptions -> ApplyGhcOptions -> Bool)
-> (ApplyGhcOptions -> ApplyGhcOptions -> Bool)
-> (ApplyGhcOptions -> ApplyGhcOptions -> Bool)
-> (ApplyGhcOptions -> ApplyGhcOptions -> Bool)
-> (ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions)
-> (ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions)
-> Ord ApplyGhcOptions
ApplyGhcOptions -> ApplyGhcOptions -> Bool
ApplyGhcOptions -> ApplyGhcOptions -> Ordering
ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
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 :: ApplyGhcOptions -> ApplyGhcOptions -> Ordering
compare :: ApplyGhcOptions -> ApplyGhcOptions -> Ordering
$c< :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
< :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c<= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
<= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c> :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
> :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c>= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
>= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$cmax :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
max :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
$cmin :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
min :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
Ord, ReadPrec [ApplyGhcOptions]
ReadPrec ApplyGhcOptions
Int -> ReadS ApplyGhcOptions
ReadS [ApplyGhcOptions]
(Int -> ReadS ApplyGhcOptions)
-> ReadS [ApplyGhcOptions]
-> ReadPrec ApplyGhcOptions
-> ReadPrec [ApplyGhcOptions]
-> Read ApplyGhcOptions
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ApplyGhcOptions
readsPrec :: Int -> ReadS ApplyGhcOptions
$creadList :: ReadS [ApplyGhcOptions]
readList :: ReadS [ApplyGhcOptions]
$creadPrec :: ReadPrec ApplyGhcOptions
readPrec :: ReadPrec ApplyGhcOptions
$creadListPrec :: ReadPrec [ApplyGhcOptions]
readListPrec :: ReadPrec [ApplyGhcOptions]
Read, Int -> ApplyGhcOptions -> ShowS
[ApplyGhcOptions] -> ShowS
ApplyGhcOptions -> [Char]
(Int -> ApplyGhcOptions -> ShowS)
-> (ApplyGhcOptions -> [Char])
-> ([ApplyGhcOptions] -> ShowS)
-> Show ApplyGhcOptions
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplyGhcOptions -> ShowS
showsPrec :: Int -> ApplyGhcOptions -> ShowS
$cshow :: ApplyGhcOptions -> [Char]
show :: ApplyGhcOptions -> [Char]
$cshowList :: [ApplyGhcOptions] -> ShowS
showList :: [ApplyGhcOptions] -> ShowS
Show)
instance FromJSON ApplyGhcOptions where
parseJSON :: Value -> Parser ApplyGhcOptions
parseJSON = [Char]
-> (Text -> Parser ApplyGhcOptions)
-> Value
-> Parser ApplyGhcOptions
forall a. [Char] -> (Text -> Parser a) -> Value -> Parser a
withText [Char]
"ApplyGhcOptions" ((Text -> Parser ApplyGhcOptions)
-> Value -> Parser ApplyGhcOptions)
-> (Text -> Parser ApplyGhcOptions)
-> Value
-> Parser ApplyGhcOptions
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text
t of
Text
"targets" -> ApplyGhcOptions -> Parser ApplyGhcOptions
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ApplyGhcOptions
AGOTargets
Text
"locals" -> ApplyGhcOptions -> Parser ApplyGhcOptions
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ApplyGhcOptions
AGOLocals
Text
"everything" -> ApplyGhcOptions -> Parser ApplyGhcOptions
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ApplyGhcOptions
AGOEverything
Text
_ -> [Char] -> Parser ApplyGhcOptions
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> Parser ApplyGhcOptions)
-> [Char] -> Parser ApplyGhcOptions
forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid ApplyGhcOptions: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
t