module GitHub.Data.Definitions where
import GitHub.Internal.Prelude
import Prelude ()
import Control.Monad       (mfilter)
import Data.Aeson.Types    (Parser)
import Network.HTTP.Client (HttpException)
import qualified Control.Exception as E
import qualified Data.ByteString   as BS
import qualified Data.Text         as T
import GitHub.Data.Id   (Id)
import GitHub.Data.Name (Name)
import GitHub.Data.URL  (URL (..))
data Error
    = HTTPError !HttpException 
    | ParseError !Text 
    | JsonError !Text 
    | UserError !Text 
    deriving (Show, Typeable)
instance E.Exception Error
data OwnerType = OwnerUser | OwnerOrganization | OwnerBot
    deriving (Eq, Ord, Enum, Bounded, Show, Read, Generic, Typeable, Data)
instance NFData OwnerType
instance Binary OwnerType
data SimpleUser = SimpleUser
    { simpleUserId        :: !(Id User)
    , simpleUserLogin     :: !(Name User)
    , simpleUserAvatarUrl :: !URL
    , simpleUserUrl       :: !URL
    }
    deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData SimpleUser where rnf = genericRnf
instance Binary SimpleUser
data SimpleOrganization = SimpleOrganization
    { simpleOrganizationId        :: !(Id Organization)
    , simpleOrganizationLogin     :: !(Name Organization)
    , simpleOrganizationUrl       :: !URL
    , simpleOrganizationAvatarUrl :: !URL
    }
    deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData SimpleOrganization where rnf = genericRnf
instance Binary SimpleOrganization
data SimpleOwner = SimpleOwner
    { simpleOwnerId        :: !(Id Owner)
    , simpleOwnerLogin     :: !(Name Owner)
    , simpleOwnerUrl       :: !URL
    , simpleOwnerAvatarUrl :: !URL
    , simpleOwnerType      :: !OwnerType
    }
    deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData SimpleOwner where rnf = genericRnf
instance Binary SimpleOwner
data User = User
    { userId          :: !(Id User)
    , userLogin       :: !(Name User)
    , userName        :: !(Maybe Text)
    , userType        :: !OwnerType  
    , userCreatedAt   :: !UTCTime
    , userPublicGists :: !Int
    , userAvatarUrl   :: !URL
    , userFollowers   :: !Int
    , userFollowing   :: !Int
    , userHireable    :: !(Maybe Bool)
    , userBlog        :: !(Maybe Text)
    , userBio         :: !(Maybe Text)
    , userPublicRepos :: !Int
    , userLocation    :: !(Maybe Text)
    , userCompany     :: !(Maybe Text)
    , userEmail       :: !(Maybe Text)
    , userUrl         :: !URL
    , userHtmlUrl     :: !URL
    }
    deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData User where rnf = genericRnf
instance Binary User
data Organization = Organization
    { organizationId          :: !(Id Organization)
    , organizationLogin       :: !(Name Organization)
    , organizationName        :: !(Maybe Text)
    , organizationType        :: !OwnerType  
    , organizationBlog        :: !(Maybe Text)
    , organizationLocation    :: !(Maybe Text)
    , organizationFollowers   :: !Int
    , organizationCompany     :: !(Maybe Text)
    , organizationAvatarUrl   :: !URL
    , organizationPublicGists :: !Int
    , organizationHtmlUrl     :: !URL
    , organizationEmail       :: !(Maybe Text)
    , organizationFollowing   :: !Int
    , organizationPublicRepos :: !Int
    , organizationUrl         :: !URL
    , organizationCreatedAt   :: !UTCTime
    }
    deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData Organization where rnf = genericRnf
instance Binary Organization
newtype Owner = Owner (Either User Organization)
    deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData Owner where rnf = genericRnf
instance Binary Owner
fromOwner :: Owner -> Either User Organization
fromOwner (Owner owner) = owner
instance FromJSON OwnerType where
    parseJSON = withText "OwnerType" $ \t -> case T.toLower t of
        "user"         -> pure $ OwnerUser
        "organization" -> pure $ OwnerOrganization
        "bot"          -> pure $ OwnerBot
        _              -> fail $ "Unknown OwnerType: " <> T.unpack t
instance FromJSON SimpleUser where
    parseJSON = withObject "SimpleUser" $ \obj -> do
        SimpleUser
            <$> obj .: "id"
            <*> obj .: "login"
            <*> obj .: "avatar_url"
            <*> obj .: "url"
instance FromJSON SimpleOrganization where
    parseJSON = withObject "SimpleOrganization" $ \obj ->
        SimpleOrganization
            <$> obj .: "id"
            <*> obj .: "login"
            <*> obj .: "url"
            <*> obj .: "avatar_url"
instance FromJSON SimpleOwner where
    parseJSON = withObject "SimpleOwner" $ \obj -> do
        SimpleOwner
            <$> obj .: "id"
            <*> obj .: "login"
            <*> obj .: "url"
            <*> obj .: "avatar_url"
            <*> obj .: "type"
