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
// a simple module | |
exports.add = function(a, b) { | |
return a + b; | |
}; |
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
module Order where | |
-- DBM is some Monad Transformer stack that allows us to talk to our DB (also a form of DI!) | |
placeOrder :: User -> OrderDetails -> DBM () | |
placeOrder user details = do | |
-- Some users will have discounts for | |
(discount :: Maybe Discount) <- findRelevantDiscount user details | |
-- Create the specific order for this user with any discount |
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://en.wikibooks.org/wiki/Haskell/Category_theory#The_second_law | |
join . fmap return = join . return = id | |
return = repeat | |
join . fmap repeat = join . repeat = id | |
-- let's try it on some arbitrary list | |
join [repeat a, repeat b, ...] = join (repeat [a, b, c, ...]) = [a, b, c, ...] |
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
ghcid -c 'stack ghci --test' --test 'Test.Hspec.hspec Main.spec' |
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 DataKinds #-} | |
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE KindSignatures #-} | |
module Data.HdrHistogram.Config.Test where | |
import GHC.TypeLits (Nat, type (<=)) | |
-- Is there a way to add constraints to these kinds? For example, 1 <= sig <= 7, or lowest <= highest. | |
-- I found https://hackage.haskell.org/package/base-4.7.0.1/docs/GHC-TypeLits.html#t:-60--61--63-, but don't know how to use it. |
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
irb(main):001:0> require 'riemann/dash' | |
=> true | |
irb(main):002:0> require 'riemann/dash/browser_config/s3' | |
Gem::LoadError: Unable to activate fog-json-1.0.2, because multi_json-1.3.6 conflicts with multi_json (~> 1.10) |
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
Running 1 benchmarks... | |
Benchmark bench: RUNNING... | |
benchmarking burst/encoding/1 | |
time 520.7 ns (512.9 ns .. 529.5 ns) | |
0.997 R² (0.992 R² .. 0.999 R²) | |
mean 516.5 ns (509.9 ns .. 534.9 ns) | |
std dev 32.75 ns (12.46 ns .. 65.36 ns) | |
variance introduced by outliers: 77% (severely inflated) | |
benchmarking burst/encoding/10 |
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
module Fork where | |
newtype Fork' f a = Fork' { runFork :: forall r. (a -> r) -> | |
(f r -> r) -> | |
(forall b. Fork' f b -> r -> r) -> r } deriving Functor | |
instance Applicative (Fork' f) where | |
pure a = Fork' (\kh _ _ -> kh a) | |
Fork' f <*> Fork' g = Fork' (\kh ka kf -> f (\a -> g (\b -> kh (a b)) ka kf) ka kf) |
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 DeriveFunctor #-} | |
{-# LANGUAGE ExistentialQuantification #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
module Fork where | |
import Control.Applicative (Applicative, pure, (<$>), (<*>)) | |
data Fork f a = Halt 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
Here is a test runner that uses quickcheck to generate programs against | |
a concurrent queue api, to hopefully find the intentional bugs in | |
it's implementation. | |
> main :: IO () | |
> main = hspec $ do | |
> describe "queue" $ do | |
> it "should not ever allow the client to block" $ property $ \program scheduler -> do | |
> res <- interpret scheduler $ new >>= runProgram program | |
> res `shouldSatisfy` (isRight) |
NewerOlder