diff options
| author | stuebinm | 2022-03-30 18:21:16 +0200 | 
|---|---|---|
| committer | stuebinm | 2022-03-30 18:21:16 +0200 | 
| commit | 0965e840d2e26378ef64392ed69e4c6109c31009 (patch) | |
| tree | 14ef9c25786bf400572f9ae2a5383bd85701249a /lib | |
| parent | c4b4eb91492db2950d7d6c08edab9b26fb8bf334 (diff) | |
remove unused module
Diffstat (limited to 'lib')
| -rw-r--r-- | lib/KindLinter.hs | 74 | 
1 files changed, 0 insertions, 74 deletions
| diff --git a/lib/KindLinter.hs b/lib/KindLinter.hs deleted file mode 100644 index a876a8f..0000000 --- a/lib/KindLinter.hs +++ /dev/null @@ -1,74 +0,0 @@ -{-# 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           Universum - -import           Data.HList -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 | 
