Skip to content

Instantly share code, notes, and snippets.

@lylek
lylek / short_circuiting_folds.hs
Created March 2, 2020 00:53
Demonstration of short-circuiting left and right folds
-- short-circuiting folds
import Prelude hiding (foldl, foldr)
foldl :: (b -> a -> b) -> b -> [a] -> b
foldl f a [] = a
foldl f a (x:xs) = foldl f (f a x) xs
foldr :: (a -> b -> b) -> b -> [a] -> b
foldr f z [] = z
@lylek
lylek / system_f_product.hs
Last active March 1, 2020 22:16
Constructing pairs using functions as in System F, instead of built-in products
data A = A1 | A2 deriving Show
data B = B1 | B2 | B3 deriving Show
type PairAB x = (A -> B -> x) -> x
pairAB :: A -> B -> PairAB x
pairAB a b g = g a b
fstAB :: PairAB A -> A -- ((A -> B -> A) -> A) -> A
fstAB p = p (\x y -> x)
@lylek
lylek / Database.hs
Created January 21, 2020 01:51
Solution to Parallel and Concurrent Programming in Haskell, Chapter 14, Distributed Key-Value Store Exercise, Part 2
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
module Database (
Database,
Key, Value,
createDB,
get, set,
rcdata
@lylek
lylek / Database.hs
Created January 19, 2020 01:36
Solution to Parallel and Concurrent Programming in Haskell, Chapter 14, Distributed Key-Value Store Exercise, Part 1
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
module Database (
Database,
Key, Value,
createDB,
get, set,
rcdata,
@lylek
lylek / my-chat-noslave.hs
Created January 1, 2020 00:17
My attempt at making a peer-to-peer version of the distributed chat server from Concurrent and Parallel Programming in Haskell
{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
import Control.Distributed.Process
hiding (Message, mask, finally, handleMessage, proxy)
import Control.Distributed.Process.Backend.SimpleLocalnet (Backend, findPeers, initializeBackend, newLocalNode)
import Control.Distributed.Process.Closure
import Control.Distributed.Process.Node (initRemoteTable, runProcess)
import Control.Concurrent.Async
import Control.Monad.IO.Class
import Data.List (unfoldr)
-- Recursive definition of binomial coefficient
-- Can take exponential time in n + k
-- Try binom_r 25 10 -- already takes several seconds
binom_r :: Int -> Int -> Integer
binom_r n 0 = 1
binom_r n k | n == k = 1
| otherwise = binom_r (n-1) (k-1) + binom_r (n-1) k
@lylek
lylek / HExcel-date-bug.hs
Created December 24, 2019 03:24
Demonstrates bug in HExcel with generating dates
#!/usr/bin/env stack
-- stack script --resolver lts-14.9 --package=HExcel
import HExcel
main = do
wb <- workbookNew "buggy-dates.xls"
let props = mkDocProperties
{ docPropertiesTitle = "Buggy Dates"
, docPropertiesCompany = ""
@lylek
lylek / Lib.hs
Last active October 28, 2019 05:13
STLC Pairs
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Lib
( HasDummy
, Injectable
, Product
, Union
, pair
@lylek
lylek / stack.yaml
Created January 22, 2019 00:21
stack.yaml file for parconc-examples that can build rotateimage.hs
resolver: lts-6.35 # need to set this to old resolver
flags:
parconc-examples:
distributed: true
accelerate: true
devil: true # need to set this to build repa-devil
extra-package-dbs: []
packages:
- '.'
extra-deps:
@lylek
lylek / rsa-pipeline-fork.hs
Created December 17, 2018 05:19
Rate-limiting version of rsa-pipeline.hs
--
-- Derived from a program believed to be originally written by John
-- Launchbury, and incorporating the RSA algorithm which is in the
-- public domain.
--
-- This is a rate-limiting version of https://github.com/simonmar/parconc-examples/blob/master/rsa-pipeline.hs,
-- as per the exercise on page 69 of Parallel and Concurrent Programming in Haskell.
-- Uses https://gist.github.com/lylek/58d9307431c9dbee6505bd588b8dfbc9 for the StreamFork library.