parseUser :: Object -> Parser User
parseUser obj = User
    <$> obj .: "id"
    <*> obj .: "login"
    <*> obj .:? "name"
    <*> obj .: "type"
    <*> obj .: "created_at"
    <*> obj .: "public_gists"
    <*> obj .: "avatar_url"
    <*> obj .: "followers"
    <*> obj .: "following"
    <*> obj .:? "hireable"
    <*> obj .:? "blog"
    <*> obj .:? "bio"
    <*> obj .: "public_repos"
    <*> obj .:? "location"
    <*> obj .:? "company"
    <*> obj .:? "email"
    <*> obj .: "url"
    <*> obj .: "html_url"
parseOrganization :: Object -> Parser Organization
parseOrganization obj = Organization
    <$> obj .: "id"
    <*> obj .: "login"
    <*> obj .:? "name"
    <*> obj .: "type"
    <*> obj .:? "blog"
    <*> obj .:? "location"
    <*> obj .: "followers"
    <*> obj .:? "company"
    <*> obj .: "avatar_url"
    <*> obj .: "public_gists"
    <*> obj .: "html_url"
    <*> obj .:? "email"
    <*> obj .: "following"
    <*> obj .: "public_repos"
    <*> obj .: "url"
    <*> obj .: "created_at"
instance FromJSON User where
    parseJSON = mfilter ((/= OwnerOrganization) . userType) . withObject "User" parseUser
instance FromJSON Organization where
    parseJSON = withObject "Organization" parseOrganization
instance FromJSON Owner where
    parseJSON = withObject "Owner" $ \obj -> do
        t <- obj .: "type"
        case t of
            OwnerUser         -> Owner . Left <$> parseUser obj
            OwnerBot          -> Owner . Left <$> parseUser obj
            OwnerOrganization -> Owner . Right <$> parseOrganization obj
data OrgMemberFilter
    = OrgMemberFilter2faDisabled  
    | OrgMemberFilterAll          
    deriving (Show, Eq, Ord, Enum, Bounded, Typeable, Data, Generic)
data OrgMemberRole
    = OrgMemberRoleAll     
    | OrgMemberRoleAdmin   
    | OrgMemberRoleMember  
    deriving (Show, Eq, Ord, Enum, Bounded, Typeable, Data, Generic)
type QueryString = [(BS.ByteString, Maybe BS.ByteString)]
type Count = Int
newtype IssueNumber = IssueNumber Int
    deriving (Eq, Ord, Show, Generic, Typeable, Data)
unIssueNumber :: IssueNumber -> Int
unIssueNumber (IssueNumber i) = i
instance Hashable IssueNumber
instance Binary IssueNumber
instance NFData IssueNumber where
    rnf (IssueNumber s) = rnf s
instance FromJSON IssueNumber where
    parseJSON = fmap IssueNumber . parseJSON
instance ToJSON IssueNumber where
    toJSON = toJSON . unIssueNumber
data IssueLabel = IssueLabel
    { labelColor :: !Text
    , labelUrl   :: !URL
    , labelName  :: !(Name IssueLabel)
    , labelDesc  :: !(Maybe Text)
    }
  deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData IssueLabel where rnf = genericRnf
instance Binary IssueLabel
instance FromJSON IssueLabel where
    parseJSON = withObject "IssueLabel" $ \o -> IssueLabel
        <$> o .: "color"
        <*> o .:? "url" .!= URL "" 
        <*> o .: "name"
        <*> o .:? "description"
data NewIssueLabel = NewIssueLabel
    { newLabelColor :: !Text
    , newLabelName  :: !(Name NewIssueLabel)
    , newLabelDesc  :: !(Maybe Text)
    }
  deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData NewIssueLabel where rnf = genericRnf
instance Binary NewIssueLabel
instance ToJSON NewIssueLabel where
    toJSON (NewIssueLabel color lblName lblDesc) = object $ filter notNull
        [ "name" .= lblName
        , "color" .= color
        , "description" .= lblDesc
        ]
        where
            notNull (_, Null) = False
            notNull (_, _)    = True
data UpdateIssueLabel = UpdateIssueLabel
    { updateLabelColor :: !Text
    , updateLabelName  :: !(Name UpdateIssueLabel)
    , updateLabelDesc  :: !(Maybe Text)
    }
  deriving (Show, Data, Typeable, Eq, Ord, Generic)
instance NFData UpdateIssueLabel where rnf = genericRnf
instance Binary UpdateIssueLabel
instance ToJSON UpdateIssueLabel where
    toJSON (UpdateIssueLabel color lblName lblDesc) = object $ filter notNull
        [ "new_name" .= lblName
        , "color" .= color
        , "description" .= lblDesc
        ]
        where
            notNull (_, Null) = False
            notNull (_, _)    = True