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 AllowAmbiguousTypes #-} | |
{-# LANGUAGE PolyKinds #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
module Permissions | |
( Permission, | |
PermissionLabel, | |
HasPermission, |
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 Abc (jsonWith') where | |
import Data.Aeson hiding (Value (..)) | |
import Data.Aeson.Key qualified as Key | |
import Data.Aeson.KeyMap qualified as KM | |
import Data.Aeson.Parser.Internal hiding (jsonWith') | |
import Data.Attoparsec.ByteString qualified as A | |
import Data.Attoparsec.ByteString.Char8 (Parser, char, string) | |
import Data.Function (fix) | |
import Data.Functor (($>)) |
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 Postgres.Decoder where | |
import Control.Applicative (Alternative) | |
import Data.Aeson qualified as Json | |
import Data.Aeson.BetterErrors qualified as Json | |
import Data.Error.Tree | |
import Data.Typeable (Typeable) | |
import Database.PostgreSQL.Simple.FromField qualified as PG | |
import Database.PostgreSQL.Simple.FromRow qualified as PG | |
import Json qualified |
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 AllowAmbiguousTypes #-} | |
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE LambdaCase #-} | |
{-# LANGUAGE QuasiQuotes #-} | |
module Json.Enc where | |
import Data.Aeson (Encoding, Value (..)) | |
import Data.Aeson.Encoding qualified as AesonEnc | |
import Data.Aeson.Key qualified as Key |
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
-- | Implement this class if you want your type to only implement the part of 'Num' | |
-- that allows creating them from Integer-literals, then derive Num via 'NumLiteralOnly': | |
-- | |
-- @ | |
-- data Foo = Foo Integer | |
-- deriving (Num) via (NumLiteralOnly "Foo" Foo) | |
-- | |
-- instance IntegerLiteral Foo where | |
-- integerLiteral i = Foo i | |
-- @ |
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 ImportQualifiedPost #-} | |
{-# LANGUAGE DerivingVia #-} | |
module Main where | |
import Control.Foldl (Fold) | |
import Control.Foldl qualified as Fold | |
import Data.Function ((&)) | |
import Data.Profunctor | |
import Data.Semigroup |
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 #-} | |
{-# LANGUAGE LambdaCase #-} | |
module Label | |
( -- * Labels | |
Label, | |
label, | |
label', | |
getLabel, |
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 Label | |
( Label, | |
label, | |
label', | |
) | |
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
let | |
list = | |
rec { | |
empty = { a = null; cons = null; }; | |
singleton = x: { a = x; cons = null; }; | |
cons = x: xs: { a = x; cons = xs; }; | |
# O(n) | |
foldr = f: zero: |
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 LambdaCase #-} | |
module Pretty | |
( -- * Pretty printing for error messages | |
Err, | |
printPretty, | |
-- constructors hidden | |
prettyErrs, | |
message, | |
messageString, |
NewerOlder