sure, sorry should have done at the first place. Basically I have several similar calls like one below. This one should be the heaviest one.

--scotty:
post "/setmoduletable" $ do
b <- body
let queryString = tableArrayInDataToJSON b
case queryString of
Nothing -> text $ "error parsing json! "
Just (ArrayDataIn tablename columnsCnt rowsCnt values) -> do
result <- liftIO $ FM.setmoduletable tablename columnsCnt rowsCnt values
let resultInt = fromIntegral $ result::Int
json $ ReturnIntData resultInt


--json conversions
tableArrayInDataToJSON :: L.ByteString -> Maybe ArrayDataIn
tableArrayInDataToJSON rawJson = retValue
where
json = decode rawJson :: Maybe ArrayDataIn
retValue = case json of
Nothing -> Nothing
Just a -> Just a


data ArrayDataIn = ArrayDataIn{
tablename :: !String
,columnscount :: Int
,rowscount :: Int
,values :: [Double]
}deriving (Show,Generic)

instance FromJSON ArrayDataIn
instance ToJSON ArrayDataIn

--ffi

foreign import stdcall safe "setmoduletable" c_setmoduletable :: CString -> CInt -> Ptr CDouble -> CInt -> CInt -> CInt -> IO CInt


setmoduletable :: String -> Int -> Int -> [Double] -> IO CInt
setmoduletable param columns rows array = do
let cParamLength = fromIntegral $ length param ::CInt
   cColumns = fromIntegral $ columns ::CInt
   cRows = fromIntegral $ rows ::CInt
   cTable = [realToFrac x ::CDouble | x <- array]
   firstTimeStepAfterRestart = 0::CInt
cParam <- newCString param
cTablePtr <- newArray cTable
result <- c_setmoduletable cParam cParamLength cTablePtr cColumns cRows firstTimeStepAfterRestart
free cTablePtr
free cParam
return result




On Sat, Apr 5, 2014 at 3:01 PM, John Wiegley <johnw@fpcomplete.com> wrote:
>>>>> Miro Karpis <miroslav.karpis@gmail.com> writes:

> I tried to profile it but so far I can see that the bottleneck is Aeson
> (please correct me if I'm wrong). Is there a way how to optimise it? The
> data I'm sending via JSON are very small, so that can not be the problem.

Can you share any of your code with us?

John
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe