Skip to content

Instantly share code, notes, and snippets.

View melrief's full-sized avatar

Mario Pastorelli melrief

View GitHub Profile
@melrief
melrief / swap.hs
Last active August 29, 2015 13:55
Print swap memory used by each process
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Control.Exception
import Control.Monad
import Data.Char
import Data.List
import Data.Maybe
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as C
import Prelude hiding (readFile)
@melrief
melrief / csv.hs
Created November 25, 2013 10:26
Create a list of strings from a CSV line. Requires the DList library installed. Usage example: ghc csv.hs; ./csv 'foo,bar,"foo,bar","foo bar "" foo,,bar",bar'
import Control.Monad (forM_)
import qualified Data.DList as DL
import System.Environment (getArgs,getProgName)
import System.Exit (exitSuccess)
data CSVState = OutsideQuote | InsideQuote | AfterQuote
listFromCSV :: String
→ [String]
listFromCSV = toResult ∘ foldl parseChar (OutsideQuote,DL.empty,DL.empty)
@melrief
melrief / 23Tree.hs
Last active December 26, 2015 20:09
23Tree implementation in Haskell (http://en.wikipedia.org/wiki/2-3_tree)
{-# LANGUAGE InstanceSigs #-}
module Data.TwoThreeTree where
import Control.Applicative
import Data.Foldable
import Data.Traversable
import Prelude hiding (foldr)
data Tree23 k = Leaf
@melrief
melrief / ViewConvexHull.hs
Created August 31, 2013 22:47
An example of Graphics.Rendering.Chart usage from the haskell chart package (https://github.com/timbod7/haskell-chart/wiki). Calculates and shows the convex hull (http://en.wikipedia.org/wiki/Convex_hull) from a finite list of points using the Graham's scan method (http://en.wikipedia.org/wiki/Graham_scan)
-- To build just copy this and convexhull.cabal somewhere
-- and then run cabal build
--
-- Usage Example:
-- > ./dist/build/viewConvexHull/viewConvexHull plot.pdf 1,10 10,5 4,6 7,9 20,1 4,2 5,6 8,2 3,9
--
-- this creates a pdf file called plot.pdf with the plot in the current directory
module Main where
import Control.Arrow
import Data.Colour.RGBSpace.HSV (RGB, hsv)
nextColor :: (RealFrac a) => a -> a -> a -> (RGB a,a)
nextColor h s v = let h' = (h + golden_ratio_conjugate) % 360
in (hsv h' s v,h')
where golden_ratio_conjugate = 222.4922359499622 -- 0.618033988749895 * 360
dividend % divisor = dividend - divisor *
(fromIntegral $ floor (dividend/divisor))
goldenColors :: (RealFrac a) => a -> a -> a -> [RGB a]
@melrief
melrief / lines.hs
Created July 19, 2013 19:14
Lazily prepend the line number to each line
import Control.Monad (unless)
import Prelude hiding (catch)
import System.IO (isEOF)
prependLineNums :: Int -> IO ()
prependLineNums n = isEOF >>= flip unless prependLineNum
where prependLineNum = getLine >>= putStrLn . (++) (padTo 5 $ show n)
>> prependLineNums (n+1)
padTo c s = case c `compare` length s of
GT -> s ++ replicate (c - length s) ' '