Skip to content

Instantly share code, notes, and snippets.

View Ino4137's full-sized avatar
🤔
hmm

Ino4137

🤔
hmm
View GitHub Profile

Weapons

nameskilldamcritrangeencumpricerarityspecial
knifem:light+13engaged1251
pistolr:light63medium15004
laser pistolr:light44medium14004accurate 1, pierce 1

Armor

namedefensesoakencumpricerarityhardspecial
technical vest01330053
@Ino4137
Ino4137 / bananas.hs
Last active March 23, 2019 23:19
recursion schemes, based on the paper
{-# LANGUAGE DeriveTraversable #-}
import Prelude hiding (iterate)
import Control.Monad ((<=<))
data Fix m = In {out :: m (Fix m)}
data ListF x xs = Nil | Cons x xs
deriving (Functor, Foldable, Traversable)
@Ino4137
Ino4137 / plotter.hs
Created October 17, 2018 18:03
Plotter - simple function plotting
{-# LANGUAGE DeriveTraversable, GADTs #-}
import Data.List (intersperse,intercalate,transpose)
import Text.Printf (printf)
type Graph = GraphF Bool
type Function = Integer -> Integer -> Bool
height, width :: Integer
height = 40
@Ino4137
Ino4137 / frc.hs
Created May 5, 2018 20:31
frc wars
import Control.Monad.Trans.State
import Data.List
frc sequ = fst $ execState (mapM_ check sequ) (Nothing,[])
check :: Eq a => a -> State (Maybe a, [a]) ()
check x = do
(status,prev) <- get
case status of
Just x ->
@Ino4137
Ino4137 / sierpinski.hs
Last active April 25, 2018 13:18 — forked from Xophmeister/sierpinski.hs
Sierpinski Triangle in Haskell
sumPairs :: [Integer] -> [Integer]
sumPairs (x:y:s) = (x + y) : sumPairs (y:s)
sumPairs _ = []
pascal :: Integer -> [Integer]
pascal 0 = [1]
pascal n = sumPairs $ 0 : pascal (n - 1) ++ [0]
sierpinski :: Integer -> String
sierpinski n = pascal n >>= (ascii . odd)
@Ino4137
Ino4137 / solution.hs
Last active April 12, 2018 20:41
Solution Haskell
import Data.List
import Data.Function
import Control.Monad
import Text.Printf
data Tree a =
Leaf | Unary a | Node (Tree a) a (Tree a)
deriving (Eq, Show)
data From = F | B deriving (Eq, Show)
@Ino4137
Ino4137 / 666.rs
Created January 15, 2018 23:18
AOC day 5 part 1 UNHOLY
macro_rules! walker {
// step
($steps:expr; $node:expr; [$($listB:tt),* $prev:expr]; [$next:expr, $($listF:expr),+]) => {
match $steps {
$steps if $steps == 0 => {
*$node + 1;
($node - 1; $node; [$listB, $prev]; [$next, $listF];)
},
$steps if $steps > 0 => {
($steps - 1; $next; [$listB, $prev, $node]; [$listF])