Skip to content

Instantly share code, notes, and snippets.

View SamirTalwar's full-sized avatar
🦖
Hunting for bugs.

Samir Talwar SamirTalwar

🦖
Hunting for bugs.
View GitHub Profile
@SamirTalwar
SamirTalwar / AOC_01_1.ijs
Last active November 26, 2022 20:40
Solutions for Advent of Code 2021, in J. This is a warmup for 2022.
#!/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 `<`
@SamirTalwar
SamirTalwar / DataFamiliesExample.hs
Created January 12, 2022 16:04
An example of data families, in preparation for an article.
{-# 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
% vim: set syntax=prolog
:- use_module(library(clpfd)).
:- initialization(main, main).
puzzle([
[_, _, _, _, _, _, 4, _, 3],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, 6],
@SamirTalwar
SamirTalwar / Serially.scala
Created February 20, 2020 15:43
Serially execute a list of futures, in Scala. I find myself writing this fairly often, typically for testing or debugging.
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 =>
@SamirTalwar
SamirTalwar / Add Country Codes.scpt
Last active October 1, 2019 10:43
JavaScript to add country codes to all phone numbers without them, for the Mac Script Editor.
{
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)
}
@SamirTalwar
SamirTalwar / prime.pl
Created September 15, 2019 17:53
A prime number detector in Prolog that caches intermediate results.
:- 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),
@SamirTalwar
SamirTalwar / random-hacks.ts
Last active August 19, 2019 23:42
Random hacks you can do with TypeScript.
type Status = "passed" | "failed" | "error" | "unknown";
interface Things {
a: string;
b: number;
c: {
d: {
e: string;
};
f: Array<{ g: number }>;
@SamirTalwar
SamirTalwar / Tree.hs
Created May 10, 2019 16:46
A tree implementation in Haskell.
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
@SamirTalwar
SamirTalwar / sudoku.pl
Created December 22, 2017 13:04
Sudoku solver in Prolog.
% vim: set syntax=prolog
:- use_module(library(clpfd)).
:- initialization(main, main).
main(_) :- main.
main :-
current_input(S),
@SamirTalwar
SamirTalwar / update-yarn-lock.sh
Created March 2, 2017 17:18
Update yarn.lock files in Greenkeeper branches.
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