Hi Michael,

Yep, I am working with conduit because of AWS API. Object response is of 
type Response 
<https://s3.amazonaws.com/haddock.stackage.org/lts-6.3/http-client-0.4.28/Network-HTTP-Client.html#t:Response>
 (ResumableSource 
<https://s3.amazonaws.com/haddock.stackage.org/lts-6.3/conduit-1.2.6.6/Data-Conduit.html#t:ResumableSource>
 (ResourceT 
<https://s3.amazonaws.com/haddock.stackage.org/lts-6.3/resourcet-1.1.7.4/Control-Monad-Trans-Resource.html#t:ResourceT>
 IO 
<https://s3.amazonaws.com/haddock.stackage.org/lts-6.3/base-4.8.2.0/System-IO.html#t:IO>
) ByteString 
<https://s3.amazonaws.com/haddock.stackage.org/lts-6.3/bytestring-0.10.6.0/Data-ByteString.html#t:ByteString>
).

I figured the same thing that you mentioned about inspecting the objects 
which forces them to be in memory. 

So, I re-wrote it to do a `mapM_` instead to a sink. Now, I am trying to 
figure out how to map this solution to websocket. Since you asked about the 
conduit source, here is the code from a StackOverflow question 
<http://stackoverflow.com/questions/37813120/streaming-bytes-to-network-websocket>
 
I just posted - I have refactored it now to use constant memory:

{-# LANGUAGE OverloadedStrings,ScopedTypeVariables #-}
import qualified Awsimport qualified Aws.S3 as S3import           Data.Conduit 
(($$+-))import qualified Data.Conduit.List as CL (mapM_)import qualified 
Data.ByteString.Streaming.HTTP as SPimport qualified Data.ByteString.Lazy as 
LBSimport Streaming as Simport Streaming.Prelude as S hiding (show,print)import 
Control.Concurrent.Async (async,waitCatch)import Data.Text as T (Text)
data AwsConfig a = AwsConfig { _aws_cfg :: Aws.Configuration, _aws_s3cfg :: 
S3.S3Configuration a, _aws_httpmgr :: SP.Manager }

getObject :: AwsConfig Aws.NormalQuery -> T.Text -> T.Text ->  IO Int
getObject cfg bucket key = do
  req <- waitCatch =<< async (runResourceT $ do
    {- Create a request object with S3.getObject and run the request with 
pureAws. -}
    S3.GetObjectResponse { S3.gorResponse = rsp, S3.gorMetadata = mdata } <- 
      Aws.pureAws (_aws_cfg cfg) (_aws_s3cfg cfg) (_aws_httpmgr cfg) $
        S3.getObject bucket key
    {- Stream the response to a lazy bytestring -}
    liftIO $ LBS.writeFile "testaws" LBS.empty -- this will be replaced by 
content-length of the bytes 
    let obj = (($$+- CL.mapM_ S.yield) . hoist lift ) (SP.responseBody rsp)
    S.mapM_ (liftIO . (LBS.appendFile "testaws") . LBS.fromStrict) obj
    return $ lookup "content-length" (S3.omUserMetadata mdata))
  case req of
    Left _ -> return 2 -- perhaps, we could use this to send an error message 
over websocket 

    Right _ -> return 0 

-- 
You received this message because you are subscribed to the Google Groups 
"Haskell Pipes" group.
To unsubscribe from this group and stop receiving emails from it, send an email 
to haskell-pipes+unsubscr...@googlegroups.com.
To post to this group, send email to haskell-pipes@googlegroups.com.

Reply via email to