{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-} module RBPCP.Internal.Types ( module RBPCP.Internal.Types , module X , ByteString , Generic ) where import RBPCP.Internal.Util import Network.Haskoin.Transaction as X import Network.Haskoin.Crypto as X hiding (PubKey) import Network.Haskoin.Script as X import Data.ByteString (ByteString) import Data.Word as X (Word32, Word64) import GHC.Generics (Generic) import Data.Aeson import qualified Data.Serialize as Bin import qualified Web.HttpApiData as Web type PubKey = PubKeyC newtype JsonHex a = JsonHex { fromHex :: a } deriving (Eq, Show, Generic, Bin.Serialize) instance Bin.Serialize a => ToJSON (JsonHex a) where toJSON = String . cs . hexEncode . fromHex instance Bin.Serialize a => FromJSON (JsonHex a) where parseJSON = withText "JsonHex a" $ either (fail . (++ "Hex decode fail: ")) return . fmap JsonHex . hexDecode . cs -- | Wraps any client-related datatype (eg. pubkey, signature) newtype Client a = Client a deriving ( Eq , Show , Generic , Bin.Serialize , ToJSON , FromJSON , Web.ToHttpApiData , Web.FromHttpApiData ) -- | Wraps any server-related datatype (eg. pubkey, signature) newtype Server a = Server a deriving ( Eq , Show , Generic , Bin.Serialize , ToJSON , FromJSON , Web.ToHttpApiData , Web.FromHttpApiData )