{-# LANGUAGE ViewPatterns #-}
module Summoner.ProjectData
       ( ProjectData (..)
       , GhcVer (..)
       , supportedGhcVers
       , parseGhcVer
       , showGhcVer
       , latestLts
       , baseNopreludeVer
       , Decision (..)
       , CustomPrelude (..)
       , Answer (..)
       , yesOrNo
       ) where
import Universum
import Generics.Deriving.Monoid (GMonoid (..))
import Generics.Deriving.Semigroup (GSemigroup (..))
import qualified Data.Text as T
data ProjectData = ProjectData
    { repo           :: Text   
    , owner          :: Text   
    , description    :: Text   
    , nm             :: Text   
    , email          :: Text   
    , year           :: Text   
    , category       :: Text   
    , license        :: Text   
    , licenseText    :: Text   
    , github         :: Bool   
    , travis         :: Bool   
    , appVey         :: Bool   
    , script         :: Bool   
    , isLib          :: Bool   
    , isExe          :: Bool   
    , test           :: Bool   
    , bench          :: Bool   
    , testedVersions :: [GhcVer]  
    , base           :: Text 
    , prelude        :: Maybe CustomPrelude  
    , extensions     :: [Text] 
    } deriving (Show)
data Decision = Yes | Nop | Idk
    deriving (Show, Eq, Enum, Bounded, Generic)
instance Semigroup Decision where
    (<>) :: Decision -> Decision -> Decision
    Idk <> x   = x
    x   <> Idk = x
    _   <> x   = x
instance Monoid Decision where
    mempty  = Idk
    mappend = (<>)
instance GSemigroup Decision where
    gsappend = (<>)
instance GMonoid Decision where
    gmempty = mempty
    gmappend = (<>)
data GhcVer = Ghc7103
            | Ghc801
            | Ghc802
            | Ghc822
            deriving (Eq, Ord, Show, Enum, Bounded)
supportedGhcVers :: [GhcVer]
supportedGhcVers = [minBound .. maxBound]
showGhcVer :: GhcVer -> Text
showGhcVer Ghc7103 = "7.10.3"
showGhcVer Ghc801  = "8.0.1"
showGhcVer Ghc802  = "8.0.2"
showGhcVer Ghc822  = "8.2.2"
parseGhcVer :: Text -> Maybe GhcVer
parseGhcVer "7.10.3" = Just Ghc7103
parseGhcVer "8.0.1"  = Just Ghc801
parseGhcVer "8.0.2"  = Just Ghc802
parseGhcVer "8.2.2"  = Just Ghc822
parseGhcVer _        = Nothing
latestLts :: GhcVer -> Text
latestLts Ghc7103 = "6.35"
latestLts Ghc801  = "7.24"
latestLts Ghc802  = "9.21"
latestLts Ghc822  = "11.10"
baseNopreludeVer :: GhcVer -> Text
baseNopreludeVer Ghc7103 = "4.8.0.2"
baseNopreludeVer Ghc801  = "4.9.0.0"
baseNopreludeVer Ghc802  = "4.9.1.0"
baseNopreludeVer Ghc822  = "4.10.1.0"
data CustomPrelude = Prelude
    { cpPackage :: Text
    , cpModule  :: Text
    } deriving (Show)
data Answer = Y | N
yesOrNo :: Text -> Maybe Answer
yesOrNo (T.toLower -> answer )
    | T.null answer = Just Y
    | answer `elem` ["yes", "y", "ys"] = Just Y
    | answer `elem` ["no", "n"]  = Just N
    | otherwise = Nothing