Skip to content

Instantly share code, notes, and snippets.

@luqui
luqui / intervals.txt
Created November 28, 2013 06:39
An exploration of "small-ratio" musical intervals, compared to equal temperament.
An exploration of "small-ratio" musical intervals, compared to equal temperament. Each interval has
a perfect ratio before the colon, and a number of semitones with a cents (100th of a semitone) correction
approximation.
This is study for playing the Haken Continuum.
Root: 1 : 0
P2: 9/8 : 2 +3c
Fourth: 4/3 : 5 -2c
@luqui
luqui / gist:7611127
Created November 23, 2013 05:21
A neat list-like monoid that supports extracting information from both ends, even with undefined values in the middle.
{-# LANGUAGE RankNTypes #-}
import Data.Foldable
import Data.Monoid
newtype M a = M { getM :: forall m. Monoid m => (a -> m) -> m }
instance Monoid (M a) where
mempty = M $ const mempty
x `mappend` y = M $ \f -> getM x f `mappend` getM y f
{-# LANGUAGE ConstraintKinds, MultiParamTypeClasses, FunctionalDependencies #-}
class FromCon k a | a -> k where
convert :: k b => b -> a
instance FromCon Integral Integer where
convert = fromIntegral
foo :: Integer
foo = convert 4
@luqui
luqui / codata.hs
Created July 13, 2013 21:50
Functions from codata are not necessarily codata.
import qualified Data.Searchable as S -- from infinite-search package
import Control.Applicative (liftA2)
import Data.Function (fix)
-- We will see that a function which takes codata as an argument is
-- not necessarily codata itself. Here we see an isomorphism between
-- total functions of type (Stream Bool -> a) and finite trees of the
-- shape (SBFunc a) (below), whenever a has decidable equality.
-- We will be using infinite lists as streams, pretending

Am I too ambitious? Yes. Moving on.

I am very interested in getting things to work together. One of the most annoying parts of software engineering to me is knowing that somebody else has already solved your problem, but not being able to use the solution because the rest of your system is in the wrong language/framework/...

Let's solve that problem. Or at least make a step towards a solution.

So far I've been interested in creating a language / environment in which everything that is programmed in it has this adaptive property. But that is no good, because most people are not using it, so most people will still have the essential problem. I can make my own personal universe in which this problem doesn't exist, but the problem will still exist in the real world. I want to change my focus to solving a problem without creating a universe to do it in.

There is usually some way to get things to work. Let's say you have some Java library to Amazon AWS and you're writing a Haskell program that needs i

@luqui
luqui / journal.mkd
Created March 18, 2013 07:09
Journal Entry 2013-03-18

Hello, this is my journal. I have a good 3-4 shots of cheap whiskey in me (at the very least, positive time-derivative). I don't know why I journal on github, I figure I'll have roughly the same number of readers as if I wrote it to myself, and here I have an audience. I can't share my innermost deepest secrets here, but that's okay, I can share most things. If anybody reads it they will arrive here from a random google search for something random I mentioned anyway.

So... I'm getting excited about (1) my Continuum, which I will be able to afford in a month!!!!!! and (2) my time off, which I will be able to afford in 2? years. Assuming I can keep my job. The project is ending, but I have a suspicion that they are unhappy with my work. There's more than a 50% chance that that's my own shit coming through... I dunno, after the abrupt end of the socialmedia contract I am perpetually jittery about my job security.

Oh well, what I really want to do is research and music. I mean my own research. I'm

import Data.List
import qualified Data.Set as Set
import Criterion.Main
import System.Random
itemsEqualOnDiff :: (Eq a) => [a] -> [a] -> Bool
itemsEqualOnDiff a b = null $ absDiff a b
absDiff :: (Eq a) => [a] -> [a] -> [a]
absDiff [] [] = []
import Data.List
import qualified Data.Set as Set
import Criterion.Main
itemsEqualOnDiff :: (Eq a) => [a] -> [a] -> Bool
itemsEqualOnDiff [] [] = True
itemsEqualOnDiff [] _ = False
itemsEqualOnDiff _ [] = False
itemsEqualOnDiff (aHead:aTail) b = itemsEqualOnDiff aTail $ delete aHead b
@luqui
luqui / gnd-gadts.hs
Created March 4, 2013 06:45
GeneralizedNewtypeDeriving and GADT interaction
{-# LANGUAGE GADTs, GeneralizedNewtypeDeriving #-}
data Switch b a where
SwitchA :: Switch b A
SwitchB :: b -> Switch b B
class Switchable c where
switch :: c -> Switch b c
data A = A
@luqui
luqui / unsafeCoerce.hs
Created March 4, 2013 05:44
unsafeCoerce from TypeFamilies and GeneralizedNewtypeDeriving
{-# LANGUAGE TypeFamilies, GeneralizedNewtypeDeriving #-}
type family Switch b a
type instance Switch b (A a) = a
type instance Switch b (B a) = b
newtype A a = A a
newtype B a = B (A a)
deriving (Switchable)