blob: 99dbd6f1a2d25164ea93cd8b3087fc51b5b2d0aa [file] [log] [blame]
Bryan Duxburye59a80f2010-09-20 15:21:37 +00001{-# LANGUAGE DeriveDataTypeable #-}
Bryan Duxbury0781f2b2009-04-07 23:29:42 +00002--
3-- Licensed to the Apache Software Foundation (ASF) under one
4-- or more contributor license agreements. See the NOTICE file
5-- distributed with this work for additional information
6-- regarding copyright ownership. The ASF licenses this file
7-- to you under the Apache License, Version 2.0 (the
8-- "License"); you may not use this file except in compliance
9-- with the License. You may obtain a copy of the License at
10--
11-- http://www.apache.org/licenses/LICENSE-2.0
12--
13-- Unless required by applicable law or agreed to in writing,
14-- software distributed under the License is distributed on an
15-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
16-- KIND, either express or implied. See the License for the
17-- specific language governing permissions and limitations
18-- under the License.
19--
20
21module Thrift.Transport
22 ( Transport(..)
23 , TransportExn(..)
24 , TransportExnType(..)
25 ) where
26
27import Control.Monad ( when )
28import Control.Exception ( Exception, throw )
29
30import Data.Typeable ( Typeable )
31
David Reiss752529e2010-01-11 19:12:56 +000032import qualified Data.ByteString.Lazy.Char8 as LBS
33import Data.Monoid
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000034
35class Transport a where
36 tIsOpen :: a -> IO Bool
37 tClose :: a -> IO ()
David Reiss752529e2010-01-11 19:12:56 +000038 tRead :: a -> Int -> IO LBS.ByteString
39 tWrite :: a -> LBS.ByteString -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000040 tFlush :: a -> IO ()
David Reiss752529e2010-01-11 19:12:56 +000041 tReadAll :: a -> Int -> IO LBS.ByteString
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000042
Bryan Duxburye59a80f2010-09-20 15:21:37 +000043 tReadAll _ 0 = return mempty
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000044 tReadAll a len = do
45 result <- tRead a len
David Reiss752529e2010-01-11 19:12:56 +000046 let rlen = fromIntegral $ LBS.length result
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000047 when (rlen == 0) (throw $ TransportExn "Cannot read. Remote side has closed." TE_UNKNOWN)
48 if len <= rlen
49 then return result
David Reiss752529e2010-01-11 19:12:56 +000050 else (result `mappend`) `fmap` (tReadAll a (len - rlen))
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000051
52data TransportExn = TransportExn String TransportExnType
53 deriving ( Show, Typeable )
54instance Exception TransportExn
55
56data TransportExnType
57 = TE_UNKNOWN
58 | TE_NOT_OPEN
59 | TE_ALREADY_OPEN
60 | TE_TIMED_OUT
61 | TE_END_OF_FILE
62 deriving ( Eq, Show, Typeable )
63