Skip to content

Instantly share code, notes, and snippets.

View dmalikov's full-sized avatar
🥞
!

Dmitry Malikov dmalikov

🥞
!
View GitHub Profile
@dmalikov
dmalikov / exercise5.hs
Created July 9, 2012 22:29
Algorithms: design and analysis I, exercise5 (week5)
{-# LANGUAGE UnicodeSyntax #-}
import Control.Applicative ((<$>))
import Data.Foldable (foldMap)
import Data.Maybe (mapMaybe)
import Data.Monoid (Any(..))
import System.Environment (getArgs)
import qualified Data.ByteString.Lazy.Char8 as BSC
import qualified Data.HashSet as HS
@dmalikov
dmalikov / Graph.hs
Created June 29, 2012 08:53
Karger's MinCut realization
{-# LANGUAGE UnicodeSyntax #-}
module Graph where
import Control.Applicative ((<$>))
import Control.Monad (replicateM)
import System.Random (randomRIO)
import qualified Data.IntMap as IntMap
type Graph = IntMap.IntMap [Int]
@dmalikov
dmalikov / mergesort.hs
Created June 12, 2012 15:15
mergesort
{-# LANGUAGE UnicodeSyntax #-}
import Control.Arrow ((***))
import Control.Monad (join)
merge ∷ Ord α => [α] -> [α] -> [α]
merge a [] = a
merge [] a = a
merge xlist@(x:xs) ylist@(y:ys) | x < y = x : merge xs ylist
| otherwise = y : merge xlist ys
@dmalikov
dmalikov / Inversions.hs
Created June 11, 2012 18:22
Algorithms: design and analysis I, exercise1 (week1)
{-# LANGUAGE UnicodeSyntax #-}
module Inversions (inversions) where
inversions ∷ Ord α ⇒ [α] → Int
inversions = fst . inversions'
where
inversions' list@(_:_:_) = (leftInvs + rightInvs + splitInvs, sortedList)
where (leftInvs, leftSortedList) = inversions' leftList
(rightInvs, rightSortedList) = inversions' rightList
(splitInvs, sortedList) = mergeInvs leftSortedList rightSortedList
@dmalikov
dmalikov / Elements.hs
Created April 18, 2012 16:04
some bipolygon finder
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Elements
( aElements, bElements, sElements
) where
import Control.Applicative (liftA2)
import Types
@dmalikov
dmalikov / hipster.hs
Created March 28, 2012 22:01
Find some unlistenable artists in user library (via liblastfm)
import Control.Arrow ((***), (&&&))
import Control.Monad ((<=<), forM_, join, liftM, liftM2, when)
import Data.Maybe (fromMaybe)
import Kludges
import Network.Lastfm.API.Artist (getInfo)
import Network.Lastfm.Types
import Text.Printf
import Text.XML.Light
import qualified Network.Lastfm.API.Library as L
@dmalikov
dmalikov / lastfm-distance.hs
Created March 24, 2012 22:33
Some usage of liblastfm
import Control.Applicative ((<$>))
import Control.Monad ((<=<), forever, liftM, liftM2)
import Data.Function (on)
import Data.Maybe (fromMaybe)
import Data.Time.Format (formatTime)
import Data.Time.LocalTime (getZonedTime)
import GHC.Conc.IO (threadDelay)
import Network.Lastfm.Types
import Network.Lastfm.API.User
import System.Directory (getHomeDirectory)
@dmalikov
dmalikov / pr203.hs
Created January 3, 2012 22:47
Project Euler 203 (0.02s)
import Data.Numbers.Primes (primeFactors)
import Data.List (group, nub, sort)
import Control.Arrow ((&&&))
import PECore
squarefree :: Integer -> Bool
squarefree = all ((< 2) . snd) . map ((&&&) head length) . group . primeFactors
numFromPascalTriangles :: Integer -> [Integer]
numFromPascalTriangles n = nub . sort . concat . map (\x -> map (combinations x) $ [0..x]) $ [0..n-1]
@dmalikov
dmalikov / pr112.hs
Created January 2, 2012 05:32
Project Euler 112 (2s)
import PECore (numToList, listToNum)
import Control.Monad (ap)
import Data.List (sort)
bouncy :: (Num a, Ord a) => [a] -> Bool
bouncy = not . (\x -> all (>=0) x || all (<=0) x) . map (uncurry (-)) . ap zip tail
bouncyNumber :: Integer -> Bool
bouncyNumber = bouncy . numToList
@dmalikov
dmalikov / pr132.hs
Created December 31, 2011 12:56
Project Euler 132 (1s)
import PECore (fastPow)
import Data.Numbers.Primes (primes)
import Control.Arrow ((&&&))
main = print . sum . take 40 . map fst . filter ( (== 1) . snd) . map ( (&&&) id (fastPow 10 (10^9)) ) . dropWhile (<= 3) $ primes