{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-warn-dodgy-exports -fno-warn-duplicate-exports #-}
module Autodocodec.Nix.Options
(
renderNixOptionTypeViaCodec,
renderNixOptionsViaCodec,
renderNixOptionTypeVia,
renderNixOptionsVia,
valueCodecNixOptionType,
objectCodecNixOptions,
Option (..),
emptyOption,
simplifyOption,
OptionType (..),
simplifyOptionType,
renderOption,
renderOptionType,
withNixArgs,
optionExpression,
optionExpr,
optionsExpression,
optionsExpr,
optionTypeExpression,
optionTypeExpr,
renderExpression,
)
where
import Autodocodec
import Autodocodec.Nix.Expression
import Autodocodec.Nix.Render
import Control.Applicative
import Data.Aeson as JSON
import Data.Containers.ListUtils
import qualified Data.HashMap.Strict as HM
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as T
renderNixOptionTypeViaCodec :: forall a. (HasCodec a) => Text
renderNixOptionTypeViaCodec :: forall a. HasCodec a => Text
renderNixOptionTypeViaCodec = ValueCodec a a -> Text
forall input output. ValueCodec input output -> Text
renderNixOptionTypeVia (forall value. HasCodec value => JSONCodec value
codec @a)
renderNixOptionsViaCodec :: forall a. (HasObjectCodec a) => Text
renderNixOptionsViaCodec :: forall a. HasObjectCodec a => Text
renderNixOptionsViaCodec = ObjectCodec a a -> Text
forall input output. ObjectCodec input output -> Text
renderNixOptionsVia (forall object. HasObjectCodec object => JSONObjectCodec object
objectCodec @a)
renderNixOptionTypeVia :: ValueCodec input output -> Text
renderNixOptionTypeVia :: forall input output. ValueCodec input output -> Text
renderNixOptionTypeVia =
OptionType -> Text
renderOptionType
(OptionType -> Text)
-> (ValueCodec input output -> OptionType)
-> ValueCodec input output
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionType -> Maybe OptionType -> OptionType
forall a. a -> Maybe a -> a
fromMaybe (Text -> OptionType
OptionTypeSimple Text
"lib.types.anything")
(Maybe OptionType -> OptionType)
-> (ValueCodec input output -> Maybe OptionType)
-> ValueCodec input output
-> OptionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueCodec input output -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
valueCodecNixOptionType
renderNixOptionsVia :: ObjectCodec input output -> Text
renderNixOptionsVia :: forall input output. ObjectCodec input output -> Text
renderNixOptionsVia =
Map Text Option -> Text
renderOptions
(Map Text Option -> Text)
-> (ObjectCodec input output -> Map Text Option)
-> ObjectCodec input output
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectCodec input output -> Map Text Option
forall input output. ObjectCodec input output -> Map Text Option
objectCodecNixOptions
valueCodecNixOptionType :: ValueCodec input output -> Maybe OptionType
valueCodecNixOptionType :: forall input output. ValueCodec input output -> Maybe OptionType
valueCodecNixOptionType = (OptionType -> OptionType) -> Maybe OptionType -> Maybe OptionType
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OptionType -> OptionType
simplifyOptionType (Maybe OptionType -> Maybe OptionType)
-> (ValueCodec input output -> Maybe OptionType)
-> ValueCodec input output
-> Maybe OptionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueCodec input output -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go
where
mTyp :: Maybe OptionType -> OptionType
mTyp = OptionType -> Maybe OptionType -> OptionType
forall a. a -> Maybe a -> a
fromMaybe (OptionType -> Maybe OptionType -> OptionType)
-> OptionType -> Maybe OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ Text -> OptionType
OptionTypeSimple Text
"lib.types.anything"
go :: ValueCodec input output -> Maybe OptionType
go :: forall input output. ValueCodec input output -> Maybe OptionType
go = \case
ValueCodec input output
NullCodec -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just OptionType
OptionTypeNull
BoolCodec Maybe Text
_ -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ Text -> OptionType
OptionTypeSimple Text
"lib.types.bool"
StringCodec Maybe Text
_ -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ Text -> OptionType
OptionTypeSimple Text
"lib.types.str"
IntegerCodec Maybe Text
_ Bounds Integer
bounds -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$
Text -> OptionType
OptionTypeSimple (Text -> OptionType) -> Text -> OptionType
forall a b. (a -> b) -> a -> b
$
case Bounds Integer -> IntegerBoundsSymbolic
guessIntegerBoundsSymbolic Bounds Integer
bounds of
BitUInt Word8
w -> case Word8
w of
Word8
64 -> Text
"lib.types.ints.unsigned"
Word8
32 -> Text
"lib.types.ints.u32"
Word8
16 -> Text
"lib.types.ints.u16"
Word8
8 -> Text
"lib.types.ints.u8"
Word8
_ -> Text
"lib.types.int"
BitSInt Word8
w -> case Word8
w of
Word8
64 -> Text
"lib.types.int"
Word8
32 -> Text
"lib.types.ints.s32"
Word8
16 -> Text
"lib.types.ints.s16"
Word8
8 -> Text
"lib.types.ints.s8"
Word8
_ -> Text
"lib.types.int"
OtherIntegerBounds Maybe IntegerSymbolic
_ Maybe IntegerSymbolic
_ -> Text
"lib.types.int"
NumberCodec Maybe Text
_ Bounds Scientific
_ -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ Text -> OptionType
OptionTypeSimple Text
"lib.types.number"
HashMapCodec JSONCodec v
c -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
OptionTypeAttrsOf (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ Maybe OptionType -> OptionType
mTyp (Maybe OptionType -> OptionType) -> Maybe OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ JSONCodec v -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go JSONCodec v
c
MapCodec JSONCodec v
c -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
OptionTypeAttrsOf (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ Maybe OptionType -> OptionType
mTyp (Maybe OptionType -> OptionType) -> Maybe OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ JSONCodec v -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go JSONCodec v
c
ValueCodec input output
ValueCodec -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (Text -> OptionType
OptionTypeSimple Text
"lib.types.unspecified")
ArrayOfCodec Maybe Text
_ ValueCodec input1 output1
c -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
OptionTypeListOf (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ Maybe OptionType -> OptionType
mTyp (Maybe OptionType -> OptionType) -> Maybe OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ ValueCodec input1 output1 -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go ValueCodec input1 output1
c
ObjectOfCodec Maybe Text
_ ObjectCodec input output
oc -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (Map Text Option -> OptionType
OptionTypeSubmodule (ObjectCodec input output -> Map Text Option
forall input output. ObjectCodec input output -> Map Text Option
objectCodecNixOptions ObjectCodec input output
oc))
EqCodec value
v JSONCodec value
c -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ [Expression] -> OptionType
OptionTypeEnum [JSONCodec value -> value -> Expression
forall a void. ValueCodec a void -> a -> Expression
toNixExpressionVia JSONCodec value
c value
v]
BimapCodec oldOutput -> Either String output
_ input -> oldInput
_ Codec Value oldInput oldOutput
c -> Codec Value oldInput oldOutput -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go Codec Value oldInput oldOutput
c
EitherCodec Union
_ Codec Value input1 output1
c1 Codec Value input2 output2
c2 -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ [OptionType] -> OptionType
OptionTypeOneOf ((Maybe OptionType -> OptionType)
-> [Maybe OptionType] -> [OptionType]
forall a b. (a -> b) -> [a] -> [b]
map Maybe OptionType -> OptionType
mTyp [Codec Value input1 output1 -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go Codec Value input1 output1
c1, Codec Value input2 output2 -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go Codec Value input2 output2
c2])
CommentCodec Text
_ ValueCodec input output
c -> ValueCodec input output -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
go ValueCodec input output
c
ReferenceCodec {} -> Maybe OptionType
forall a. Maybe a
Nothing
objectCodecNixOptions :: ObjectCodec input output -> Map Text Option
objectCodecNixOptions :: forall input output. ObjectCodec input output -> Map Text Option
objectCodecNixOptions = Map Text Option -> Map Text Option
simplifyOptions (Map Text Option -> Map Text Option)
-> (ObjectCodec input output -> Map Text Option)
-> ObjectCodec input output
-> Map Text Option
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ObjectCodec input output -> Map Text Option
forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
False
where
go :: Bool -> ObjectCodec input output -> Map Text Option
go :: forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
b = \case
DiscriminatedUnionCodec Text
k input -> (Text, ObjectCodec input ())
_ HashMap Text (Text, ObjectCodec Void output)
m ->
Text -> Option -> Map Text Option -> Map Text Option
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert
Text
k
( Option
{ optionType :: Maybe OptionType
optionType = OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ [OptionType] -> OptionType
OptionTypeOneOf ([OptionType] -> OptionType) -> [OptionType] -> OptionType
forall a b. (a -> b) -> a -> b
$ (Text -> OptionType) -> [Text] -> [OptionType]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> OptionType
OptionTypeSimple (Text -> OptionType) -> (Text -> Text) -> Text -> OptionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
forall a. Show a => a -> String
show) ([Text] -> [OptionType]) -> [Text] -> [OptionType]
forall a b. (a -> b) -> a -> b
$ HashMap Text (Text, ObjectCodec Void output) -> [Text]
forall k v. HashMap k v -> [k]
HM.keys HashMap Text (Text, ObjectCodec Void output)
m,
optionDescription :: Maybe Text
optionDescription = Maybe Text
forall a. Maybe a
Nothing,
optionDefault :: Maybe Value
optionDefault = Maybe Value
forall a. Maybe a
Nothing
}
)
(Map Text Option -> Map Text Option)
-> Map Text Option -> Map Text Option
forall a b. (a -> b) -> a -> b
$ (Option -> Option -> Option)
-> [Map Text Option] -> Map Text Option
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
M.unionsWith
( \Option
t1 Option
t2 ->
Option
{ optionType :: Maybe OptionType
optionType = OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just (OptionType -> Maybe OptionType) -> OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ [OptionType] -> OptionType
OptionTypeOneOf ([OptionType] -> OptionType) -> [OptionType] -> OptionType
forall a b. (a -> b) -> a -> b
$ (Option -> OptionType) -> [Option] -> [OptionType]
forall a b. (a -> b) -> [a] -> [b]
map (OptionType -> Maybe OptionType -> OptionType
forall a. a -> Maybe a -> a
fromMaybe (Text -> OptionType
OptionTypeSimple Text
"lib.types.anything") (Maybe OptionType -> OptionType)
-> (Option -> Maybe OptionType) -> Option -> OptionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Option -> Maybe OptionType
optionType) [Option
t1, Option
t2],
optionDescription :: Maybe Text
optionDescription = Option -> Maybe Text
optionDescription Option
t1 Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Option -> Maybe Text
optionDescription Option
t2,
optionDefault :: Maybe Value
optionDefault = Maybe Value
forall a. Maybe a
Nothing
}
)
([Map Text Option] -> Map Text Option)
-> [Map Text Option] -> Map Text Option
forall a b. (a -> b) -> a -> b
$ ((Text, ObjectCodec Void output) -> Map Text Option)
-> [(Text, ObjectCodec Void output)] -> [Map Text Option]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> ObjectCodec Void output -> Map Text Option
forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
b (ObjectCodec Void output -> Map Text Option)
-> ((Text, ObjectCodec Void output) -> ObjectCodec Void output)
-> (Text, ObjectCodec Void output)
-> Map Text Option
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, ObjectCodec Void output) -> ObjectCodec Void output
forall a b. (a, b) -> b
snd)
([(Text, ObjectCodec Void output)] -> [Map Text Option])
-> [(Text, ObjectCodec Void output)] -> [Map Text Option]
forall a b. (a -> b) -> a -> b
$ HashMap Text (Text, ObjectCodec Void output)
-> [(Text, ObjectCodec Void output)]
forall k v. HashMap k v -> [v]
HM.elems HashMap Text (Text, ObjectCodec Void output)
m
RequiredKeyCodec Text
key ValueCodec input output
o Maybe Text
mDesc ->
Text -> Option -> Map Text Option
forall k a. k -> a -> Map k a
M.singleton Text
key (Option -> Map Text Option) -> Option -> Map Text Option
forall a b. (a -> b) -> a -> b
$
Option
{ optionType :: Maybe OptionType
optionType =
( if Bool
b
then (OptionType -> OptionType) -> Maybe OptionType -> Maybe OptionType
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OptionType -> OptionType
OptionTypeNullOr
else Maybe OptionType -> Maybe OptionType
forall a. a -> a
id
)
(Maybe OptionType -> Maybe OptionType)
-> Maybe OptionType -> Maybe OptionType
forall a b. (a -> b) -> a -> b
$ ValueCodec input output -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
valueCodecNixOptionType ValueCodec input output
o,
optionDescription :: Maybe Text
optionDescription = Maybe Text
mDesc,
optionDefault :: Maybe Value
optionDefault =
if Bool
b
then Value -> Maybe Value
forall a. a -> Maybe a
Just Value
JSON.Null
else Maybe Value
forall a. Maybe a
Nothing
}
OptionalKeyCodec Text
key ValueCodec input1 output1
o Maybe Text
mDesc ->
Text -> Option -> Map Text Option
forall k a. k -> a -> Map k a
M.singleton Text
key (Option -> Map Text Option) -> Option -> Map Text Option
forall a b. (a -> b) -> a -> b
$
Option
{ optionType :: Maybe OptionType
optionType = OptionType -> OptionType
OptionTypeNullOr (OptionType -> OptionType) -> Maybe OptionType -> Maybe OptionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ValueCodec input1 output1 -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
valueCodecNixOptionType ValueCodec input1 output1
o,
optionDescription :: Maybe Text
optionDescription = Maybe Text
mDesc,
optionDefault :: Maybe Value
optionDefault = Value -> Maybe Value
forall a. a -> Maybe a
Just Value
JSON.Null
}
OptionalKeyWithDefaultCodec Text
key ValueCodec input input
c input
defaultValue Maybe Text
mDesc ->
Text -> Option -> Map Text Option
forall k a. k -> a -> Map k a
M.singleton
Text
key
Option
{ optionType :: Maybe OptionType
optionType = ValueCodec input input -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
valueCodecNixOptionType ValueCodec input input
c,
optionDescription :: Maybe Text
optionDescription = Maybe Text
mDesc,
optionDefault :: Maybe Value
optionDefault = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ ValueCodec input input -> input -> Value
forall a void. ValueCodec a void -> a -> Value
toJSONVia ValueCodec input input
c input
defaultValue
}
OptionalKeyWithOmittedDefaultCodec Text
key ValueCodec value value
c value
defaultValue Maybe Text
mDesc ->
Text -> Option -> Map Text Option
forall k a. k -> a -> Map k a
M.singleton
Text
key
Option
{ optionType :: Maybe OptionType
optionType = ValueCodec value value -> Maybe OptionType
forall input output. ValueCodec input output -> Maybe OptionType
valueCodecNixOptionType ValueCodec value value
c,
optionDescription :: Maybe Text
optionDescription = Maybe Text
mDesc,
optionDefault :: Maybe Value
optionDefault = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ ValueCodec value value -> value -> Value
forall a void. ValueCodec a void -> a -> Value
toJSONVia ValueCodec value value
c value
defaultValue
}
PureCodec output
_ -> Map Text Option
forall k a. Map k a
M.empty
ApCodec ObjectCodec input (output1 -> output)
c1 ObjectCodec input output1
c2 -> (Option -> Option -> Option)
-> Map Text Option -> Map Text Option -> Map Text Option
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
M.unionWith Option -> Option -> Option
mergeOption (Bool -> ObjectCodec input (output1 -> output) -> Map Text Option
forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
b ObjectCodec input (output1 -> output)
c1) (Bool -> ObjectCodec input output1 -> Map Text Option
forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
b ObjectCodec input output1
c2)
BimapCodec oldOutput -> Either String output
_ input -> oldInput
_ Codec Object oldInput oldOutput
c -> Bool -> Codec Object oldInput oldOutput -> Map Text Option
forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
b Codec Object oldInput oldOutput
c
EitherCodec Union
_ Codec Object input1 output1
c1 Codec Object input2 output2
c2 -> (Option -> Option -> Option)
-> Map Text Option -> Map Text Option -> Map Text Option
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
M.unionWith Option -> Option -> Option
mergeOption (Bool -> Codec Object input1 output1 -> Map Text Option
forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
True Codec Object input1 output1
c1) (Bool -> Codec Object input2 output2 -> Map Text Option
forall input output.
Bool -> ObjectCodec input output -> Map Text Option
go Bool
True Codec Object input2 output2
c2)
mergeOption :: Option -> Option -> Option
mergeOption :: Option -> Option -> Option
mergeOption Option
o1 Option
o2 =
Option
o1
{ optionType =
( \OptionType
ot1 OptionType
ot2 ->
OptionType -> OptionType
simplifyOptionType (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$
[OptionType] -> OptionType
OptionTypeOneOf
[ OptionType
ot1,
OptionType
ot2
]
)
<$> optionType o1
<*> optionType o2
}
data Option = Option
{ Option -> Maybe OptionType
optionType :: !(Maybe OptionType),
Option -> Maybe Text
optionDescription :: !(Maybe Text),
Option -> Maybe Value
optionDefault :: !(Maybe JSON.Value)
}
deriving (Int -> Option -> ShowS
[Option] -> ShowS
Option -> String
(Int -> Option -> ShowS)
-> (Option -> String) -> ([Option] -> ShowS) -> Show Option
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Option -> ShowS
showsPrec :: Int -> Option -> ShowS
$cshow :: Option -> String
show :: Option -> String
$cshowList :: [Option] -> ShowS
showList :: [Option] -> ShowS
Show, Option -> Option -> Bool
(Option -> Option -> Bool)
-> (Option -> Option -> Bool) -> Eq Option
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Option -> Option -> Bool
== :: Option -> Option -> Bool
$c/= :: Option -> Option -> Bool
/= :: Option -> Option -> Bool
Eq, Eq Option
Eq Option =>
(Option -> Option -> Ordering)
-> (Option -> Option -> Bool)
-> (Option -> Option -> Bool)
-> (Option -> Option -> Bool)
-> (Option -> Option -> Bool)
-> (Option -> Option -> Option)
-> (Option -> Option -> Option)
-> Ord Option
Option -> Option -> Bool
Option -> Option -> Ordering
Option -> Option -> Option
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Option -> Option -> Ordering
compare :: Option -> Option -> Ordering
$c< :: Option -> Option -> Bool
< :: Option -> Option -> Bool
$c<= :: Option -> Option -> Bool
<= :: Option -> Option -> Bool
$c> :: Option -> Option -> Bool
> :: Option -> Option -> Bool
$c>= :: Option -> Option -> Bool
>= :: Option -> Option -> Bool
$cmax :: Option -> Option -> Option
max :: Option -> Option -> Option
$cmin :: Option -> Option -> Option
min :: Option -> Option -> Option
Ord)
emptyOption :: Option
emptyOption :: Option
emptyOption =
Option
{ optionType :: Maybe OptionType
optionType = Maybe OptionType
forall a. Maybe a
Nothing,
optionDescription :: Maybe Text
optionDescription = Maybe Text
forall a. Maybe a
Nothing,
optionDefault :: Maybe Value
optionDefault = Maybe Value
forall a. Maybe a
Nothing
}
simplifyOption :: Option -> Option
simplifyOption :: Option -> Option
simplifyOption Option
o = Option
o {optionType = simplifyOptionType <$> optionType o}
data OptionType
= OptionTypeNull
| OptionTypeSimple !Text
| OptionTypeEnum ![Expression]
| OptionTypeNullOr !OptionType
| OptionTypeListOf !OptionType
| OptionTypeAttrsOf !OptionType
| OptionTypeOneOf ![OptionType]
| OptionTypeSubmodule !(Map Text Option)
deriving (Int -> OptionType -> ShowS
[OptionType] -> ShowS
OptionType -> String
(Int -> OptionType -> ShowS)
-> (OptionType -> String)
-> ([OptionType] -> ShowS)
-> Show OptionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OptionType -> ShowS
showsPrec :: Int -> OptionType -> ShowS
$cshow :: OptionType -> String
show :: OptionType -> String
$cshowList :: [OptionType] -> ShowS
showList :: [OptionType] -> ShowS
Show, OptionType -> OptionType -> Bool
(OptionType -> OptionType -> Bool)
-> (OptionType -> OptionType -> Bool) -> Eq OptionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OptionType -> OptionType -> Bool
== :: OptionType -> OptionType -> Bool
$c/= :: OptionType -> OptionType -> Bool
/= :: OptionType -> OptionType -> Bool
Eq, Eq OptionType
Eq OptionType =>
(OptionType -> OptionType -> Ordering)
-> (OptionType -> OptionType -> Bool)
-> (OptionType -> OptionType -> Bool)
-> (OptionType -> OptionType -> Bool)
-> (OptionType -> OptionType -> Bool)
-> (OptionType -> OptionType -> OptionType)
-> (OptionType -> OptionType -> OptionType)
-> Ord OptionType
OptionType -> OptionType -> Bool
OptionType -> OptionType -> Ordering
OptionType -> OptionType -> OptionType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OptionType -> OptionType -> Ordering
compare :: OptionType -> OptionType -> Ordering
$c< :: OptionType -> OptionType -> Bool
< :: OptionType -> OptionType -> Bool
$c<= :: OptionType -> OptionType -> Bool
<= :: OptionType -> OptionType -> Bool
$c> :: OptionType -> OptionType -> Bool
> :: OptionType -> OptionType -> Bool
$c>= :: OptionType -> OptionType -> Bool
>= :: OptionType -> OptionType -> Bool
$cmax :: OptionType -> OptionType -> OptionType
max :: OptionType -> OptionType -> OptionType
$cmin :: OptionType -> OptionType -> OptionType
min :: OptionType -> OptionType -> OptionType
Ord)
simplifyOptionType :: OptionType -> OptionType
simplifyOptionType :: OptionType -> OptionType
simplifyOptionType = OptionType -> OptionType
go
where
go :: OptionType -> OptionType
go = \case
OptionType
OptionTypeNull -> OptionType
OptionTypeNull
OptionTypeSimple Text
t -> Text -> OptionType
OptionTypeSimple Text
t
OptionTypeEnum [Expression]
es -> [Expression] -> OptionType
OptionTypeEnum [Expression]
es
OptionTypeNullOr OptionType
t -> case OptionType
t of
OptionType
OptionTypeNull -> OptionType
OptionTypeNull
OptionTypeNullOr OptionType
t' -> OptionType -> OptionType
go (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
OptionTypeNullOr OptionType
t'
OptionTypeOneOf [OptionType]
os -> OptionType -> OptionType
OptionTypeNullOr (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
go (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ [OptionType] -> OptionType
OptionTypeOneOf ([OptionType] -> OptionType) -> [OptionType] -> OptionType
forall a b. (a -> b) -> a -> b
$ (OptionType -> Bool) -> [OptionType] -> [OptionType]
forall a. (a -> Bool) -> [a] -> [a]
filter (OptionType -> OptionType -> Bool
forall a. Eq a => a -> a -> Bool
/= OptionType
OptionTypeNull) ([OptionType] -> [OptionType]) -> [OptionType] -> [OptionType]
forall a b. (a -> b) -> a -> b
$ (OptionType -> OptionType) -> [OptionType] -> [OptionType]
forall a b. (a -> b) -> [a] -> [b]
map OptionType -> OptionType
go [OptionType]
os
OptionType
_ -> OptionType -> OptionType
OptionTypeNullOr (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
go OptionType
t
OptionTypeListOf OptionType
o -> OptionType -> OptionType
OptionTypeListOf (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
go OptionType
o
OptionTypeAttrsOf OptionType
o -> OptionType -> OptionType
OptionTypeAttrsOf (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
go OptionType
o
OptionTypeOneOf [OptionType]
os -> case [OptionType] -> [OptionType]
goEnums ([OptionType] -> [OptionType]) -> [OptionType] -> [OptionType]
forall a b. (a -> b) -> a -> b
$ [OptionType] -> [OptionType]
forall a. Ord a => [a] -> [a]
nubOrd ([OptionType] -> [OptionType]) -> [OptionType] -> [OptionType]
forall a b. (a -> b) -> a -> b
$ (OptionType -> [OptionType]) -> [OptionType] -> [OptionType]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap OptionType -> [OptionType]
goOr [OptionType]
os of
[OptionType
ot] -> OptionType
ot
[OptionType]
os' ->
if (OptionType -> Bool) -> [OptionType] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any OptionType -> Bool
canBeNull [OptionType]
os'
then OptionType -> OptionType
go (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ OptionType -> OptionType
OptionTypeNullOr (OptionType -> OptionType) -> OptionType -> OptionType
forall a b. (a -> b) -> a -> b
$ case (OptionType -> Maybe OptionType) -> [OptionType] -> [OptionType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe OptionType -> Maybe OptionType
stripNull [OptionType]
os' of
[OptionType
t] -> OptionType
t
[OptionType]
ts' -> [OptionType] -> OptionType
OptionTypeOneOf [OptionType]
ts'
else [OptionType] -> OptionType
OptionTypeOneOf [OptionType]
os'
OptionTypeSubmodule Map Text Option
m -> Map Text Option -> OptionType
OptionTypeSubmodule (Map Text Option -> OptionType) -> Map Text Option -> OptionType
forall a b. (a -> b) -> a -> b
$ (Option -> Option) -> Map Text Option -> Map Text Option
forall a b k. (a -> b) -> Map k a -> Map k b
M.map Option -> Option
goOpt Map Text Option
m
canBeNull :: OptionType -> Bool
canBeNull :: OptionType -> Bool
canBeNull = \case
OptionType
OptionTypeNull -> Bool
True
OptionTypeNullOr OptionType
_ -> Bool
True
OptionType
_ -> Bool
False
stripNull :: OptionType -> Maybe OptionType
stripNull :: OptionType -> Maybe OptionType
stripNull = \case
OptionType
OptionTypeNull -> Maybe OptionType
forall a. Maybe a
Nothing
OptionTypeNullOr OptionType
t -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just OptionType
t
OptionType
t -> OptionType -> Maybe OptionType
forall a. a -> Maybe a
Just OptionType
t
goEnums :: [OptionType] -> [OptionType]
goEnums :: [OptionType] -> [OptionType]
goEnums = [Expression] -> [OptionType] -> [OptionType]
goEnum []
where
goEnum :: [Expression] -> [OptionType] -> [OptionType]
goEnum :: [Expression] -> [OptionType] -> [OptionType]
goEnum [Expression]
es = \case
[] -> case [Expression]
es of
[] -> []
[Expression]
_ -> [[Expression] -> OptionType
OptionTypeEnum [Expression]
es]
(OptionType
t : [OptionType]
rest) -> case OptionType
t of
OptionTypeEnum [Expression]
es' -> [Expression] -> [OptionType] -> [OptionType]
goEnum ([Expression]
es [Expression] -> [Expression] -> [Expression]
forall a. [a] -> [a] -> [a]
++ [Expression]
es') [OptionType]
rest
OptionType
_ -> OptionType
t OptionType -> [OptionType] -> [OptionType]
forall a. a -> [a] -> [a]
: [Expression] -> [OptionType] -> [OptionType]
goEnum [Expression]
es [OptionType]
rest
goOpt :: Option -> Option
goOpt Option
o = Option
o {optionType = go <$> optionType o}
goOr :: OptionType -> [OptionType]
goOr = \case
OptionTypeOneOf [OptionType]
os -> (OptionType -> [OptionType]) -> [OptionType] -> [OptionType]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap OptionType -> [OptionType]
goOr [OptionType]
os
OptionType
o -> [OptionType
o]
simplifyOptions :: Map Text Option -> Map Text Option
simplifyOptions :: Map Text Option -> Map Text Option
simplifyOptions = (Option -> Option) -> Map Text Option -> Map Text Option
forall a b k. (a -> b) -> Map k a -> Map k b
M.map Option -> Option
simplifyOption
renderOption :: Option -> Text
renderOption :: Option -> Text
renderOption = Expression -> Text
renderExpression (Expression -> Text) -> (Option -> Expression) -> Option -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> Expression
withNixArgs (Expression -> Expression)
-> (Option -> Expression) -> Option -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Option -> Expression
optionExpression
renderOptions :: Map Text Option -> Text
renderOptions :: Map Text Option -> Text
renderOptions = Expression -> Text
renderExpression (Expression -> Text)
-> (Map Text Option -> Expression) -> Map Text Option -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> Expression
withNixArgs (Expression -> Expression)
-> (Map Text Option -> Expression) -> Map Text Option -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Text Option -> Expression
optionsExpression
renderOptionType :: OptionType -> Text
renderOptionType :: OptionType -> Text
renderOptionType = Expression -> Text
renderExpression (Expression -> Text)
-> (OptionType -> Expression) -> OptionType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> Expression
withNixArgs (Expression -> Expression)
-> (OptionType -> Expression) -> OptionType -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionType -> Expression
optionTypeExpression
withNixArgs :: Expression -> Expression
withNixArgs :: Expression -> Expression
withNixArgs = [Text] -> Expression -> Expression
ExprFun [Text
"lib"]
optionExpr :: Option -> Expression
optionExpr :: Option -> Expression
optionExpr = Option -> Expression
optionExpression
optionExpression :: Option -> Expression
optionExpression :: Option -> Expression
optionExpression Option {Maybe Value
Maybe Text
Maybe OptionType
optionType :: Option -> Maybe OptionType
optionDescription :: Option -> Maybe Text
optionDefault :: Option -> Maybe Value
optionType :: Maybe OptionType
optionDescription :: Maybe Text
optionDefault :: Maybe Value
..} =
Expression -> Expression -> Expression
ExprAp
(Text -> Expression
ExprVar Text
"lib.mkOption")
( Map Text Expression -> Expression
ExprAttrSet (Map Text Expression -> Expression)
-> Map Text Expression -> Expression
forall a b. (a -> b) -> a -> b
$
[(Text, Expression)] -> Map Text Expression
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Text, Expression)] -> Map Text Expression)
-> [(Text, Expression)] -> Map Text Expression
forall a b. (a -> b) -> a -> b
$
[[(Text, Expression)]] -> [(Text, Expression)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [(Text
"type", OptionType -> Expression
optionTypeExpression OptionType
typ) | OptionType
typ <- Maybe OptionType -> [OptionType]
forall a. Maybe a -> [a]
maybeToList Maybe OptionType
optionType],
[(Text
"description", Text -> Expression
ExprLitString Text
d) | Text
d <- Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList Maybe Text
optionDescription],
case Maybe Value
optionDefault of
Maybe Value
Nothing -> case Maybe OptionType
optionType of
Just (OptionTypeSubmodule Map Text Option
_) -> [(Text
"default", Map Text Expression -> Expression
ExprAttrSet Map Text Expression
forall k a. Map k a
M.empty)]
Maybe OptionType
_ -> []
Just Value
d -> [(Text
"default", Value -> Expression
forall a. HasCodec a => a -> Expression
toNixExpressionViaCodec Value
d)]
]
)
optionsExpr :: Map Text Option -> Expression
optionsExpr :: Map Text Option -> Expression
optionsExpr = Map Text Option -> Expression
optionsExpression
optionsExpression :: Map Text Option -> Expression
optionsExpression :: Map Text Option -> Expression
optionsExpression = Map Text Expression -> Expression
ExprAttrSet (Map Text Expression -> Expression)
-> (Map Text Option -> Map Text Expression)
-> Map Text Option
-> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Option -> Expression) -> Map Text Option -> Map Text Expression
forall a b k. (a -> b) -> Map k a -> Map k b
M.map Option -> Expression
optionExpression
optionTypeExpr :: OptionType -> Expression
optionTypeExpr :: OptionType -> Expression
optionTypeExpr = OptionType -> Expression
optionTypeExpression
optionTypeExpression :: OptionType -> Expression
optionTypeExpression :: OptionType -> Expression
optionTypeExpression = OptionType -> Expression
go
where
go :: OptionType -> Expression
go = \case
OptionType
OptionTypeNull -> Expression -> Expression -> Expression
ExprAp (Text -> Expression
ExprVar Text
"lib.types.enum") ([Expression] -> Expression
ExprLitList [Expression
ExprNull])
OptionTypeSimple Text
s -> Text -> Expression
ExprVar Text
s
OptionTypeEnum [Expression]
es -> Expression -> Expression -> Expression
ExprAp (Text -> Expression
ExprVar Text
"lib.types.enum") ([Expression] -> Expression
ExprLitList [Expression]
es)
OptionTypeNullOr OptionType
ot -> Expression -> Expression -> Expression
ExprAp (Text -> Expression
ExprVar Text
"lib.types.nullOr") (OptionType -> Expression
go OptionType
ot)
OptionTypeListOf OptionType
ot ->
Expression -> Expression -> Expression
ExprAp
(Text -> Expression
ExprVar Text
"lib.types.listOf")
(OptionType -> Expression
go OptionType
ot)
OptionTypeAttrsOf OptionType
ot ->
Expression -> Expression -> Expression
ExprAp
(Text -> Expression
ExprVar Text
"lib.types.attrsOf")
(OptionType -> Expression
go OptionType
ot)
OptionTypeOneOf [OptionType]
os ->
Expression -> Expression -> Expression
ExprAp
(Text -> Expression
ExprVar Text
"lib.types.oneOf")
([Expression] -> Expression
ExprLitList ((OptionType -> Expression) -> [OptionType] -> [Expression]
forall a b. (a -> b) -> [a] -> [b]
map OptionType -> Expression
go [OptionType]
os))
OptionTypeSubmodule Map Text Option
os ->
Expression -> Expression -> Expression
ExprAp
(Text -> Expression
ExprVar Text
"lib.types.submodule")
(Map Text Expression -> Expression
ExprAttrSet (Text -> Expression -> Map Text Expression
forall k a. k -> a -> Map k a
M.singleton Text
"options" (Map Text Option -> Expression
optionsExpression Map Text Option
os)))