Skip to content

Instantly share code, notes, and snippets.

@mmakowski
mmakowski / bitrate
Last active December 14, 2015 03:49
#!/bin/bash
mediainfo "$1" | grep "Bit rate"
module Lenses where
import Prelude hiding ((.), id)
import Control.Category
data Lens s a = Lens (s -> a) ((a -> a) -> s -> s)
instance Category Lens where
id = Lens id id
(Lens lg lm) . (Lens rg rm) = Lens (lg . rg) (rm . lm)
module Alloc where
import Control.Arrow (first)
import Data.List (mapAccumL)
{-
given a stream of [[Int]] each sublist representing a day, each place representing people
each number representing the number of days they want to stay
We would like to get a list of rooms to check in on the day and rooms to check out on the day
and maximum number of occupied rooms.
{-
problem: generate infinite list of triples by height, i.e.:
[(1,1,1), (1,1,2), (1,2,1), (2,1,1), (1,1,3), ... ]
-}
import Data.List (nub, inits)
-- inefficient (exponential):
triples :: Int -> [(Int, Int, Int)]
module Schools where
import Data.List (elemIndex)
{-
Problem:
- for every chilld rank all schools
- for every school, rank every child
- specify capacity of every school (Pupil Allocation Number)
-- this runs pretty nicely with +RTS -N2
import Control.Concurrent.STM (atomically, STM)
import Control.Concurrent.STM.TQueue (TQueue, newTQueueIO, tryReadTQueue, writeTQueue)
import Control.Concurrent (forkIO)
import Control.Monad (forever, forM_, when)
import Graphics.UI.WX hiding (when)
-- Graphics.UI.WX.Async
module Logger where
import System.IO
type Logger = String -> IO ()
data Logging a = Logging { unLogging :: Logger -> IO a }
logLine :: String -> Logging ()
logLine s = Logging $ \l -> l s
{-# language TypeSynonymInstances, FlexibleInstances, DeriveDataTypeable #-}
module Traverse where
import Data.Data
import Data.Generics.Aliases
import Data.Typeable
data Tree a = Node a [Tree a]
deriving (Show, Data, Typeable)
{-# Language ViewPatterns, GADTs, KindSignatures #-}
import Data.List
{-
catamorphisms: folds
anamorphisms: unfolds
foldr vs foldl: foldl is almost never the right thing to use, use foldl' instead, which is a strict version
(optimiser will do this for us)
-}
module Puzzle where
import Data.List
data Girl = Ellie | Emily | Jessica deriving (Bounded, Enum, Eq, Show)
data Animal = Elephant | Zebra | Giraffe deriving (Bounded, Enum, Eq, Show)
data Lolly = Grunge | Plooper | Zinger deriving (Bounded, Enum, Eq, Show)
data Adult = Aunt | Grandma | Mum deriving (Bounded, Enum, Eq, Show)