Skip to content

Instantly share code, notes, and snippets.

View adamgundry's full-sized avatar

Adam Gundry adamgundry

View GitHub Profile
@adamgundry
adamgundry / DetectScopedTypeVariables.hs
Created January 26, 2024 18:22
Haskell program to test whether ScopedTypeVariables is enabled
{-# LANGUAGE GHC2021, NoScopedTypeVariables, RequiredTypeArguments, AllowAmbiguousTypes #-}
import Data.Proxy
hasScopedTypeVariables :: Bool
hasScopedTypeVariables = f Char
f :: forall a -> C a => Bool
f a = g @Int
where
@adamgundry
adamgundry / SafeByteStringLiterals.hs
Created December 10, 2023 21:31
OverloadedLabels for checked ByteString literals
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import qualified Data.ByteString.Char8 as BS
import Data.Kind
import Data.Proxy
import GHC.OverloadedLabels
{-# LANGUAGE DataKinds, PolyKinds, StandaloneKindSignatures, TypeFamilies, UndecidableInstances #-}
import GHC.TypeLits
import Data.Kind
-- This is the proposed API for Warning/WarningBin
type Warning :: Symbol -> WarningBin -> ErrorMessage -> Constraint
class Warning flag bin msg
@adamgundry
adamgundry / Joinable.js
Last active April 9, 2020 21:43
Optics composition with backwards reasoning
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
@adamgundry
adamgundry / GenericDiscrimination.hs
Created March 4, 2020 22:13
Being a horrible abuse of INCOHERENT to determine whether Generic instances exist
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

Keybase proof

I hereby claim:

  • I am adamgundry on github.
  • I am adamgundry (https://keybase.io/adamgundry) on keybase.
  • I have a public key ASCjG4OJrVK8rcTnOXwK-GoHUZmq02gkastcgZX5n9oxhAo

To claim this, I am signing this object:

@adamgundry
adamgundry / Spells.hs
Created November 20, 2019 23:32
Dark dependently-typed magic
-- https://www.reddit.com/r/haskell/comments/dywiqx/question_about_disallowing_impossible_states/
-- and influenced by https://gist.github.com/gelisam/3dd536882296f672d3bcdfd88c98ac10
{-# LANGUAGE DataKinds, GADTs, PolyKinds, TypeFamilies #-}
module Spells where
data Nat where
Zero :: Nat
Suc :: Nat -> Nat
@adamgundry
adamgundry / HasField.hs
Created October 16, 2019 07:58
HasField with support for partial fields
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Main(main) where
import Control.Concurrent
import Control.Exception
import Control.Monad.Reader
import Control.Monad.State
import Data.Acid
@adamgundry
adamgundry / licenses.sh
Created July 2, 2018 15:41
Quick hack to collect licenses of dependencies using stack
#!/bin/bash
# This is a quick hack using stack to list dependencies and then
# copying their licenses from the locations in which it stores them.
# It tries various possible filenames in the store first, then tries
# the global location for system packages. It will miss out licenses
# for parts of the local project, the "rts" package (but that's okay,
# because it is covered by the license for "base"), and will
# (silently) exclude licenses for underlying C libraries.
LOCAL_PATH=.stack-work/install/x86_64-linux/lts-9.0/8.0.2/doc/