mirror of
https://github.com/facebook/Haxl.git
synced 2024-12-24 01:04:21 +03:00
dc6eeb46ef
Summary: Expose a conveniece wrapper `runHaxlWithWrites` which returns the writes along with the result of the `Haxl` computation. Reviewed By: simonmar Differential Revision: D14386668 fbshipit-source-id: 95757916691f7b9b1291c7dceae7eafe8738cfca
53 lines
1.2 KiB
Haskell
53 lines
1.2 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 OverloadedStrings #-}
|
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
|
{-# LANGUAGE DeriveDataTypeable #-}
|
|
|
|
module TestTypes
|
|
( UserEnv
|
|
, Haxl
|
|
, HaxlEnv
|
|
, lookupInput
|
|
, Id(..)
|
|
) where
|
|
|
|
import Data.Aeson
|
|
import Data.Binary (Binary)
|
|
import Data.Text (Text)
|
|
import qualified Data.Text as Text
|
|
import qualified Data.HashMap.Strict as HashMap
|
|
import Data.Hashable
|
|
import Data.Typeable
|
|
|
|
import Haxl.Core
|
|
|
|
type UserEnv = Object
|
|
type Haxl a = GenHaxl UserEnv () a
|
|
type HaxlEnv = Env UserEnv ()
|
|
|
|
lookupInput :: FromJSON a => Text -> Haxl a
|
|
lookupInput field = do
|
|
mb_val <- env (HashMap.lookup field . userEnv)
|
|
case mb_val of
|
|
Nothing ->
|
|
throw (NotFound (Text.concat ["field ", field, " was not found."]))
|
|
Just val ->
|
|
case fromJSON val of
|
|
Error str ->
|
|
throw (UnexpectedType (Text.concat
|
|
["field ", field, ": ", Text.pack str]))
|
|
Success a -> return a
|
|
|
|
|
|
newtype Id = Id Int
|
|
deriving (Eq, Ord, Binary, Enum, Num, Integral, Real, Hashable, Typeable,
|
|
ToJSON, FromJSON)
|
|
|
|
instance Show Id where
|
|
show (Id i) = show i
|