Haxl/tests/WorkDataSource.hs
Simon Marlow aff472bc25 Fix profiling test
Summary: I noticed this test was broken in `cabal test` recently.

Reviewed By: mic47

Differential Revision: D6857296

fbshipit-source-id: ca7d15ba841f1dc79acccf1cd4999e8fcea994c8
2018-02-01 07:42:18 -08:00

45 lines
1.1 KiB
Haskell

-- Copyright (c) 2014-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is distributed under the terms of a BSD license,
-- found in the LICENSE file.
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
module WorkDataSource (
work,
) where
import Haxl.Prelude
import Prelude ()
import Haxl.Core
import Haxl.DataSource.ConcurrentIO
import Control.Exception
import Data.Hashable
import Data.Typeable
work :: Integer -> GenHaxl u Integer
work n = dataFetch (Work n)
data Work deriving Typeable
instance ConcurrentIO Work where
data ConcurrentIOReq Work a where
Work :: Integer -> ConcurrentIOReq Work Integer
performIO (Work n) = evaluate (sum [1..n]) >> return n
deriving instance Eq (ConcurrentIOReq Work a)
deriving instance Show (ConcurrentIOReq Work a)
instance ShowP (ConcurrentIOReq Work) where showp = show
instance Hashable (ConcurrentIOReq Work a) where
hashWithSalt s (Work n) = hashWithSalt s n