{-# LANGUAGE NoImplicitPrelude #-}
module Stack.Types.CompilerBuild
( CompilerBuild (..)
, compilerBuildName
, compilerBuildSuffix
, parseCompilerBuild
) where
import Data.Aeson.Types ( FromJSON, parseJSON, withText )
import Data.Text as T
import Stack.Prelude
data CompilerBuild
= CompilerBuildStandard
| CompilerBuildSpecialized String
deriving Int -> CompilerBuild -> ShowS
[CompilerBuild] -> ShowS
CompilerBuild -> String
(Int -> CompilerBuild -> ShowS)
-> (CompilerBuild -> String)
-> ([CompilerBuild] -> ShowS)
-> Show CompilerBuild
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompilerBuild -> ShowS
showsPrec :: Int -> CompilerBuild -> ShowS
$cshow :: CompilerBuild -> String
show :: CompilerBuild -> String
$cshowList :: [CompilerBuild] -> ShowS
showList :: [CompilerBuild] -> ShowS
Show
instance FromJSON CompilerBuild where
parseJSON :: Value -> Parser CompilerBuild
parseJSON =
String
-> (Text -> Parser CompilerBuild) -> Value -> Parser CompilerBuild
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText
String
"CompilerBuild"
((SomeException -> Parser CompilerBuild)
-> (CompilerBuild -> Parser CompilerBuild)
-> Either SomeException CompilerBuild
-> Parser CompilerBuild
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser CompilerBuild
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser CompilerBuild)
-> (SomeException -> String)
-> SomeException
-> Parser CompilerBuild
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> String
forall a. Show a => a -> String
show) CompilerBuild -> Parser CompilerBuild
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either SomeException CompilerBuild -> Parser CompilerBuild)
-> (Text -> Either SomeException CompilerBuild)
-> Text
-> Parser CompilerBuild
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either SomeException CompilerBuild
forall (m :: * -> *). MonadThrow m => String -> m CompilerBuild
parseCompilerBuild (String -> Either SomeException CompilerBuild)
-> (Text -> String) -> Text -> Either SomeException CompilerBuild
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
compilerBuildName :: CompilerBuild -> String
compilerBuildName :: CompilerBuild -> String
compilerBuildName CompilerBuild
CompilerBuildStandard = String
"standard"
compilerBuildName (CompilerBuildSpecialized String
s) = String
s
compilerBuildSuffix :: CompilerBuild -> String
compilerBuildSuffix :: CompilerBuild -> String
compilerBuildSuffix CompilerBuild
CompilerBuildStandard = String
""
compilerBuildSuffix (CompilerBuildSpecialized String
s) = Char
'-' Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
parseCompilerBuild :: (MonadThrow m) => String -> m CompilerBuild
parseCompilerBuild :: forall (m :: * -> *). MonadThrow m => String -> m CompilerBuild
parseCompilerBuild String
"" = CompilerBuild -> m CompilerBuild
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CompilerBuild
CompilerBuildStandard
parseCompilerBuild String
"standard" = CompilerBuild -> m CompilerBuild
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CompilerBuild
CompilerBuildStandard
parseCompilerBuild String
name = CompilerBuild -> m CompilerBuild
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> CompilerBuild
CompilerBuildSpecialized String
name)