Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data PropertyType
- type family ToHsType (t :: PropertyType) where ...
- type family NotElem (s :: Symbol) (r :: [PropertyKey]) :: Constraint where ...
- data MetaData (t :: PropertyType) where
- MetaData :: (IsTEnum t ~ 'False, IsProperties t ~ 'False) => {..} -> MetaData t
- EnumMetaData :: IsTEnum t ~ 'True => {..} -> MetaData t
- PropertiesMetaData :: t ~ TProperties rs => {..} -> MetaData t
- data PropertyKey = PropertyKey Symbol PropertyType
- data SPropertyKey (k :: PropertyKey) where
- SNumber :: SPropertyKey ('PropertyKey s 'TNumber)
- SInteger :: SPropertyKey ('PropertyKey s 'TInteger)
- SString :: SPropertyKey ('PropertyKey s 'TString)
- SBoolean :: SPropertyKey ('PropertyKey s 'TBoolean)
- SObject :: (ToJSON a, FromJSON a) => Proxy a -> SPropertyKey ('PropertyKey s ('TObject a))
- SArray :: (ToJSON a, FromJSON a) => Proxy a -> SPropertyKey ('PropertyKey s ('TArray a))
- SEnum :: (ToJSON a, FromJSON a, Eq a, Show a) => Proxy a -> SPropertyKey ('PropertyKey s ('TEnum a))
- SProperties :: SPropertyKey ('PropertyKey s ('TProperties pp))
- data KeyNameProxy (s :: Symbol) = KnownSymbol s => KeyNameProxy
- data KeyNamePath (r :: NonEmptyList Symbol) where
- SingleKey :: KeyNameProxy s -> KeyNamePath (NE s)
- ConsKeysPath :: KeyNameProxy s1 -> KeyNamePath ss -> KeyNamePath (s1 :| ss)
- data Properties (r :: [PropertyKey])
- type HasProperty s k t r = (k ~ 'PropertyKey s t, Elem s r, FindByKeyPath (NE s) r ~ t, FindByKeyName s r ~ t, KnownSymbol s, FindPropertyMeta s r t)
- type HasPropertyByPath props path t = (t ~ FindByKeyPath path props, ParsePropertyPath props path)
- emptyProperties :: Properties '[]
- defineNumberProperty :: (KnownSymbol s, NotElem s r) => KeyNameProxy s -> Text -> Double -> Properties r -> Properties ('PropertyKey s 'TNumber : r)
- defineIntegerProperty :: (KnownSymbol s, NotElem s r) => KeyNameProxy s -> Text -> Int -> Properties r -> Properties ('PropertyKey s 'TInteger : r)
- defineStringProperty :: (KnownSymbol s, NotElem s r) => KeyNameProxy s -> Text -> Text -> Properties r -> Properties ('PropertyKey s 'TString : r)
- defineBooleanProperty :: (KnownSymbol s, NotElem s r) => KeyNameProxy s -> Text -> Bool -> Properties r -> Properties ('PropertyKey s 'TBoolean : r)
- defineObjectProperty :: (KnownSymbol s, NotElem s r, ToJSON a, FromJSON a) => KeyNameProxy s -> Text -> a -> Properties r -> Properties ('PropertyKey s ('TObject a) : r)
- defineArrayProperty :: (KnownSymbol s, NotElem s r, ToJSON a, FromJSON a) => KeyNameProxy s -> Text -> [a] -> Properties r -> Properties ('PropertyKey s ('TArray a) : r)
- defineEnumProperty :: (KnownSymbol s, NotElem s r, ToJSON a, FromJSON a, Eq a, Show a) => KeyNameProxy s -> Text -> [(a, Text)] -> a -> Properties r -> Properties ('PropertyKey s ('TEnum a) : r)
- definePropertiesProperty :: (KnownSymbol s, NotElem s r) => KeyNameProxy s -> Text -> Properties childrenProps -> Properties r -> Properties ('PropertyKey s ('TProperties childrenProps) : r)
- toDefaultJSON :: Properties r -> [Pair]
- toVSCodeExtensionSchema :: Text -> Properties r -> [Pair]
- usePropertyEither :: HasProperty s k t r => KeyNameProxy s -> Properties r -> Object -> Either String (ToHsType t)
- useProperty :: HasProperty s k t r => KeyNameProxy s -> Properties r -> Object -> ToHsType t
- usePropertyByPathEither :: ParsePropertyPath rs r => KeyNamePath r -> Properties rs -> Object -> Either String (ToHsType (FindByKeyPath r rs))
- usePropertyByPath :: ParsePropertyPath rs r => KeyNamePath r -> Properties rs -> Object -> ToHsType (FindByKeyPath r rs)
- (&) :: a -> (a -> b) -> b
Documentation
data PropertyType Source #
Types properties may have
type family ToHsType (t :: PropertyType) where ... Source #
type family NotElem (s :: Symbol) (r :: [PropertyKey]) :: Constraint where ... Source #
data MetaData (t :: PropertyType) where Source #
Metadata of a property
MetaData | |
| |
EnumMetaData | |
| |
PropertiesMetaData | |
|
data PropertyKey Source #
Used at type level for name-type mapping in Properties
data SPropertyKey (k :: PropertyKey) where Source #
Singleton type of PropertyKey
SNumber :: SPropertyKey ('PropertyKey s 'TNumber) | |
SInteger :: SPropertyKey ('PropertyKey s 'TInteger) | |
SString :: SPropertyKey ('PropertyKey s 'TString) | |
SBoolean :: SPropertyKey ('PropertyKey s 'TBoolean) | |
SObject :: (ToJSON a, FromJSON a) => Proxy a -> SPropertyKey ('PropertyKey s ('TObject a)) | |
SArray :: (ToJSON a, FromJSON a) => Proxy a -> SPropertyKey ('PropertyKey s ('TArray a)) | |
SEnum :: (ToJSON a, FromJSON a, Eq a, Show a) => Proxy a -> SPropertyKey ('PropertyKey s ('TEnum a)) | |
SProperties :: SPropertyKey ('PropertyKey s ('TProperties pp)) |
data KeyNameProxy (s :: Symbol) Source #
A proxy type in order to allow overloaded labels as properties' names at the call site
KnownSymbol s => KeyNameProxy |
Instances
(KnownSymbol s', s ~ s') => IsLabel s (KeyNameProxy s') Source # | |
Defined in Ide.Plugin.Properties fromLabel :: KeyNameProxy s' # |
data KeyNamePath (r :: NonEmptyList Symbol) where Source #
a path to a property in a json object
SingleKey :: KeyNameProxy s -> KeyNamePath (NE s) | |
ConsKeysPath :: KeyNameProxy s1 -> KeyNamePath ss -> KeyNamePath (s1 :| ss) |
data Properties (r :: [PropertyKey]) Source #
Properties
is a partial implementation of json schema, without supporting union types and validation.
In hls, it defines a set of properties used in dedicated configuration of a plugin.
A property is an immediate child of the json object in each plugin's "config" section.
It was designed to be compatible with vscode's settings UI.
Use emptyProperties
and useProperty
to create and consume Properties
.
type HasProperty s k t r = (k ~ 'PropertyKey s t, Elem s r, FindByKeyPath (NE s) r ~ t, FindByKeyName s r ~ t, KnownSymbol s, FindPropertyMeta s r t) Source #
In row r
, there is a PropertyKey
k
, which has name s
and carries haskell type t
type HasPropertyByPath props path t = (t ~ FindByKeyPath path props, ParsePropertyPath props path) Source #
emptyProperties :: Properties '[] Source #
Creates a Properties
that defines no property
Useful to start a definitions chain, for example:
properties =
emptyProperties
& defineStringProperty
#exampleString
"Description of exampleString"
Foo
& defineNumberProperty
#exampleNumber
"Description of exampleNumber"
233
:: (KnownSymbol s, NotElem s r) | |
=> KeyNameProxy s | |
-> Text | description |
-> Double | default value |
-> Properties r | |
-> Properties ('PropertyKey s 'TNumber : r) |
Defines a number property
defineIntegerProperty Source #
:: (KnownSymbol s, NotElem s r) | |
=> KeyNameProxy s | |
-> Text | description |
-> Int | default value |
-> Properties r | |
-> Properties ('PropertyKey s 'TInteger : r) |
Defines an integer property
:: (KnownSymbol s, NotElem s r) | |
=> KeyNameProxy s | |
-> Text | description |
-> Text | default value |
-> Properties r | |
-> Properties ('PropertyKey s 'TString : r) |
Defines a string property
defineBooleanProperty Source #
:: (KnownSymbol s, NotElem s r) | |
=> KeyNameProxy s | |
-> Text | description |
-> Bool | default value |
-> Properties r | |
-> Properties ('PropertyKey s 'TBoolean : r) |
Defines a boolean property
:: (KnownSymbol s, NotElem s r, ToJSON a, FromJSON a) | |
=> KeyNameProxy s | |
-> Text | description |
-> a | default value |
-> Properties r | |
-> Properties ('PropertyKey s ('TObject a) : r) |
Defines an object property
:: (KnownSymbol s, NotElem s r, ToJSON a, FromJSON a) | |
=> KeyNameProxy s | |
-> Text | description |
-> [a] | default value |
-> Properties r | |
-> Properties ('PropertyKey s ('TArray a) : r) |
Defines an array property
:: (KnownSymbol s, NotElem s r, ToJSON a, FromJSON a, Eq a, Show a) | |
=> KeyNameProxy s | |
-> Text | description |
-> [(a, Text)] | valid enum members with each of description |
-> a | |
-> Properties r | |
-> Properties ('PropertyKey s ('TEnum a) : r) |
Defines an enum property
definePropertiesProperty :: (KnownSymbol s, NotElem s r) => KeyNameProxy s -> Text -> Properties childrenProps -> Properties r -> Properties ('PropertyKey s ('TProperties childrenProps) : r) Source #
toDefaultJSON :: Properties r -> [Pair] Source #
Converts a properties definition into kv pairs with default values from MetaData
toVSCodeExtensionSchema :: Text -> Properties r -> [Pair] Source #
Converts a properties definition into kv pairs as vscode schema
usePropertyEither :: HasProperty s k t r => KeyNameProxy s -> Properties r -> Object -> Either String (ToHsType t) Source #
Given the name of a defined property, generates a JSON parser of plcConfig
useProperty :: HasProperty s k t r => KeyNameProxy s -> Properties r -> Object -> ToHsType t Source #
Like usePropertyEither
but returns defaultValue
on parse error
usePropertyByPathEither :: ParsePropertyPath rs r => KeyNamePath r -> Properties rs -> Object -> Either String (ToHsType (FindByKeyPath r rs)) Source #
usePropertyByPath :: ParsePropertyPath rs r => KeyNamePath r -> Properties rs -> Object -> ToHsType (FindByKeyPath r rs) Source #