{-# LANGUAGE NoImplicitPrelude #-}
module Stack.Types.CompilerBuild
  (CompilerBuild(..)
  ,compilerBuildName
  ,compilerBuildSuffix
  ,parseCompilerBuild
  ) where
import           Stack.Prelude
import           Pantry.Internal.AesonExtended (FromJSON, parseJSON, withText)
import           Data.Text as T
data CompilerBuild
    = CompilerBuildStandard
    | CompilerBuildSpecialized String
    deriving (Show)
instance FromJSON CompilerBuild where
    
    parseJSON =
        withText
            "CompilerBuild"
            (either (fail . show) return . parseCompilerBuild . T.unpack)
compilerBuildName :: CompilerBuild -> String
compilerBuildName CompilerBuildStandard = "standard"
compilerBuildName (CompilerBuildSpecialized s) = s
compilerBuildSuffix :: CompilerBuild -> String
compilerBuildSuffix CompilerBuildStandard = ""
compilerBuildSuffix (CompilerBuildSpecialized s) = '-' : s
parseCompilerBuild :: (MonadThrow m) => String -> m CompilerBuild
parseCompilerBuild "" = return CompilerBuildStandard
parseCompilerBuild "standard" = return CompilerBuildStandard
parseCompilerBuild name = return (CompilerBuildSpecialized name)