{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS -fno-warn-orphans #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}

module FP.API
    ( module FP.API
    , module FP.API.Types
    ) where

import Data.Text
import FP.API.Types
import Prelude

#ifndef FAY
import Data.Serialize
import GHC.Generics (Generic)
#endif

-- | Convert a theme to a string.
themeToString :: Theme -> String
themeToString Zenburn = "zenburn"
themeToString Panda   = "panda"
themeToString Monokai = "monokai"

-- | Get a human-readable name for a theme.
themeName :: Theme -> String
themeName Zenburn = "Zenburn"
themeName Panda = "Panda"
themeName Monokai = "Monokai"

-- | Get a human-readable description of a string.
themeDescription :: Theme -> String
themeDescription Zenburn = "A theme based on the popular Zenburn theme"
themeDescription Panda = "The default FP Development Environment theme"
themeDescription Monokai = "A Sublime inspired theme based on Monokai"

-- | Similar to [minBound..maxBound], with our own custom ordering.
enumerateThemes :: [Theme]
enumerateThemes = [Panda,Zenburn,Monokai]

-- | The default theme to use when there is no existing theme.
defaultTheme :: Theme
defaultTheme = Panda

-- | The default font size to use.
defaultFontSize :: Int
defaultFontSize = 14

defaultSearchStyle :: Bool
defaultSearchStyle = False

-- | Default license to use upon initialization.
defaultLicense :: IdeLicense
defaultLicense = ILCommunity

-- | Error that can be returned by some commands, which indicates that the
--   command requires that the settings file be valid.
invalidSettingsError :: Text
invalidSettingsError = fromString "Invalid settings file"

-- | Error that can be returned by 'GetProjectMessages', which
-- indicates that the backend server hasn't started yet.  In order to
-- cause the server to run, some normal command needs to be executed
-- (not a project messages poll, though).
serverSessionNotReadyError :: Text
serverSessionNotReadyError = fromString "Server session not yet ready"

-- | The filepath used for the settings file.
projectSettingsPath :: Text
projectSettingsPath = fromString ".project-settings.yml"

-- | Determine whether a git branch name is valid.
--
--   TODO: This could be better.  See, e.g. the regexes here:
--   http://stackoverflow.com/a/12093994/1164871
validGitBranch :: String -> Bool
validGitBranch = Prelude.all ok where
  ok c = elem c "abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789-_."

--------------------------------------------------------------------------------
-- Access control

-- | Action that roles can perform.
data Action
  = DoBuildExecutables
  | DoDeployment
  | DoPrivateProjects
  | DoMakeCommercialProducts
  | DoGitStuff
  | DoExternalEditor
  deriving (Show, Eq
#ifndef FAY
           , Generic
#endif
           )

#ifndef FAY
instance Serialize Action
#endif

-- | Give a human readable description for actions that could be used
-- in a sentence.
describeAction :: Action -> Text
describeAction = fromString . describe where
  describe x =
    case x of
      DoBuildExecutables       -> "build executables"
      DoDeployment             -> "make deployments"
      DoPrivateProjects        -> "have private projects"
      DoGitStuff               -> "perform Git actions"
      DoMakeCommercialProducts -> "use the IDE for commercial work"
      DoExternalEditor         -> "use an external editor"

-- | Can the given role do the given action?
canDo :: IdeLicense -> Action -> Bool
canDo ILProfessional = const True
canDo ILPersonal     = flip elem [DoBuildExecutables,DoDeployment,DoMakeCommercialProducts,DoGitStuff,DoExternalEditor]
canDo ILCommunity    = flip elem [DoBuildExecutables,DoDeployment,DoMakeCommercialProducts,DoGitStuff,DoExternalEditor]

-- | Get the name of the license, for use in code IDs and such.
licenseName :: IdeLicense -> Text
licenseName ILPersonal = fromString "personal"
licenseName ILCommunity = fromString "community"
licenseName ILProfessional = fromString "professional"