Skip to content

Instantly share code, notes, and snippets.

View raymondtay's full-sized avatar
:shipit:
Focusing

Raymond Tay raymondtay

:shipit:
Focusing
View GitHub Profile
@raymondtay
raymondtay / RateLimitingStream.hs
Last active November 4, 2018 13:06
Rate Limiting Producer using Par Monad Direct Scheduler
module RateLimitingStream (
Stream(..),
foldS,
streamFromList
) where
import System.Environment
import Control.Monad.IO.Class
import Control.Monad.Par
import Control.DeepSeq

Explaining Miles's Magic

Miles Sabin recently opened a pull request fixing the infamous SI-2712. First off, this is remarkable and, if merged, will make everyone's life enormously easier. This is a bug that a lot of people hit often without even realizing it, and they just assume that either they did something wrong or the compiler is broken in some weird way. It is especially common for users of scalaz or cats.

But that's not what I wanted to write about. What I want to write about is the exact semantics of Miles's fix, because it does impose some very specific assumptions about the way that type constructors work, and understanding those assumptions is the key to getting the most of it his fix.

For starters, here is the sort of thing that SI-2712 affects:

def foo[F[_], A](fa: F[A]): String = fa.toString
import akka.actor._
import scala.concurrent._
import duration._
class EEcho extends Actor {
import ExecutionContext.Implicits.global
def receive = {
case Some(msg:Int) =>
println("RECV => " + msg)
package actors.scalaz
import scalaz._
import Scalaz._
import akka.actor._
import akka.util.Timeout
import akka.pattern.ask
import scala.concurrent._
import scala.concurrent.duration._
module Chapter26_1 where
import Control.Monad.Trans.Reader
import Data.Functor.Identity
-- Part (2) of my beginnings with Monad Transformers. See Part (1) of my journey with Monad Transformers written here (https://gist.github.com/raygit/e540aacf58e32d5e071d3d1cefb61b96)
--
-- I'm trying to understand how this would work. From the package's description
-- (https://hackage.haskell.org/package/transformers-0.5.2.0/docs/Control-Monad-Trans-Reader.html),
-- i see that:
{-# LANGUAGE InstanceSigs #-}
module Chapter26 where
import Control.Monad (liftM)
newtype MaybeT m a = MaybeT' { runMaybeT :: m (Maybe a) }
instance (Functor m) => Functor (MaybeT m) where
fmap f (MaybeT' ma) = MaybeT' $ (fmap . fmap) f ma
import scalaz._
import Scalaz._
case class Result(eCode: Int)
case class Action(z: Int, f : Int => Int)
// Artificially created two "steps" with the intention
// combining them later in a composition
val step1 = State[Action, Result] {
case (a: Action) =>
template<int v>
struct Int2Type {
enum { value = v };
};
import java.util.*;
interface Fn<T,R> {
R apply(T a);
R f(T a);
}
// Created for the purpose of a class.
class AddOneFunction implements Fn<Integer,Integer> {
public Integer apply(Integer a) { return f(a); }
@raymondtay
raymondtay / .vimrc
Last active December 16, 2015 07:49
my vimrc
set t_Co=256
set nu
set hlsearch
syntax on
set tabstop=4
set background=dark
let g:solarized_termcolors=256
colorscheme solarized
set shiftwidth=4
set expandtab