This file contains hidden or 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 Closures where | |
| -- Learn to mimic the concept of (oop) encapsulation. | |
| -- From paolino, with love to his uscs (summer school 2016) mates | |
| -------------------------------- | |
| -- Library for place holders ---- | |
| --------------------------------- |
This file contains hidden or 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
| {-https://en.wikibooks.org/wiki/Algorithm_Implementation/Geometry/Convex_hull/Monotone_chain-} | |
| {-# language ViewPatterns #-} | |
| {- perimeter of convex hull of points -} | |
| import Data.List | |
| type P = (Double,Double) | |
| (.-.) :: P -> P -> P | |
| (x1, y1) .-. (x2, y2) = (x1 - x2, y1 - y2) |
This file contains hidden or 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 ViewPatterns #-} | |
| import System.IO (hSetBuffering, BufferMode(NoBuffering), stdout) | |
| import Data.Ord (comparing) | |
| import Data.List (minimumBy) | |
| import Control.Applicative ((<$>)) | |
| data Dir = SE | E | NE | S | R | N | SW | W | NW deriving (Enum, Show,Eq) | |
| dist (x,y) ((-) x -> cx, (-) y -> cy) = sqrt $ cx ^ 2 + cy ^ 2 |
This file contains hidden or 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 Control.Applicative | |
| import Control.Monad.List | |
| import Control.Monad.State | |
| liftLT :: Monad m => [a] -> ListT m a | |
| liftLT = ListT . return | |
| produceAndCountTuples :: [a] -> [b] -> ListT (State Int) (a,b) | |
| produceAndCountTuples xs ys = do |
This file contains hidden or 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 FlexibleInstances #-} | |
| {-# language MultiParamTypeClasses #-} | |
| {- | |
| Keeping a monoid running on a window of the stream | |
| -} | |
| import Pipes | |
| import qualified Pipes.Prelude as P | |
| import Control.Monad.Fix |
This file contains hidden or 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 DataKinds #-} | |
| {-# language TypeFamilies #-} | |
| {-# language MultiParamTypeClasses #-} | |
| {-# language FlexibleInstances #-} | |
| data Operation = Split | Correct | |
| class At (c:: Operation) b a where | |
| type AtPred c (b :: * -> *) a |
This file contains hidden or 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 RecursiveDo #-} | |
| {-# language ConstraintKinds #-} | |
| {-# language FlexibleContexts #-} | |
| {-# language OverloadedStrings #-} | |
| {-# language TemplateHaskell #-} | |
| {-# language GADTs #-} | |
| import Reflex.Dom | |
| import Data.Text (pack, Text) | |
| import qualified Data.Text as T |
This file contains hidden or 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
| resolver: lts-7.2 | |
| compiler: ghcjs-0.2.1.9007002_ghc-8.0.1 | |
| compiler-check: match-exact | |
| setup-info: | |
| ghcjs: | |
| source: | |
| ghcjs-0.2.1.9007002_ghc-8.0.1: | |
| url: http://ghcjs.tolysz.org/ghc-8.0-2016-10-01-lts-7.2-9007002.tar.gz | |
| sha1: a41ae415328e2b257d40724d13d1386390c26322 |
This file contains hidden or 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 ViewPatterns #-} | |
| {-# language FlexibleInstances #-} | |
| {-# language MultiParamTypeClasses #-} | |
| -- http://okmij.org/ftp/Haskell/perfect-shuffle.txt | |
| import System.Random (randoms, newStdGen) | |
| import Data.FingerTree (FingerTree, split, Measured (..), | |
| ViewL (..), viewl, fromList) | |
| import Data.Monoid (Sum (..), (<>)) |
This file contains hidden or 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
| data Bin a = Leaf a | Bin (Bin a) Int (Bin a) deriving Show | |
| count (Bin _ n _ ) = n | |
| count (Leaf _) = 1 | |
| fromListB :: [a] -> Bin a | |
| fromListB = head . head . dropWhile ((>1) . length) . | |
| iterate (collapse id ((+) `on` count) ) . collapse Leaf (\_ _ -> 2) | |
| collapse f g (x:y:rest) = Bin (f x) (x `g` y) (f y) : collapse f g rest |