This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
def prefix_function(s): | |
result = len(s) * [0] | |
for (i, c) in enumerate(s): | |
if i == 0: | |
continue | |
guess = result[i - 1] | |
while True: |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Dfs where | |
import Control.Monad.State | |
import Data.IntMap (IntMap) | |
import Data.IntSet (IntSet) | |
import Data.Maybe (fromMaybe) | |
import qualified Data.IntMap as IntMap | |
import qualified Data.IntSet as IntSet | |
type Vertex = Int |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DeriveFunctor #-} | |
{-# LANGUAGE LambdaCase #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
{-# LANGUAGE StandaloneDeriving #-} | |
{-# OPTIONS -Wall -fno-warn-orphans #-} | |
module Lecture1 where | |
import Data.List (partition) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import Control.Monad | |
import Data.Functor ((<$>)) | |
import Text.HTML.TagSoup | |
extractData tags = | |
case dropWhile (~/= "<td class=problem_solved>") tags of | |
[] -> [] | |
ls@(hd : tl) -> (take 8 ls : extractData tl) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE TypeOperators #-} | |
module Lecture6 where | |
import Control.Applicative | |
import Control.Monad.State hiding (sequence) | |
import Data.Char (isSpace) | |
import Data.Monoid hiding (getAll) | |
import Prelude hiding (sequence) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE UndecidableInstances #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE FunctionalDependencies #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
module Typelevel where | |
import Prelude hiding (sum) | |
-- type-level natural numbers | |
data Zero = Zero |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Indexed where | |
import Prelude hiding ((>>=), (>>)) | |
class IxFunctor f where | |
imap :: (a -> b) -> f j k a -> f j k b | |
class IxFunctor f => IxPointed f where | |
ireturn :: a -> f i i a |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# OPTIONS_GHC -Wall #-} | |
{-# LANGUAGE FlexibleInstances, TupleSections #-} | |
import Prelude hiding (repeat) | |
class Functor w => Comonad w where | |
extract :: w a -> a | |
extend :: (w a -> b) -> (w a -> w b) | |
data Product e a = Product e a |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Window | |
import Mouse | |
fpsCount = 35 | |
delta = fps fpsCount | |
time = foldp (+) 0.0 delta | |
timeSeconds = (\ x -> x / 1000.0) <~ time | |
black = rgb 0 0 0 | |
display (w, h) (x, y) t = |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Refresher where | |
data ℕ : Set where | |
zero : ℕ | |
succ : ℕ → ℕ | |
_+_ : ℕ → ℕ → ℕ | |
zero + n = n | |
succ n + m = succ (n + m) |
NewerOlder