title: MTLiens author: Jason Shipman | jship patat: wrap: true margins: left: 10 right: 10 incrementalLists: true ...
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Debouncer | |
( Debouncer | |
, Task | |
, new | |
, defaultDelay | |
, run | |
) where | |
import Control.Applicative as Applicative | |
import Control.Bind (bind, discard, pure) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE BlockArguments #-} | |
{-# LANGUAGE ConstraintKinds #-} | |
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
{-# LANGUAGE PolyKinds #-} | |
{-# LANGUAGE ScopedTypeVariables #-} | |
{-# LANGUAGE TypeApplications #-} | |
{-# LANGUAGE TypeFamilies #-} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- This script sketches out a way of doing some processing in response to one or | |
-- more changes being made to tables throughout the transaction. The processing | |
-- is done just once before the transaction commits. | |
begin; | |
-- Create a table that stores a marker indicating whether or not a change has | |
-- happened in this transaction. We aren't concerned with what the change | |
-- specifically was, just that there was a change. | |
drop table if exists changed; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
jq --sort-keys 'walk( if type == "array" then sort else . end )' |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- i | i | |
-- ---+--- | |
-- 1 | | |
-- 2 | 2 | |
-- (2 rows) | |
select * | |
from ( | |
values (1), (2) | |
) x(i) | |
left join lateral ( |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE DerivingStrategies #-} | |
module Scratch where | |
import Data.Proxy (Proxy(..)) | |
import Servant.API ((:<|>)(..), (:>), Capture, DeleteNoContent, Get, JSON, Link, ReqBody, PutNoContent) | |
import Servant.API.Generic (GenericMode((:-)), Generic, ToServantApi, genericApi) | |
import Servant.Links (allLinks) | |
type FooAPI = ToServantApi FooRoutes |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE BlockArguments #-} | |
{-# LANGUAGE DerivingVia #-} | |
{-# LANGUAGE QuantifiedConstraints #-} | |
module QuantifiedConstraintsExample | |
( Stuff(..) | |
, Things | |
, getThingsIO | |
, getThings | |
) where |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} | |
import Control.Exception (PatternMatchFail(..), evaluate) -- @base@ | |
import Control.Exception.Safe (catch) -- @safe-exceptions@ | |
import Test.HUnit (assertFailure) -- @HUnit@ | |
import Test.Hspec (HasCallStack) -- @hspec@ | |
import qualified Test.Hspec as Hspec -- @hspec@ | |
shouldReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m () | |
shouldReturn action expected = action >>= \x -> x `shouldBe` expected |
NewerOlder