summaryrefslogtreecommitdiff
path: root/lib/KindLinter.hs
blob: ccca1db5a691f5a5f95228371e32a2a247592304 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
{-# LANGUAGE AllowAmbiguousTypes       #-}
{-# LANGUAGE ConstraintKinds           #-}
{-# LANGUAGE DataKinds                 #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE KindSignatures            #-}
{-# LANGUAGE PartialTypeSignatures     #-}
{-# LANGUAGE PolyKinds                 #-}
{-# LANGUAGE RankNTypes                #-}
{-# LANGUAGE ScopedTypeVariables       #-}
{-# LANGUAGE TypeApplications          #-}
{-# LANGUAGE TypeFamilies              #-}
{-# LANGUAGE TypeOperators             #-}

module KindLinter where

import           Data.HList
import           Data.Kind       (Type)
import           Data.Map.Strict
import           Data.Void       (Void)
import           GHC.TypeLits    (KnownSymbol, Symbol, symbolVal)


func :: a -> HList [Int, String]
func _ = hBuild 10 "test"

field :: forall a. KnownSymbol a => Label a
field = Label

data Linter a = Some a | None

type LintSingleton b a = Tagged b a

-- newtype LintSet a :: Record '[LintSingleton Int]
-- newtype LintSet (a :: Type -> Record '[Type]) = Record (a Void)

type SomeList (a :: Type) = Record '[Tagged "test" a]

type family MkList (b :: [Symbol]) a where
  MkList '[] _ = '[]
  MkList (x:xs) a = Tagged x a : MkList xs a

type Lints labels a = Record (MkList labels a)

type KnownProperties = '["hello", "test"]

record :: Lints KnownProperties Int
record =
  Label @"hello" .=. 20 .*.
  Label @"test" .=. 10 .*.
  -- field @"x" .=. 20 .*.
  emptyRecord


class KnownList a where
  listVal :: Proxy a -> [String]

instance KnownList '[] where
  listVal _ = []

instance (KnownList xs, KnownSymbol x) => KnownList (x:xs) where
  listVal _ = symbolVal (Proxy @x) : listVal (Proxy @xs)


lints :: [String]
lints = listVal (Proxy @KnownProperties)

-- TODO: how to pattern match on that?
doSth :: forall a b ctxt. (KnownList a, b ~ MkList a (Linter ctxt)) => Proxy b -> String -> Linter ctxt
doSth _ name = None -- want to get a different result for each value of name in a
  -- is there a better way than using listVal / something related to it?

-- TODO: these should be limited to Tagged "symbol" (LintWriter a)
tileLints =
  field @"test" .=. (\a -> a) .*.
  emptyRecord