diff --git a/github.cabal b/github.cabal
index 7b6724f1..e394fa32 100644
--- a/github.cabal
+++ b/github.cabal
@@ -96,6 +96,7 @@ library
GitHub.Data.Search
GitHub.Data.Statuses
GitHub.Data.Teams
+ GitHub.Data.Traffic
GitHub.Data.URL
GitHub.Data.Webhooks
GitHub.Data.Webhooks.Validate
@@ -131,6 +132,7 @@ library
GitHub.Endpoints.Repos.Forks
GitHub.Endpoints.Repos.Releases
GitHub.Endpoints.Repos.Statuses
+ GitHub.Endpoints.Repos.Traffic
GitHub.Endpoints.Repos.Webhooks
GitHub.Endpoints.Search
GitHub.Endpoints.Users
diff --git a/src/GitHub.hs b/src/GitHub.hs
index fb342a9c..5de81045 100644
--- a/src/GitHub.hs
+++ b/src/GitHub.hs
@@ -313,6 +313,13 @@ module GitHub (
pingRepoWebhookR,
deleteRepoWebhookR,
+ -- ** Traffic
+ -- | See
+ popularReferrersR,
+ popularPathsR,
+ viewsR,
+ clonesR,
+
-- * Releases
releasesR,
releaseR,
@@ -410,6 +417,7 @@ import GitHub.Endpoints.Repos.Deployments
import GitHub.Endpoints.Repos.Forks
import GitHub.Endpoints.Repos.Releases
import GitHub.Endpoints.Repos.Statuses
+import GitHub.Endpoints.Repos.Traffic
import GitHub.Endpoints.Repos.Webhooks
import GitHub.Endpoints.Search
import GitHub.Endpoints.Users
diff --git a/src/GitHub/Data.hs b/src/GitHub/Data.hs
index e6fbd4a0..9bdb3fdb 100644
--- a/src/GitHub/Data.hs
+++ b/src/GitHub/Data.hs
@@ -57,6 +57,7 @@ module GitHub.Data (
module GitHub.Data.Search,
module GitHub.Data.Statuses,
module GitHub.Data.Teams,
+ module GitHub.Data.Traffic,
module GitHub.Data.URL,
module GitHub.Data.Webhooks
) where
@@ -90,6 +91,7 @@ import GitHub.Data.Reviews
import GitHub.Data.Search
import GitHub.Data.Statuses
import GitHub.Data.Teams
+import GitHub.Data.Traffic
import GitHub.Data.URL
import GitHub.Data.Webhooks
diff --git a/src/GitHub/Data/Traffic.hs b/src/GitHub/Data/Traffic.hs
new file mode 100644
index 00000000..df45b8ad
--- /dev/null
+++ b/src/GitHub/Data/Traffic.hs
@@ -0,0 +1,126 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE KindSignatures #-}
+
+-- | Data types used in the traffic API
+module GitHub.Data.Traffic where
+
+import Data.Text (Text)
+import Data.Time (UTCTime)
+import Data.Vector (Vector)
+
+import GitHub.Data.Name (Name)
+import GitHub.Internal.Prelude
+import Prelude ()
+
+data Referrer = Referrer
+ { referrer :: !(Name Referrer)
+ , referrerCount :: !Int
+ , referrerUniques :: !Int
+ }
+ deriving (Eq, Show, Generic)
+
+instance FromJSON Referrer where
+ parseJSON = withObject "Referrer" $ \o -> Referrer
+ <$> o .: "referrer"
+ <*> o .: "count"
+ <*> o .: "uniques"
+
+instance ToJSON Referrer where
+ toJSON (Referrer r c u) = object
+ [ "referrer" .= r
+ , "count" .= c
+ , "uniques" .= u
+ ]
+
+data PopularPath = PopularPath
+ { popularPath :: !Text
+ , popularPathTitle :: !Text
+ , popularPathCount :: !Int
+ , popularPathUniques :: !Int
+ }
+ deriving (Eq, Show)
+
+instance FromJSON PopularPath where
+ parseJSON = withObject "Path" $ \o -> PopularPath
+ <$> o .: "path"
+ <*> o .: "title"
+ <*> o .: "count"
+ <*> o .: "uniques"
+
+instance ToJSON PopularPath where
+ toJSON (PopularPath p t c u) = object
+ [ "path" .= p
+ , "title" .= t
+ , "count" .= c
+ , "uniques" .= u
+ ]
+
+data Period =
+ Day
+ | Week
+ deriving (Eq, Show)
+
+data TrafficEvent
+ = View
+ | Clone
+ deriving (Eq, Show)
+
+data TrafficCount (e :: TrafficEvent) = TrafficCount
+ { trafficCountTimestamp :: !UTCTime
+ , trafficCount :: !Int
+ , trafficCountUniques :: !Int
+ }
+ deriving (Eq, Show)
+
+instance FromJSON (TrafficCount e) where
+ parseJSON = withObject "TrafficCount" $ \o -> TrafficCount
+ <$> o .: "timestamp"
+ <*> o .: "count"
+ <*> o .: "uniques"
+
+instance ToJSON (TrafficCount e) where
+ toJSON (TrafficCount t c u) = object
+ [ "timestamp" .= t
+ , "count" .= c
+ , "uniques" .= u
+ ]
+
+data Views = Views
+ { viewsCount :: !Int
+ , viewsUniques :: !Int
+ , views :: !(Vector (TrafficCount 'View))
+ }
+ deriving (Eq, Show)
+
+instance FromJSON Views where
+ parseJSON = withObject "Views" $ \o -> Views
+ <$> o .: "count"
+ <*> o .: "uniques"
+ <*> o .: "views"
+
+instance ToJSON Views where
+ toJSON (Views c u v) = object
+ [ "count" .= c
+ , "uniques" .= u
+ , "views" .= v
+ ]
+
+data Clones = Clones
+ { clonesCount :: !Int
+ , clonesUniques :: !Int
+ , clones :: !(Vector (TrafficCount 'Clone))
+ }
+ deriving (Eq, Show)
+
+instance FromJSON Clones where
+ parseJSON = withObject "Clones" $ \o -> Clones
+ <$> o .: "count"
+ <*> o .: "uniques"
+ <*> o .: "clones"
+
+instance ToJSON Clones where
+ toJSON (Clones c u cs) = object
+ [ "count" .= c
+ , "uniques" .= u
+ , "clones" .= cs
+ ]
diff --git a/src/GitHub/Endpoints/Repos/Traffic.hs b/src/GitHub/Endpoints/Repos/Traffic.hs
new file mode 100644
index 00000000..084a358b
--- /dev/null
+++ b/src/GitHub/Endpoints/Repos/Traffic.hs
@@ -0,0 +1,80 @@
+-- | The traffic API, as described at
+module GitHub.Endpoints.Repos.Traffic (
+ popularReferrers',
+ popularReferrersR,
+ popularPaths',
+ popularPathsR,
+ views',
+ viewsR,
+ clones',
+ clonesR
+ ) where
+
+import Data.Vector (Vector)
+
+import GitHub.Data
+ (Auth, Clones, Error, Name, Owner, Period (Day, Week), PopularPath,
+ Referrer, Repo, Views)
+import GitHub.Data.Request (query, toPathPart)
+import GitHub.Internal.Prelude
+import GitHub.Request (Request, executeRequest)
+import Prelude ()
+
+-- | The top 10 referrers for the past 14 days.
+--
+-- > popularReferrers' (BasicAuth "github-username" "github-password") "qfpl" "tasty-hedgehog"
+popularReferrers' :: Auth -> Name Owner -> Name Repo -> IO (Either Error (Vector Referrer))
+popularReferrers' auth user =
+ executeRequest auth . popularReferrersR user
+
+-- | The top 10 referrers for the past 14 days.
+-- See
+popularReferrersR :: Name Owner -> Name Repo -> Request k (Vector Referrer)
+popularReferrersR user repo =
+ query ["repos", toPathPart user, toPathPart repo, "traffic", "popular", "referrers"] []
+
+-- | The 10 most popular paths based on visits over the last 14 days.
+--
+-- > popularPaths' (OAuth "supersecrettoken") "qfpl" "tasty-hedgehog"
+popularPaths' :: Auth -> Name Owner -> Name Repo -> IO (Either Error (Vector PopularPath))
+popularPaths' auth user =
+ executeRequest auth . popularPathsR user
+
+-- | The 10 most popular paths based on visits over the last 14 days.
+-- See
+popularPathsR :: Name Owner -> Name Repo -> Request k (Vector PopularPath)
+popularPathsR user repo =
+ query ["repos", toPathPart user, toPathPart repo, "traffic", "popular", "paths"] []
+
+-- | The total number of views over the last 14 days, and a daily or weekly breakdown.
+--
+-- > views' (OAuth "supersecrettoken") "qfpl" "tasty-hedgehog" Day
+views' :: Auth -> Name Owner -> Name Repo -> Period -> IO (Either Error Views)
+views' auth user repo =
+ executeRequest auth . viewsR user repo
+
+-- | The total number of views over the last 14 days, and a daily or weekly breakdown.
+-- See
+viewsR :: Name Owner -> Name Repo -> Period -> Request k Views
+viewsR user repo period =
+ query ["repos", toPathPart user, toPathPart repo, "traffic", "views"]
+ [("per", Just $ serializePeriod period)]
+
+-- | The total number of clones over the last 14 days, and a daily or weekly breakdown.
+--
+-- > clones' (OAuth "supersecrettoken") "qfpl" "tasty-hedgehog" Week
+clones' :: Auth -> Name Owner -> Name Repo -> Period -> IO (Either Error Clones)
+clones' auth user repo =
+ executeRequest auth . clonesR user repo
+
+-- | The total number of clones over the last 14 days, and a daily or weekly breakdown.
+-- See
+clonesR :: Name Owner -> Name Repo -> Period -> Request k Clones
+clonesR user repo period =
+ query ["repos", toPathPart user, toPathPart repo, "traffic", "clones"]
+ [("per", Just $ serializePeriod period)]
+
+serializePeriod :: IsString a => Period -> a
+serializePeriod p = case p of
+ Day -> "day"
+ Week -> "week"