Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Autodocodec.Nix
Synopsis
- renderNixOptionTypeViaCodec :: forall a. HasCodec a => Text
- renderNixOptionsViaCodec :: forall a. HasObjectCodec a => Text
- renderNixOptionTypeVia :: ValueCodec input output -> Text
- renderNixOptionsVia :: ObjectCodec input output -> Text
- valueCodecNixOptionType :: ValueCodec input output -> Maybe OptionType
- objectCodecNixOptions :: ObjectCodec input output -> Map Text Option
- data Option = Option {
- optionType :: !(Maybe OptionType)
- optionDescription :: !(Maybe Text)
- optionDefault :: !(Maybe Value)
- data OptionType
- renderOption :: Option -> Text
- renderOptionType :: OptionType -> Text
- optionExpr :: Option -> Expr
- optionsExpr :: Map Text Option -> Expr
- optionTypeExpr :: OptionType -> Expr
- renderExpr :: Expr -> Text
- data Option = Option {
- optionType :: !(Maybe OptionType)
- optionDescription :: !(Maybe Text)
- optionDefault :: !(Maybe Value)
- data OptionType
- data Expr
- = ExprNull
- | ExprLitBool !Bool
- | ExprLitString !Text
- | ExprLitNumber !Scientific
- | ExprLitList ![Expr]
- | ExprVar !Text
- | ExprAttrSet !(Map Text Expr)
- | ExprAp !Expr !Expr
- | ExprFun ![Text] !Expr
- | ExprWith !Text !Expr
- apply :: [Text] -> [Text] -> [Text]
- parens :: [Text] -> [Text]
- append :: [Text] -> Text -> [Text]
- indent :: [Text] -> [Text]
- renderNixOptionTypeViaCodec :: forall a. HasCodec a => Text
- renderNixOptionsViaCodec :: forall a. HasObjectCodec a => Text
- renderNixOptionTypeVia :: ValueCodec input output -> Text
- renderNixOptionsVia :: ObjectCodec input output -> Text
- valueCodecNixOptionType :: ValueCodec input output -> Maybe OptionType
- objectCodecNixOptions :: ObjectCodec input output -> Map Text Option
- renderOption :: Option -> Text
- renderOptionType :: OptionType -> Text
- optionExpr :: Option -> Expr
- optionsExpr :: Map Text Option -> Expr
- optionTypeExpr :: OptionType -> Expr
- renderExpr :: Expr -> Text
- renderOptions :: Map Text Option -> Text
- simplifyOptionType :: OptionType -> OptionType
- jsonValueExpr :: Value -> Expr
- simplifyOptions :: Map Text Option -> Map Text Option
- emptyOption :: Option
- simplifyOption :: Option -> Option
- withNixArgs :: Expr -> Expr
- surround :: Text -> Text -> [Text] -> [Text]
- surroundWith :: Text -> Text -> Text -> [Text] -> [Text]
- prependWith :: Text -> Text -> [Text] -> [Text]
- prepend :: Text -> [Text] -> [Text]
- appendWith :: Text -> [Text] -> Text -> [Text]
Producing a Nixos module type
renderNixOptionTypeViaCodec :: forall a. HasCodec a => Text Source #
renderNixOptionsViaCodec :: forall a. HasObjectCodec a => Text Source #
renderNixOptionTypeVia :: ValueCodec input output -> Text Source #
renderNixOptionsVia :: ObjectCodec input output -> Text Source #
valueCodecNixOptionType :: ValueCodec input output -> Maybe OptionType Source #
objectCodecNixOptions :: ObjectCodec input output -> Map Text Option Source #
Constructors
Option | |
Fields
|
data OptionType Source #
Constructors
Instances
Show OptionType Source # | |
Defined in Autodocodec.Nix Methods showsPrec :: Int -> OptionType -> ShowS # show :: OptionType -> String # showList :: [OptionType] -> ShowS # | |
Eq OptionType Source # | |
Defined in Autodocodec.Nix | |
Ord OptionType Source # | |
Defined in Autodocodec.Nix Methods compare :: OptionType -> OptionType -> Ordering # (<) :: OptionType -> OptionType -> Bool # (<=) :: OptionType -> OptionType -> Bool # (>) :: OptionType -> OptionType -> Bool # (>=) :: OptionType -> OptionType -> Bool # max :: OptionType -> OptionType -> OptionType # min :: OptionType -> OptionType -> OptionType # |
renderOption :: Option -> Text Source #
renderOptionType :: OptionType -> Text Source #
optionExpr :: Option -> Expr Source #
optionTypeExpr :: OptionType -> Expr Source #
renderExpr :: Expr -> Text Source #
To makes sure we definitely export everything.
Constructors
Option | |
Fields
|
data OptionType Source #
Constructors
Instances
Show OptionType Source # | |
Defined in Autodocodec.Nix Methods showsPrec :: Int -> OptionType -> ShowS # show :: OptionType -> String # showList :: [OptionType] -> ShowS # | |
Eq OptionType Source # | |
Defined in Autodocodec.Nix | |
Ord OptionType Source # | |
Defined in Autodocodec.Nix Methods compare :: OptionType -> OptionType -> Ordering # (<) :: OptionType -> OptionType -> Bool # (<=) :: OptionType -> OptionType -> Bool # (>) :: OptionType -> OptionType -> Bool # (>=) :: OptionType -> OptionType -> Bool # max :: OptionType -> OptionType -> OptionType # min :: OptionType -> OptionType -> OptionType # |
Constructors
ExprNull | |
ExprLitBool !Bool | |
ExprLitString !Text | |
ExprLitNumber !Scientific | |
ExprLitList ![Expr] | |
ExprVar !Text | |
ExprAttrSet !(Map Text Expr) | |
ExprAp !Expr !Expr | |
ExprFun ![Text] !Expr | |
ExprWith !Text !Expr |
renderNixOptionTypeViaCodec :: forall a. HasCodec a => Text Source #
renderNixOptionsViaCodec :: forall a. HasObjectCodec a => Text Source #
renderNixOptionTypeVia :: ValueCodec input output -> Text Source #
renderNixOptionsVia :: ObjectCodec input output -> Text Source #
valueCodecNixOptionType :: ValueCodec input output -> Maybe OptionType Source #
objectCodecNixOptions :: ObjectCodec input output -> Map Text Option Source #
renderOption :: Option -> Text Source #
renderOptionType :: OptionType -> Text Source #
optionExpr :: Option -> Expr Source #
optionTypeExpr :: OptionType -> Expr Source #
renderExpr :: Expr -> Text Source #
jsonValueExpr :: Value -> Expr Source #
emptyOption :: Option Source #
simplifyOption :: Option -> Option Source #
withNixArgs :: Expr -> Expr Source #