Skip to content

Instantly share code, notes, and snippets.

View dmwit's full-sized avatar

Daniel Wagner dmwit

View GitHub Profile
data RawDebtRec = RawDebtRec
{ company :: Text
, debt :: Int
, phones :: [Int]
}
parseCompany o = o .: "company"
<|> o .: "company" >>= (.: "name")
parseInt o = parseJSON o <|> (read <$> parseJSON o)
@dmwit
dmwit / gmonoid.hs
Created May 8, 2019 17:48
maybe a way to use generic-deriving
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
import Generics.Deriving.Monoid
import Generics.Deriving.Semigroup
import GHC.Generics
data Foo = Foo () deriving (Generic, GSemigroup, GMonoid)
instance Semigroup Foo where (<>) = gsappend
instance Monoid Foo where mempty = gmempty
@dmwit
dmwit / 83601.cry
Created May 4, 2019 17:27
cryptol code to solve https://puzzling.stackexchange.com/q/83601/8871; use `cryptol 83601.cry -c ':sat isSolution'` to run it
isSolution w o n e = all isDigit [w,o,n,e] /\ no*won*won == wonewon /\ no != 0 where
no = fromDigits [o,n]
won = fromDigits [n,o,w]
wonewon = fromDigits [n,o,w,e,n,o,w] : [32]
isDigit x = 0 <= x /\ x <= 9
fromDigits digits = sum [digit * 10^^exp | digit <- digits | exp <- [0...]]
-- bad: everything in ... is nested
do
v <- foo
case v of
Matches v' -> ...
_ -> throwError "doesn't match"
-- good: ... is not nested
do
v <- foo
{-# Language
Rank2Types,
GADTs,
DataKinds,
PolyKinds,
TypeFamilies,
DatatypeContexts,
MultiParamTypeClasses,
UndecidableInstances,
UndecidableSuperClasses
@dmwit
dmwit / xmonad.hs
Created April 15, 2019 22:34
how to xmonad graceful exit
import Control.Concurrent
import Control.Monad.State
import qualified Data.Map as M
import System.Exit
import XMonad.Core
import XMonad.Operations
import qualified XMonad.StackSet as W
windowIDs :: W.StackSet i l a sid sd -> [a]
windowIDs ss
@dmwit
dmwit / bf.hs
Created April 11, 2019 15:20
simple symbolic execution for straight-line bf
import Data.Int
import Data.IntMap (IntMap)
import qualified Data.IntMap as IM
data CellUpdate = CellUpdate
{ inputID :: Maybe Int
, offset :: Int8
} deriving (Eq, Ord, Read, Show)
instance Monoid CellUpdate where mempty = CellUpdate Nothing 0
import Data.List
import Data.Maybe
import Data.Ord
shareArea = 85
pizzaArea size = pi * (size/2)^2
totalPizzaArea = sum . map pizzaArea
sufficient area sizes | area < 0 = [[]]
sufficient area [] = []
@dmwit
dmwit / gist:c764c9b46b08c9aa88fd2d3a5f1f010a
Created March 24, 2019 13:17
applicative initialization
import Control.Monad.Writer hiding (liftIO)
import Data.Functor.Compose
type InitIO = Compose (Writer (IO ())) IO
-- | Do no initialization
liftIO :: IO a -> InitIO a
liftIO = Compose . pure
liftInit :: IO () -> InitIO ()
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE TypeFamilies #-}
import GHC.Exts
class (forall a. A t a => A t [a]) => B t where type A t a :: Constraint
instance B t => B [t] where type A [t] a = A t a