Skip to content

Instantly share code, notes, and snippets.

@chowells79
chowells79 / LICENSE
Last active February 2, 2024 18:42
Monty Hall Problem
Copyright (c) 2023-2024 chowells
Permission is hereby granted, free of charge, to any person obtaining
a copy of this software and associated documentation files (the
"Software"), to deal in the Software without restriction, including
without limitation the rights to use, copy, modify, merge, publish,
distribute, sublicense, and/or sell copies of the Software, and to
permit persons to whom the Software is furnished to do so, subject to
the following conditions:
@chowells79
chowells79 / dijkstra.hs
Last active December 23, 2021 08:02
Dijkstra's algorithm using psqueues package
import Data.List (foldl')
-- unordered-containers
import Data.Hashable (Hashable)
import qualified Data.HashMap.Strict as HM
-- psqueues
import qualified Data.HashPSQ as P
-- Streams all nodes as they are found in order of non-decreasing cost
@chowells79
chowells79 / crt.hs
Last active August 30, 2022 01:31
Chinese Remainder Theorem, documented
-- Chinese Remainder Theorem
--
-- Generalized to work with non-coprime moduli when a solution exists
--
-- Inputs and output are (remainder, modulus) pairs
-- Preconditions:
-- 1. r1 `mod` gcd m1 m2 == r2 `mod` gcd m1 m2
-- 2. m1 > 0
-- 3. m2 > 0
--
def suffixes(string):
return [ string[i:] for i in range(len(string)) ]
def common_prefix(string1, string2):
for i, (c1, c2) in enumerate(zip(string1, string2)):
if c1 != c2:
return i
return min(len(string1), len(string2))
def sublist_rank(target):
module SortByKey where
-- Sorts an array by way of a function to extract a limited-range Int
-- key. This is a stable sort, suitable as a building block for a
-- bottom-up radix sort.
--
-- Runs in O(|bounds| + key function * n) time
sortByKey ::
(Int, Int) -- minimum and maximum key produced by the key
-- extraction function
-- Finds the largest Integer x such that 'f x <= target'
--
-- preconditions:
-- the provided function is monotonically non-decreasing
-- there exist an Integer y such that 'f y > target'
-- there exists an Integer z such that 'f z <= target'
--
-- violation of the first precondition may result in incorrect output
-- violation of the second or third preconditions results in non-termination
unboundedSearch :: Ord a => (Integer -> a) -> a -> Integer
{-# LANGUAGE RankNTypes #-}
module ReflectiveIntersperse (intersperse, intersperse') where
import Data.Reflection (Reifies, reflect, reify)
import Data.Foldable (Foldable(..))
data Between a s = Empty | Has a
instance (Reifies s a, Semigroup a) => Semigroup (Between a s) where
{-# Language PolyKinds, GADTs, ScopedTypeVariables, TypeApplications #-}
module HasochistIntersperse (intersperse) where
import Data.Singletons
data Between a v = Empty | Has v deriving (Eq, Ord, Show)
instance forall k (a :: k) v.
(SingI a, SingKind k, v ~ Demote k, Semigroup v) =>

Class import magic

Demonstrate how to get things to magically happen when you import instances of a class.

-- The ancient symbol consisting of a serpent or dragon devouring its
-- own tail. This is the central loop of a BFS implementation that
-- used laziness to share the list of enqueued elements for future
-- processing with the output list of visited elements.
--
-- That implementation detail isn't that important for using it,
-- though. The first argument is a processing function that takes the
-- current element and state, and returns any number of new elements
-- to process along with a new state for processing the next
-- element. The second argument is an initial list of elements to