{-# LANGUAGE
DataKinds
, FlexibleContexts
, GADTs
, LambdaCase
, MultiParamTypeClasses
, OverloadedStrings
, PolyKinds
, QuantifiedConstraints
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeFamilies
, TypeOperators
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Type.List
(
SOP.NP (..)
, (*:)
, one
, Path (..)
, Join
, disjoin
, Additional (..)
, Elem
, In
, Length
, SubList
, SubsetList
, Sort
, MergeSort
, Twos
, FoldMerge
, Merge
, MergeHelper
, MapFst
) where
import Control.Category.Free
import Data.Function ((&))
import Data.Kind
import Data.Type.Bool
import GHC.TypeLits
import Generics.SOP as SOP
type family Join xs ys where
Join '[] ys = ys
Join (x ': xs) ys = x ': Join xs ys
disjoin
:: forall xs ys expr. SListI xs
=> NP expr (Join xs ys)
-> (NP expr xs, NP expr ys)
disjoin :: NP expr (Join xs ys) -> (NP expr xs, NP expr ys)
disjoin = case SListI xs => SList xs
forall k (xs :: [k]). SListI xs => SList xs
sList @xs of
SList xs
SNil -> \NP expr (Join xs ys)
ys -> (NP expr xs
forall k (a :: k -> *). NP a '[]
Nil, NP expr ys
NP expr (Join xs ys)
ys)
SList xs
SCons -> \(expr x
x :* NP expr xs
xsys) ->
case NP expr (Join xs ys) -> (NP expr xs, NP expr ys)
forall k (xs :: [k]) (ys :: [k]) (expr :: k -> *).
SListI xs =>
NP expr (Join xs ys) -> (NP expr xs, NP expr ys)
disjoin NP expr xs
NP expr (Join xs ys)
xsys of (NP expr xs
xs,NP expr ys
ys) -> (expr x
x expr x -> NP expr xs -> NP expr (x : xs)
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP expr xs
xs, NP expr ys
ys)
class Additional expr where
also :: expr ys -> expr xs -> expr (Join xs ys)
instance Additional (NP expr) where
also :: NP expr ys -> NP expr xs -> NP expr (Join xs ys)
also NP expr ys
ys = \case
NP expr xs
Nil -> NP expr ys
NP expr (Join xs ys)
ys
expr x
x :* NP expr xs
xs -> expr x
x expr x -> NP expr (Join xs ys) -> NP expr (x : Join xs ys)
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* (NP expr xs
xs NP expr xs
-> (NP expr xs -> NP expr (Join xs ys)) -> NP expr (Join xs ys)
forall a b. a -> (a -> b) -> b
& NP expr ys -> NP expr xs -> NP expr (Join xs ys)
forall a (expr :: [a] -> *) (ys :: [a]) (xs :: [a]).
Additional expr =>
expr ys -> expr xs -> expr (Join xs ys)
also NP expr ys
ys)
(*:) :: f x -> f y -> NP f '[x,y]
f x
x *: :: f x -> f y -> NP f '[x, y]
*: f y
y = f x
x f x -> NP f '[y] -> NP f '[x, y]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* f y
y f y -> NP f '[] -> NP f '[y]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP f '[]
forall k (a :: k -> *). NP a '[]
Nil
infixl 8 *:
one :: f x -> NP f '[x]
one :: f x -> NP f '[x]
one f x
f = f x
f f x -> NP f '[] -> NP f '[x]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP f '[]
forall k (a :: k -> *). NP a '[]
Nil
type family Elem x xs where
Elem x '[] = 'False
Elem x (x ': _) = 'True
Elem x (_ ': xs) = Elem x xs
type family In x xs :: Constraint where
In x xs = If (Elem x xs) (() :: Constraint)
(TypeError ('ShowType x ':<>: 'Text " is not in " ':<>: 'ShowType xs))
type family Length (xs :: [k]) :: Nat where
Length '[] = 0
Length (_ : xs) = 1 + Length xs
type family SubList (xs :: [k]) (ys :: [k]) :: Bool where
SubList '[] ys = 'True
SubList (x ': xs) '[] = 'False
SubList (x ': xs) (x ': ys) = SubList xs ys
SubList (x ': xs) (y ': ys) = SubList (x ': xs) ys
type family SubsetList (xs :: [k]) (ys :: [k]) :: Bool where
SubsetList '[] ys = 'True
SubsetList (x ': xs) ys = Elem x ys && SubsetList xs ys
type Sort ls = MergeSort (Twos ls)
type family MergeSort (ls :: [[Symbol]]) :: [Symbol] where
MergeSort '[] = '[]
MergeSort '[x] = x
MergeSort ls = MergeSort (FoldMerge ls)
type family Twos (ls :: [k]) :: [[k]] where
Twos (x ': y ': rs) = Merge '[x] '[y] ': Twos rs
Twos '[x] = '[ '[x]]
Twos '[] = '[]
type family Merge (ls :: [Symbol]) (rs :: [Symbol]) :: [Symbol] where
Merge '[] r = r
Merge l '[] = l
Merge (l ': ls) (r ': rs) = MergeHelper (l ': ls) (r ': rs) (CmpSymbol l r)
type family MergeHelper (ls :: [Symbol]) (rs :: [Symbol]) (cmp :: Ordering) where
MergeHelper ls (r ': rs) 'GT = r ': Merge ls rs
MergeHelper (l ': ls) rs leq = l ': Merge ls rs
type family FoldMerge (ls :: [[Symbol]]) :: [[Symbol]] where
FoldMerge (x ': y ': rs) = (Merge x y ': FoldMerge rs)
FoldMerge '[x] = '[x]
FoldMerge '[] = '[]
type family MapFst (ls :: [(j, k)]) :: [j] where
MapFst ('(j, _) ': rest) = j ': MapFst rest
MapFst '[] = '[]