This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
pub struct TransactionGroup { | |
/// Nonce. | |
pub nonce: U256, | |
/// Amount of CCC to be paid as a cost for distributing these transactions to the network. | |
pub fee: U256, | |
/// Transactions | |
pub transactions: Vec<Transaction>, | |
/// Mainnet or Testnet | |
pub network_id: u64, | |
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
pub struct AssetOutPoint { | |
pub transaction_hash: H256, | |
pub index: usize, | |
pub asset_type: H256, | |
pub amount: u64, | |
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE NamedFieldPuns #-} | |
import Control.Monad (when) | |
import qualified Data.ByteString.Char8 as BSC | |
import Data.Default.Class (def) | |
import Data.Monoid ((<>)) | |
import System.IO.Error (ioError, userError) | |
import Data.X509 (CertificateChain (..), HashALG(..)) | |
import Data.X509.CertificateStore (makeCertificateStore) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE TypeFamilies #-} | |
module Beard.DOM | |
( Element(..) | |
, Node(..) | |
, parseDOM | |
) where | |
import Control.Monad (when) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Control.Monad | |
import Control.Monad.ST | |
import Data.STRef | |
sumST :: Num a => [a] -> a | |
sumST xs = runST $ do | |
n <- newSTRef 0 | |
forM_ xs $ \x -> modifySTRef n (+x) | |
readSTRef n |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- https://jeltsch.wordpress.com/2013/02/14/the-constraint-kind/ | |
{-# LANGUAGE ConstraintKinds, TypeFamilies #-} | |
import Prelude hiding (Monad (..)) | |
import Data.Set | |
import GHC.Exts (Constraint) | |
setReturn :: el -> Set el | |
setReturn = singleton |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Prelude hiding (foldr) | |
import Data.Monoid | |
foldComposing :: (a -> (b -> b)) -> [a] -> Endo b | |
foldComposing f = foldMap (Endo . f) | |
foldr :: (a -> (b -> b)) -> b -> [a] -> b | |
foldr f z xs = appEndo (foldComposing f xs) z |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
odule Eval where | |
import Control.Monad.Identity | |
import Control.Monad.Error | |
import Control.Monad.Reader | |
import Control.Monad.State | |
import Control.Monad.Writer | |
import Data.Maybe | |
import qualified Data.Map as Map |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
import Control.Monad | |
import Control.Monad.State | |
import Control.Monad.Trans | |
newtype MaybeT m a = MaybeT { | |
runMaybeT :: m (Maybe a) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- http://research.microsoft.com/en-us/um/people/simonpj/papers/assoc-types/fun-with-type-funs/typefun.pdf | |
{-# LANGUAGE TypeFamilies #-} | |
class Memo a where | |
data Table a :: * -> * | |
toTable :: (a -> w) -> Table a w | |
fromTable :: Table a w -> (a -> w) | |
instance Memo Bool where | |
data Table Bool w = TBool w w |
NewerOlder