Skip to content

Instantly share code, notes, and snippets.

@Decoherence
Decoherence / HiDPICanvas.html
Last active August 29, 2015 14:06
HTML5 Canvas HiDPI
<h2>Naive canvas</h2>
<canvas id="naive" width="400" height="50"></canvas>
<h2>High-def Canvas</h2>
<canvas id="hidef" width="800" height="500"></canvas>
@Decoherence
Decoherence / GADTsEvaluateTerms.hs
Last active August 29, 2015 14:08
Haskell: Generalized Algebraic Data Types (GADTs)
{-# Language GADTs #-}
data Term a where
Lit :: a -> Term a
Succ :: Term Int -> Term Int
IsZero :: Term Int -> Term Bool
If :: Term Bool -> Term a -> Term a -> Term a
IsNeg :: Term Int -> Term Bool
@Decoherence
Decoherence / HasteJavaScript.hs
Last active August 29, 2015 14:09
Haskell: Compile to JavaScript -- handle onClick and onMouseOver events.
import Haste
main :: IO ()
main = do
-- Get handle to #msg div
msg <- elemById "msg"
case msg of
Just m -> do
-- Handle onClick event
@Decoherence
Decoherence / FactFibSum.hs
Last active August 29, 2015 14:09
Haskell: Using multiple cores to calculate a value in parallel -- fibonacci(n) + factorial(n)
{- For demonstration only; this is deliberately slow recursive code to highlight multicore speedup -}
import System.Time
import Control.Concurrent
import Control.Parallel.Strategies hiding (parMap)
import System.Environment
fib 0 = 1
fib 1 = 1
fib n = fib (n - 1) + fib (n - 2)
@Decoherence
Decoherence / ShapesExistentialQuantification.hs
Last active August 29, 2015 14:11
Haskell: Using existential quantification to calculate the area of a heterogeneous list of shapes.
{-# LANGUAGE ExistentialQuantification #-}
data Circle = Circle Double deriving (Show)
data Square = Square Double deriving (Show)
data Rectangle = Rectangle Double Double deriving (Show)
--------------------------------------------------------------------------------
-- Each shape implements an area function
--------------------------------------------------------------------------------
class Shape s where
@Decoherence
Decoherence / STM.hs
Last active August 29, 2015 14:11
Haskell: Software Transactional Memory (STM) -- read & write integers concurrently to a channel
import Control.Monad.STM
import Control.Concurrent
import Control.Concurrent.STM.TChan
oneSecond = 1000000 -- microseconds
-- | This thread writes values to a channel.
writerThread :: TChan Int -> IO ()
writerThread chan = do
-- Wait two seconds, then write 1 to channel
@Decoherence
Decoherence / RandomLettersFrequency.hs
Last active August 29, 2015 14:11
Haskell: Frequency count for randomly generated letters
import Control.Monad
import System.Random
import Data.List
import Data.Ord
-- Letters of the alphabet
alpha = ['a'..'z']
-- Get a random letter
rLetter = randomRIO (0,25) >>= return . (!!) alpha
@Decoherence
Decoherence / JSON_Parse.hs
Last active August 29, 2015 14:12
Haskell: Quick JSON Parse using Aeson
import Data.ByteString.Lazy.Internal
import Data.Aeson
import Control.Applicative
data Person = Person String Int deriving (Show)
instance FromJSON Person where
parseJSON (Object p) =
Person <$>
(p .: "name") <*>
@Decoherence
Decoherence / ReaderT_and_WriterT.hs
Last active August 2, 2022 02:26
Haskell: Monad Transformers -- Combine ReaderT and WriterT
-- | Main entry point to the application.
module Main where
import Control.Monad.Reader
import Control.Monad.Writer
{-
The ReaderT transformer is used to retrieve a read-only value from some environment.
The WriterT transformer will log the result of each retrieval.
Running the two transformers together yields a log of each step along with the actual results.
@Decoherence
Decoherence / Functional_Dependencies_Animals.hs
Last active August 29, 2015 14:13
Haskell: Functional dependency example -- for any instance of the Pet type class, the type of animal uniquely determines the sound it can make.
-- | Sandbox Haskell package
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
module Main where
class Pet animal sound | animal -> sound where
speak :: animal -> sound
data Sound = Bark | Meow deriving (Show)