Skip to content
Snippets Groups Projects
Commit 0965e840 authored by stuebinm's avatar stuebinm
Browse files

remove unused module

parent c4b4eb91
No related branches found
No related tags found
No related merge requests found
{-# 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
...@@ -42,7 +42,6 @@ library: ...@@ -42,7 +42,6 @@ library:
- text-metrics - text-metrics
- uri-encode - uri-encode
- network-uri - network-uri
- HList
exposed-modules: exposed-modules:
- CheckDir - CheckDir
- CheckMap - CheckMap
......
...@@ -23,7 +23,6 @@ library ...@@ -23,7 +23,6 @@ library
other-modules: other-modules:
Badges Badges
Dirgraph Dirgraph
KindLinter
LayerData LayerData
LintWriter LintWriter
Paths Paths
...@@ -36,8 +35,7 @@ library ...@@ -36,8 +35,7 @@ library
NoImplicitPrelude NoImplicitPrelude
ghc-options: -Wall -Wno-name-shadowing -Wno-unticked-promoted-constructors ghc-options: -Wall -Wno-name-shadowing -Wno-unticked-promoted-constructors
build-depends: build-depends:
HList aeson
, aeson
, base , base
, bytestring , bytestring
, containers , containers
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment