Skip to content

Instantly share code, notes, and snippets.

View L-TChen's full-sized avatar

Liang-Ting Chen L-TChen

View GitHub Profile
@L-TChen
L-TChen / JSON-RPC.hs
Last active May 16, 2018 13:30
A simple Haskell JSON-RPC server implementation using Existential Type and Monad stack
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
module JSON_RPC where
import ReadExcept
@L-TChen
L-TChen / ReadExcept.hs
Last active May 15, 2018 21:03
A Reader monad composed with an Exception monad.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGe FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module ReadExcept (
module ReadExcept
, module Control.Monad.Reader
, module Control.Monad.Except
, module Control.Monad.Identity
) where
@L-TChen
L-TChen / Caesar.hs
Last active May 27, 2018 21:31
FLOLAC'18 Exercise: A case-sensitive Caesar cipher and decipher based on frequency analysis, written in Haskell.
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE TupleSections #-}
module Caesar where
import Data.Map (Map, fromList, fromListWith, unionWith)
import Data.Char
import Data.List
import Data.Function
encode ∷ Int → String → String
@L-TChen
L-TChen / Memo.hs
Last active December 21, 2021 15:40
Memoization with IntMap and State monad in Haskell
{-# LANGUAGE FlexibleContexts, BangPatterns #-}
import Data.IntMap.Strict
import Data.Maybe
import Data.Function
import Control.Monad.Identity
import Control.Monad.State.Lazy hiding (fix)
import Prelude hiding (lookup)
@L-TChen
L-TChen / Vec.hs
Last active November 6, 2018 16:41
An example of type families---length-indexed lists---in Haskell
{-# LANGUAGE TypeFamilies, DataKinds, KindSignatures, GADTs #-}
{- TypeFamilies is required to define type-level functions -}
data Nat = Zero | Succ Nat
data Fin :: Nat -> * where
FZero :: Fin ('Succ n)
FSucc :: Fin n -> Fin ('Succ n)
data Vector (a :: *) :: Nat -> * where
@L-TChen
L-TChen / Unification.hs
Last active May 19, 2021 01:11
An implementation of McBride's structural first-order unification algorithm in Haskell. Tested on GHC 8.4.4
{-# LANGUAGE FlexibleContexts, FlexibleInstances #-}
{-# LANGUAGE TypeInType , ScopedTypeVariables , TypeFamilies, TypeOperators #-}
{-# LANGUAGE GADTs, StandaloneDeriving #-}
{-# LANGUAGE Safe #-}
module Unification where
import Data.Kind
import Prelude hiding ((++))
@L-TChen
L-TChen / BFS.hs
Last active November 30, 2018 16:06
Chris Okasaki's Queue-Based Breadth-First Traversal and the Reconstruction from its Sequential Representation of Binary Tree
{-# LANGUAGE DeriveGeneric #-}
{- Building a tree based on its bfs result. -}
module BFS where
import Test.QuickCheck hiding ((><))
import GHC.Generics
import Generic.Random
import Data.Sequence (Seq (..), singleton, (><))
@L-TChen
L-TChen / VectorPattern.hs
Last active June 30, 2023 13:42
Pattern matching for Vector using PatternSynonyms in Haskell
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
import Data.Vector as V
pattern Empty :: Vector a
pattern Empty <- (V.null -> True) where Empty = V.empty
uncons :: Vector a -> Maybe (a, Vector a)
uncons Empty = Nothing
@L-TChen
L-TChen / Quickselect.hs
Last active January 3, 2019 09:09
The derivation of Quickselect from Quicksort, see my blog post https://xcycl.wordpress.com/2019/01/02/fromquicksorttoquickselect/
{-# LANGUAGE TypeApplications #-}
import Test.QuickCheck
import Data.List (sort)
selectOrigin k = (!! k) . sort
select :: (Ord a) => Int -> [a] -> a
select k (x:xs) = case compare k n of
LT -> select k ys
EQ -> x
@L-TChen
L-TChen / Deque.hs
Last active January 18, 2019 19:14
Purely Functional Deque
{-# LANGUAGE ViewPatterns, PatternSynonyms #-}
module Deque where
import Text.Read
import Data.Bifunctor
import Prelude hiding (length, init, tail, last, head)
import qualified Prelude as P
data Deque a =