Skip to content

Instantly share code, notes, and snippets.

@sacundim
sacundim / gist:5386823
Last active July 28, 2020 21:32
Toy instructional example of Haskell GADTs: simple dynamic types.
{-# LANGUAGE GADTs #-}
-- | Toy instructional example of GADTs: simple dynamic types.
--
-- Before tackling this, skim the GHC docs section on GADTs:
--
-- <http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#gadt>
--
-- As you read this example keep in mind this quote from the
-- docs: "The key point about GADTs is that /pattern matching
@sacundim
sacundim / gist:5544704
Last active December 17, 2015 03:39
SeerT monad transformer, written with Reader and Writer.
{-# LANGUAGE GeneralizedNewtypeDeriving, DoRec #-}
module Control.Monad.Trans.Seer
( SeerT
, runSeerT -- :: MonadFix m => SeerT w m a -> m (a, w)
, evalSeerT -- :: MonadFix m => SeerT w m a -> m a
, execSeerT -- :: MonadFix m => SeerT w m a -> m w
, send -- :: (Monoid w, Monad m) => w -> SeerT w m ()
, see -- :: (Monoid w, Monad m) => SeerT w m w
@sacundim
sacundim / SeerA.hs
Last active December 17, 2015 03:49
Applicative version of Seer monad. See this for context:http://unknownparallel.wordpress.com/2013/05/07/two-implementations-of-seers/
{-# LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module SeerA (SeerA, runSeerA, see, send, contact) where
import Control.Applicative
import Data.Functor.Constant
import Data.Functor.Product
import Data.Monoid (Monoid, mempty, (<>), Sum(..))
import Data.Traversable
@sacundim
sacundim / TakeR.hs
Last active December 19, 2015 16:59
Benchmarking Data.Sequence vs. the other implementations here: http://www.joachim-breitner.de/blog/archives/600-On-taking-the-last-n-elements-of-a-list.html
{-# LANGUAGE RankNTypes, ScopedTypeVariables #-}
import Control.Monad.ST
import Data.Foldable as F
import Data.Array.ST
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Criterion.Main
@sacundim
sacundim / Shape.hs
Last active March 31, 2022 14:01
OOP Shape example in Haskell, using existentials, GADTs, Typeable and ConstraintKinds to support downcasts.
{-# LANGUAGE GADTs, ConstraintKinds, KindSignatures, DeriveDataTypeable #-}
{-# LANGUAGE TypeOperators, ScopedTypeVariables, FlexibleInstances #-}
module Shape where
import Control.Applicative ((<$>), (<|>))
import Data.Maybe (mapMaybe)
import Data.Typeable
import GHC.Exts (Constraint)
i x = x s k
where s f g x = f x (g x)
k x y = x
-- Now this gives an epic compilation error...
k = i (i (i i))
s = i (i (i (i i)))
{-
GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help
@sacundim
sacundim / Add-negative-one.json
Last active May 27, 2020 04:56
Vega: what happens when the domain of a diverging color scale doesn't include its domainMid value
{
"$schema": "https://vega.github.io/schema/vega/v5.json",
"background": "white",
"padding": 5,
"style": "cell",
"data": [
{
"name": "example-data",
"values": [
{"y": 5, "value": -1},
@sacundim
sacundim / hardcoded.json
Last active May 27, 2020 05:40
Vega-Lite: Making overlay text look good on a diverging scale
{
"$schema": "https://vega.github.io/schema/vega-lite/v4.json",
"data": {"url": "data/cars.json"},
"transform": [
{
"aggregate": [{"op": "count", "as": "num_cars"}],
"groupby": ["Origin", "Cylinders"]
}
],
"encoding": {
@sacundim
sacundim / puerto-rico-municipal-bubble-chart.vl.json
Created June 17, 2020 04:39
Experimental bubble chart with Puerto Rico COVID-19 municipal time series
{
"config": {
"axis": {"labelFontSize": 14, "titleFontSize": 14},
"header": {"labelFontSize": 14, "titleFontSize": 14},
"legend": {"labelFontSize": 14, "titleFontSize": 14},
"title": {"align": "center", "fontSize": 20, "offset": 15}
},
"data": {"name": "data-1a2ae6c5a330adb8d6b476cc8f14c107"},
"mark": {
"type": "point",
@sacundim
sacundim / spec.json
Created June 17, 2020 05:24
Vega-Lite: Negative values in the size channel
{
"$schema": "https://vega.github.io/schema/vega-lite/v4.8.1.json",
"title": "Negative values in the size channel",
"data": {
"values": [-4, -3, -2, -1, 0, 1, 2, 3, 4]
},
"transform": [
{"calculate": "abs(datum.data)", "as": "abs"}
],
"repeat": ["data", "abs"],