Skip to content

Instantly share code, notes, and snippets.

@MgaMPKAy
MgaMPKAy / Main.hs
Created August 24, 2014 04:02
Dump command history into InfluxDB (rember to `iconv -t utf8 -c ~/.bash_history > history`)
{-# LANGUAGE OverloadedStrings #-}
import Parser
import Types
import Network.HTTP.Client
import Control.Applicative
import Control.Monad.Trans (liftIO)
import Database.InfluxDB
main = do
@MgaMPKAy
MgaMPKAy / thread_switch.hs
Created July 11, 2014 10:25
It's nonsense to compare switches of native thread and green thread (https://ruby-china.org/topics/20367)
import Control.Concurrent
import Control.Monad
import Data.IORef
main = do
c <- newIORef (0::Int)
arr <- newIORef []
replicateM_ 100 $ forkIO $ thread c
import Options.Applicative
import Data.Monoid
type PackageDB = String
type Package = String
type Dir = String
type Archive = String
data Options = Options [PackageDB] Command deriving (Show)
import Data.Monoid
import Data.Maybe
fizzBuzzWhizz (x, y, z) a =
fromJust $ getFirst $ mconcat $ map First
[ x `contains` a
, fizz a x <> buzz a y <> whizz a z
, Just $ show a
]
where
@MgaMPKAy
MgaMPKAy / fib.hs
Created May 5, 2014 15:05
PatternSynonyms example
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
import System.Environment
import Data.Ratio
import Control.Applicative ((<$>))
viewRatio x = (numerator x, denominator x)
pattern p :% q <- (viewRatio -> (p, q))
main = do
{-# LANGUAGE BangPatterns #-}
module NQueens where
import Data.Bits
import Control.Parallel
queue n = queensHelper (1 `shiftL` n - 1) 0 0 0
queensHelper :: Int -> Int -> Int -> Int -> Int
queensHelper !allOnes !leftDiag !columns !rightDiags =
@MgaMPKAy
MgaMPKAy / Sudoku.hs
Last active August 29, 2015 13:59
Sudoku solver using SMT solver through sbv
{-# LANGUAGE ScopedTypeVariables #-}
module Sudoku where
import Data.SBV
import Control.Monad (zipWithM_)
sudoku game = do
vs :: [SWord8] <- mkExistVars 81
zipWithM_ setVar game vs
mapM_ (\x -> constrain $ x .>= 1 &&& x .<= 9) vs
@MgaMPKAy
MgaMPKAy / SafeFFI.hs
Created April 5, 2014 12:31
Safe and unsafe FFI slowdown compare to C
{-# LANGUAGE ForeignFunctionInterface #-}
import Foreign
import Foreign.C
data WhiteDB
data Record
foreign import ccall "wg_attach_database" c_wg_attach_database :: CString -> CInt -> IO (Ptr WhiteDB)
foreign import ccall "wg_detach_database" c_wg_detach_database :: Ptr WhiteDB -> IO CInt
{-# LANGUAGE RecordWildCards #-}
-- 1. Without lenses (and state monad), even a simple flat record becomes clumsy
import System.Random
import System.IO
import Control.Applicative ((<$>))
import Control.Monad (when)
import Text.Read (readMaybe)
import Data.Char (toLower)