1010--
1111module GitHub.Data.Request (
1212 -- * Request
13- Request ( .. ) ,
14- SimpleRequest (.. ),
13+ Request ,
14+ GenRequest (.. ),
1515 -- * Smart constructors
1616 query , pagedQuery , command ,
1717 -- * Auxiliary types
1818 RW (.. ),
19- StatusMap ,
20- statusOnlyOk ,
2119 CommandMethod (.. ),
2220 toMethod ,
2321 FetchCount (.. ),
22+ MediaType (.. ),
2423 Paths ,
2524 IsPathPart (.. ),
2625 QueryString ,
@@ -34,12 +33,10 @@ import GitHub.Internal.Prelude
3433
3534import qualified Data.ByteString.Lazy as LBS
3635import qualified Data.Text as T
37- import qualified Network.HTTP.Types as Types
3836import qualified Network.HTTP.Types.Method as Method
39- import Network.URI (URI )
4037
4138------------------------------------------------------------------------------
42- -- Auxillary types
39+ -- Path parts
4340------------------------------------------------------------------------------
4441
4542type Paths = [Text ]
@@ -56,41 +53,30 @@ instance IsPathPart (Id a) where
5653instance IsPathPart IssueNumber where
5754 toPathPart = T. pack . show . unIssueNumber
5855
56+ -------------------------------------------------------------------------------
57+ -- Command Method
58+ -------------------------------------------------------------------------------
59+
5960-- | Http method of requests with body.
60- data CommandMethod a where
61- Post :: CommandMethod a
62- Patch :: CommandMethod a
63- Put :: CommandMethod a
64-
65- -- | Put requests, where we don't care about response's body
66- Put' :: CommandMethod ()
67- Delete :: CommandMethod ()
68- deriving (Typeable )
69-
70- deriving instance Eq (CommandMethod a )
71- deriving instance Ord (CommandMethod a )
72-
73- instance Show (CommandMethod a ) where
74- showsPrec _ Post = showString " Post"
75- showsPrec _ Patch = showString " Patch"
76- showsPrec _ Put = showString " Put"
77- showsPrec _ Put' = showString " Put'"
78- showsPrec _ Delete = showString " Delete"
79-
80- instance Hashable (CommandMethod a ) where
81- hashWithSalt salt Post = hashWithSalt salt (0 :: Int )
82- hashWithSalt salt Patch = hashWithSalt salt (1 :: Int )
83- hashWithSalt salt Put = hashWithSalt salt (2 :: Int )
84- hashWithSalt salt Put' = hashWithSalt salt (3 :: Int )
85- hashWithSalt salt Delete = hashWithSalt salt (4 :: Int )
86-
87- toMethod :: CommandMethod a -> Method. Method
61+ data CommandMethod
62+ = Post
63+ | Patch
64+ | Put
65+ | Delete
66+ deriving (Eq , Ord , Read , Show , Enum , Bounded , Typeable , Data , Generic )
67+
68+ instance Hashable CommandMethod
69+
70+ toMethod :: CommandMethod -> Method. Method
8871toMethod Post = Method. methodPost
8972toMethod Patch = Method. methodPatch
9073toMethod Put = Method. methodPut
91- toMethod Put' = Method. methodPut
9274toMethod Delete = Method. methodDelete
9375
76+ -------------------------------------------------------------------------------
77+ -- Fetch count
78+ -------------------------------------------------------------------------------
79+
9480-- | 'PagedQuery' returns just some results, using this data we can specify how
9581-- many pages we want to fetch.
9682data FetchCount = FetchAtLeast ! Word | FetchAll
@@ -115,15 +101,31 @@ instance Hashable FetchCount
115101instance Binary FetchCount
116102instance NFData FetchCount where rnf = genericRnf
117103
104+ -------------------------------------------------------------------------------
105+ -- MediaType
106+ -------------------------------------------------------------------------------
107+
108+ data MediaType
109+ = MtJSON -- ^ @application/vnd.github.v3+json@
110+ | MtRaw -- ^ @application/vnd.github.v3.raw@ <https://developer.github.com/v3/media/#raw-1>
111+ | MtDiff -- ^ @application/vnd.github.v3.diff@ <https://developer.github.com/v3/media/#diff>
112+ | MtPatch -- ^ @application/vnd.github.v3.patch@ <https://developer.github.com/v3/media/#patch>
113+ | MtSha -- ^ @application/vnd.github.v3.sha@ <https://developer.github.com/v3/media/#sha>
114+ | MtStar -- ^ @application/vnd.github.v3.star+json@ <https://developer.github.com/v3/activity/starring/#alternative-response-with-star-creation-timestamps-1>
115+ | MtRedirect -- ^ <https://developer.github.com/v3/repos/contents/#get-archive-link>
116+ | MtStatus -- ^ Parse status
117+ | MtUnit -- ^ Always succeeds
118+ deriving (Eq , Ord , Read , Show , Enum , Bounded , Typeable , Data , Generic )
119+
118120------------------------------------------------------------------------------
119- -- Github request
121+ -- RW
120122------------------------------------------------------------------------------
121123
122124-- | Type used as with @DataKinds@ to tag whether requests need authentication
123125-- or aren't read-only.
124126data RW
125127 = RO -- ^ /Read-only/, doesn't necessarily requires authentication
126- | RA -- ^ /Read autenticated /
128+ | RA -- ^ /Read authenticated /
127129 | RW -- ^ /Read-write/, requires authentication
128130 deriving (Eq , Ord , Read , Show , Enum , Bounded , Typeable , Data , Generic )
129131
@@ -138,102 +140,54 @@ instance IReadOnly 'RO where iro = ROO
138140instance IReadOnly 'RA where iro = ROA
139141-}
140142
143+ -------------------------------------------------------------------------------
144+ -- GitHub Request
145+ -------------------------------------------------------------------------------
146+
141147-- | Github request data type.
142148--
143- -- * @k@ describes whether authentication is required. It's required for non-@GET@ requests.
149+ -- * @rw@ describes whether authentication is required. It's required for non-@GET@ requests.
150+ -- * @mt@ describes the media type, i.e. how the response should be interpreted.
144151-- * @a@ is the result type
145152--
146153-- /Note:/ 'Request' is not 'Functor' on purpose.
147- data Request (k :: RW ) a where
148- SimpleQuery :: FromJSON a => SimpleRequest k a -> Request k a
149- StatusQuery :: StatusMap a -> SimpleRequest k () -> Request k a
150- HeaderQuery :: FromJSON a => Types. RequestHeaders -> SimpleRequest k a -> Request k a
151-
152- -- | Redirect query is /some/ query where we expect status 302 response with @Location@ header.
153- RedirectQuery :: SimpleRequest k () -> Request k URI
154+ data GenRequest (mt :: MediaType ) (rw :: RW ) a where
155+ Query :: Paths -> QueryString -> GenRequest mt rw a
156+ PagedQuery :: Paths -> QueryString -> FetchCount -> GenRequest mt rw (Vector a )
157+
158+ -- | Command
159+ Command
160+ :: CommandMethod -- ^ command
161+ -> Paths -- ^ path
162+ -> LBS. ByteString -- ^ body
163+ -> GenRequest mt 'RW a
154164 deriving (Typeable )
155165
156- data SimpleRequest (k :: RW ) a where
157- Query :: Paths -> QueryString -> SimpleRequest k a
158- PagedQuery :: Paths -> QueryString -> FetchCount -> SimpleRequest k (Vector a )
159- Command :: CommandMethod a -> Paths -> LBS. ByteString -> SimpleRequest 'RW a
160- deriving (Typeable )
161-
162- -------------------------------------------------------------------------------
163- -- Status Map
164- -------------------------------------------------------------------------------
165-
166- -- TODO: Change to 'Map' ?
167- type StatusMap a = [(Int , a )]
168-
169- statusOnlyOk :: StatusMap Bool
170- statusOnlyOk =
171- [ (204 , True )
172- , (404 , False )
173- ]
166+ -- | Most requests ask for @JSON@.
167+ type Request = GenRequest 'MtJSON
174168
175169-------------------------------------------------------------------------------
176170-- Smart constructors
177171-------------------------------------------------------------------------------
178172
179- query :: FromJSON a => Paths -> QueryString -> Request k a
180- query ps qs = SimpleQuery ( Query ps qs)
173+ query :: Paths -> QueryString -> Request mt a
174+ query ps qs = Query ps qs
181175
182- pagedQuery :: FromJSON a => Paths -> QueryString -> FetchCount -> Request k (Vector a )
183- pagedQuery ps qs fc = SimpleQuery ( PagedQuery ps qs fc)
176+ pagedQuery :: FromJSON a => Paths -> QueryString -> FetchCount -> Request mt (Vector a )
177+ pagedQuery ps qs fc = PagedQuery ps qs fc
184178
185- command :: FromJSON a => CommandMethod a -> Paths -> LBS. ByteString -> Request 'RW a
186- command m ps body = SimpleQuery ( Command m ps body)
179+ command :: CommandMethod -> Paths -> LBS. ByteString -> Request 'RW a
180+ command m ps body = Command m ps body
187181
188182-------------------------------------------------------------------------------
189183-- Instances
190184-------------------------------------------------------------------------------
191185
192- deriving instance Eq a => Eq (Request k a )
193- deriving instance Eq a => Eq (SimpleRequest k a )
194-
195- deriving instance Ord a => Ord (Request k a )
196- deriving instance Ord a => Ord (SimpleRequest k a )
197-
198- instance Show (SimpleRequest k a ) where
199- showsPrec d r = showParen (d > appPrec) $ case r of
200- Query ps qs -> showString " Query "
201- . showsPrec (appPrec + 1 ) ps
202- . showString " "
203- . showsPrec (appPrec + 1 ) qs
204- PagedQuery ps qs l -> showString " PagedQuery "
205- . showsPrec (appPrec + 1 ) ps
206- . showString " "
207- . showsPrec (appPrec + 1 ) qs
208- . showString " "
209- . showsPrec (appPrec + 1 ) l
210- Command m ps body -> showString " Command "
211- . showsPrec (appPrec + 1 ) m
212- . showString " "
213- . showsPrec (appPrec + 1 ) ps
214- . showString " "
215- . showsPrec (appPrec + 1 ) body
216- where
217- appPrec = 10 :: Int
218-
219- instance Show (Request k a ) where
220- showsPrec d r = showParen (d > appPrec) $ case r of
221- SimpleQuery req -> showString " SimpleQuery "
222- . showsPrec (appPrec + 1 ) req
223- StatusQuery m req -> showString " Status "
224- . showsPrec (appPrec + 1 ) (map fst m) -- !!! printing only keys
225- . showString " "
226- . showsPrec (appPrec + 1 ) req
227- HeaderQuery m req -> showString " Header "
228- . showsPrec (appPrec + 1 ) m
229- . showString " "
230- . showsPrec (appPrec + 1 ) req
231- RedirectQuery req -> showString " Redirect "
232- . showsPrec (appPrec + 1 ) req
233- where
234- appPrec = 10 :: Int
235-
236- instance Hashable (SimpleRequest k a ) where
186+ deriving instance Eq (GenRequest rw mt a )
187+ deriving instance Ord (GenRequest rw mt a )
188+ deriving instance Show (GenRequest rw mt a )
189+
190+ instance Hashable (GenRequest rw mt a ) where
237191 hashWithSalt salt (Query ps qs) =
238192 salt `hashWithSalt` (0 :: Int )
239193 `hashWithSalt` ps
@@ -249,18 +203,4 @@ instance Hashable (SimpleRequest k a) where
249203 `hashWithSalt` ps
250204 `hashWithSalt` body
251205
252- instance Hashable (Request k a ) where
253- hashWithSalt salt (SimpleQuery req) =
254- salt `hashWithSalt` (0 :: Int )
255- `hashWithSalt` req
256- hashWithSalt salt (StatusQuery sm req) =
257- salt `hashWithSalt` (1 :: Int )
258- `hashWithSalt` map fst sm
259- `hashWithSalt` req
260- hashWithSalt salt (HeaderQuery h req) =
261- salt `hashWithSalt` (2 :: Int )
262- `hashWithSalt` h
263- `hashWithSalt` req
264- hashWithSalt salt (RedirectQuery req) =
265- salt `hashWithSalt` (3 :: Int )
266- `hashWithSalt` req
206+ -- TODO: Binary
0 commit comments