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
#!/usr/bin/env jconsole | |
NB. magic helper function | |
readfile =: 1 !: 1 | |
NB. read from STDIN | |
input =: readfile 3 | |
NB. split on whitespace, convert to numbers, and unbox | |
numbers =: > (_1 ". each (cutopen input)) | |
NB. drop the last element, drop the first element, and compare with `<` |
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 NoStarIsType #-} | |
{-# LANGUAGE TypeFamilies #-} | |
import Data.Kind (Type) | |
import Prelude hiding (sum) | |
class CanSum a where | |
data Sum a | |
buildSum :: a -> Sum a | |
runSum :: Num n => Sum a -> n |
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
% vim: set syntax=prolog | |
:- use_module(library(clpfd)). | |
:- initialization(main, main). | |
puzzle([ | |
[_, _, _, _, _, _, 4, _, 3], | |
[_, _, _, _, _, _, _, _, _], | |
[_, _, _, _, _, _, _, _, 6], |
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
object Serially { | |
def apply[T, U](values: Seq[T])(body: T => Future[U])(implicit executionContext: ExecutionContext): Future[List[U]] = | |
apply(values.toList)(body) | |
def apply[T, U](values: List[T])(body: T => Future[U])(implicit executionContext: ExecutionContext): Future[List[U]] = | |
values match { | |
case Nil => | |
Future.successful(List.empty) | |
case head :: tail => | |
body(head).flatMap(headResult => |
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
{ | |
const countryCode = '+44' | |
const addCountryCodeToPhoneNumbers = person => { | |
for (const phone of person.phones()) { | |
if (phone.value().startsWith('0')) { | |
const newValue = phone.value().replace(/^0/, countryCode) | |
console.log(`${person.name()}: ${phone.value()} → ${newValue}`) | |
phone.value.set(newValue) | |
} |
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
:- dynamic(prime/1). | |
prime(P) :- | |
P > 1, | |
\+ not_prime(P), | |
asserta(prime(P) :- !). | |
not_prime(P) :- | |
SqrtP is round(sqrt(P)), | |
between(2, SqrtP, N), |
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
type Status = "passed" | "failed" | "error" | "unknown"; | |
interface Things { | |
a: string; | |
b: number; | |
c: { | |
d: { | |
e: string; | |
}; | |
f: Array<{ g: number }>; |
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 Tree where | |
data Tree a | |
= Node [Tree a] | |
| Leaf a | |
deriving (Eq, Show) | |
instance Functor Tree where | |
f `fmap` Leaf value = Leaf $ f value | |
f `fmap` Node children = Node $ fmap (fmap f) children |
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
% vim: set syntax=prolog | |
:- use_module(library(clpfd)). | |
:- initialization(main, main). | |
main(_) :- main. | |
main :- | |
current_input(S), |
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
set -ex | |
for branch in $(git branch -a | fgrep greenkeeper | gsed -r 's#^ *remotes/origin/##'); do | |
git checkout $branch | |
yarn install | |
git add yarn.lock | |
git commit -m 'Update yarn.lock.' | |
git push | |
git checkout master | |
git branch -d $branch |
NewerOlder