Skip to content

Instantly share code, notes, and snippets.

Keybase proof

I hereby claim:

  • I am Decoherence on github.
  • I am qubitcoder (https://keybase.io/qubitcoder) on keybase.
  • I have a public key whose fingerprint is B2E9 8F37 4D4D 66AB 4AB5 CDCC 3ECE E817 6FFD C6C0

To claim this, I am signing this object:

@Decoherence
Decoherence / TicTacToe.hs
Last active August 29, 2015 14:19
Haskell: Tic-Tac-Toe console-based game
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RankNTypes #-}
import Control.Monad
import Data.Char
import Data.List
import Data.List.Split
import Data.Map (Map)
import qualified Data.Map as Map
import Text.Read
@Decoherence
Decoherence / TypeSafeRocket.hs
Last active August 29, 2015 14:19
Example: Type-safe rocket launch using the Either monad transformer.
module Main where
import Control.Monad.Trans
import Control.Monad.Trans.Either
import Safe
data Sensor = Temp
| Fuel
| Pressure
@Decoherence
Decoherence / Spock_PostgrSQL_Users.hs
Last active August 29, 2015 14:19
Haskell: Testing Spock web server using PostgreSQL backend and the 'users' library for user management & session handling.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
module Main where
import Database.PostgreSQL.Simple
import Data.Aeson hiding (json)
import Data.Monoid
import Data.Text (pack)
import GHC.Generics
@Decoherence
Decoherence / PrimeNumbers.hs
Last active August 29, 2015 14:19
Command-line utility to quickly generate prime numbers (Haskell)
import Control.Applicative
import Control.Monad
import Options
import Safe
{-
Command-line arguments:
-m: biggest prime less than m (required)
-l: show full list (optional)
@Decoherence
Decoherence / View_Patterns_Demo.hs
Last active August 29, 2015 14:16
Fun with View Patterns: Calculate bonus points for a customer based on their reward status
{-# LANGUAGE ViewPatterns #-}
module Main where
data Status = Silver
| Gold
| Platinum
deriving (Show)
type Points = Int
@Decoherence
Decoherence / JSON_Lens_Auto_Derive.hs
Last active August 29, 2015 14:16
Haskell JSON: Demonstrates how to automatically derive JSON instances for easy encoding/decoding of a nested data record. Also construct lenses for easy viewing/modification of fields.
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
import Data.Aeson
import qualified Data.ByteString.Lazy.Char8 as C
import GHC.Generics
-- For production code, use Text instead of String
data Person = Person { _personName :: String
, _personAge :: Int
@Decoherence
Decoherence / Servant_JSON_API.hs
Last active January 17, 2020 13:07
Haskell: Bookstore REST API with PostgreSQL backend using Servant
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import Control.Applicative
import Control.Monad.IO.Class
import Data.Aeson
@Decoherence
Decoherence / Scotty_Lucid_PostgreSQL.hs
Last active May 16, 2023 01:45
Haskell: Simple REST example. Process request, retrieve data from PostgreSQL backend, and respond with programmatically-generated HTML.
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Control.Monad
import Control.Monad.Trans
import Data.Monoid
import Data.Text
import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.FromRow
import Lucid
import Web.Scotty
@Decoherence
Decoherence / Functional_Dependencies_Animals.hs
Last active August 29, 2015 14:13
Haskell: Functional dependency example -- for any instance of the Pet type class, the type of animal uniquely determines the sound it can make.
-- | Sandbox Haskell package
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
module Main where
class Pet animal sound | animal -> sound where
speak :: animal -> sound
data Sound = Bark | Meow deriving (Show)