Skip to content

Commit

Permalink
Add new --omitEmpty option
Browse files Browse the repository at this point in the history
... as proposed in dhall-lang/dhall-kubernetes#46 (comment)

`--omitEmpty` is the same as `--omitNull` except it also omits fields that
are empty records.  To be precise, it omits fields whose transitive fields
are all `null` (and an empty record is a special case of a record whose
transitive fields are all `null` since it is vacuously true when there are
no fields).

This allows Dhall configurations that target YAML to avoid having to nest
sub-records inside of an `Optional` value.  Omitting unnecessary `Optional`
layers reduces the number of default values that the configuration format
needs to thread around.
  • Loading branch information
Gabriella439 committed Mar 6, 2019
1 parent aa35981 commit 5ee813f
Show file tree
Hide file tree
Showing 4 changed files with 49 additions and 24 deletions.
1 change: 1 addition & 0 deletions dhall-json/dhall-json.cabal
Expand Up @@ -63,6 +63,7 @@ Executable dhall-to-yaml
Main-Is: Main.hs
Build-Depends:
base ,
aeson ,
bytestring < 0.11,
dhall ,
dhall-json ,
Expand Down
15 changes: 4 additions & 11 deletions dhall-json/dhall-to-json/Main.hs
Expand Up @@ -6,6 +6,7 @@ module Main where
import Control.Applicative ((<|>))
import Control.Exception (SomeException)
import Control.Monad (when)
import Data.Aeson (Value)
import Data.Monoid ((<>))
import Data.Version (showVersion)
import Dhall.JSON (Conversion)
Expand All @@ -28,7 +29,7 @@ import qualified System.IO
data Options = Options
{ explain :: Bool
, pretty :: Bool
, omitNull :: Bool
, omission :: Value -> Value
, version :: Bool
, conversion :: Conversion
}
Expand All @@ -38,7 +39,7 @@ parseOptions =
Options
<$> parseExplain
<*> parsePretty
<*> parseOmitNull
<*> Dhall.JSON.parseOmission
<*> parseVersion
<*> Dhall.JSON.parseConversion
where
Expand Down Expand Up @@ -68,12 +69,6 @@ parseOptions =
defaultBehavior =
pure False

parseOmitNull =
Options.Applicative.switch
( Options.Applicative.long "omitNull"
<> Options.Applicative.help "Omit record fields that are null"
)

parseVersion =
Options.Applicative.switch
( Options.Applicative.long "version"
Expand Down Expand Up @@ -111,11 +106,9 @@ main = do

let explaining = if explain then Dhall.detailed else id

let omittingNull = if omitNull then Dhall.JSON.omitNull else id

stdin <- Data.Text.IO.getContents

json <- omittingNull <$> explaining (Dhall.JSON.codeToValue conversion "(stdin)" stdin)
json <- omission <$> explaining (Dhall.JSON.codeToValue conversion "(stdin)" stdin)

Data.ByteString.Char8.putStrLn $ Data.ByteString.Lazy.toStrict $ encode json

Expand Down
15 changes: 4 additions & 11 deletions dhall-json/dhall-to-yaml/Main.hs
Expand Up @@ -4,6 +4,7 @@
module Main where

import Control.Exception (SomeException)
import Data.Aeson (Value)
import Data.Monoid ((<>))
import Dhall.JSON (Conversion)
import Options.Applicative (Parser, ParserInfo)
Expand All @@ -22,7 +23,7 @@ import qualified System.IO

data Options = Options
{ explain :: Bool
, omitNull :: Bool
, omission :: Value -> Value
, documents :: Bool
, conversion :: Conversion
}
Expand All @@ -31,7 +32,7 @@ parseOptions :: Parser Options
parseOptions =
Options
<$> parseExplain
<*> parseOmitNull
<*> Dhall.JSON.parseOmission
<*> parseDocuments
<*> Dhall.JSON.parseConversion
where
Expand All @@ -41,12 +42,6 @@ parseOptions =
<> Options.Applicative.help "Explain error messages in detail"
)

parseOmitNull =
Options.Applicative.switch
( Options.Applicative.long "omitNull"
<> Options.Applicative.help "Omit record fields that are null"
)

parseDocuments =
Options.Applicative.switch
( Options.Applicative.long "documents"
Expand All @@ -70,11 +65,9 @@ main = do
handle $ do
let explaining = if explain then Dhall.detailed else id

let omittingNull = if omitNull then Dhall.JSON.omitNull else id

stdin <- Data.Text.IO.getContents

json <- omittingNull <$> explaining (Dhall.JSON.codeToValue conversion "(stdin)" stdin)
json <- omission <$> explaining (Dhall.JSON.codeToValue conversion "(stdin)" stdin)

let yaml = case (documents, json) of
(True, Data.Yaml.Array elems)
Expand Down
42 changes: 40 additions & 2 deletions dhall-json/src/Dhall/JSON.hs
Expand Up @@ -161,6 +161,8 @@ module Dhall.JSON (
-- * Dhall to JSON
dhallToJSON
, omitNull
, omitEmpty
, parseOmission
, Conversion(..)
, convertToHomogeneousMaps
, parseConversion
Expand Down Expand Up @@ -329,8 +331,9 @@ toOrderedList =

-- | Omit record fields that are @null@
omitNull :: Value -> Value
omitNull (Object object) =
Object (fmap omitNull (Data.HashMap.Strict.filter (/= Null) object))
omitNull (Object object) = Object fields
where
fields =Data.HashMap.Strict.filter (/= Null) (fmap omitNull object)
omitNull (Array array) =
Array (fmap omitNull array)
omitNull (String string) =
Expand All @@ -342,6 +345,40 @@ omitNull (Bool bool) =
omitNull Null =
Null

{-| Omit record fields that are @null@ or records whose transitive fields are
all null
-}
omitEmpty :: Value -> Value
omitEmpty (Object object) =
if null fields then Null else Object fields
where
fields = Data.HashMap.Strict.filter (/= Null) (fmap omitEmpty object)
omitEmpty (Array array) =
Array (fmap omitEmpty array)
omitEmpty (String string) =
String string
omitEmpty (Number number) =
Number number
omitEmpty (Bool bool) =
Bool bool
omitEmpty Null =
Null

-- | Parser for command-line options related to omitting fields
parseOmission :: Parser (Value -> Value)
parseOmission =
Options.Applicative.flag'
omitNull
( Options.Applicative.long "omitNull"
<> Options.Applicative.help "Omit record fields that are null"
)
<|> Options.Applicative.flag'
omitEmpty
( Options.Applicative.long "omitEmpty"
<> Options.Applicative.help "Omit record fields that are null or empty records"
)
<|> pure id

{-| Specify whether or not to convert association lists of type
@List { mapKey: Text, mapValue : v }@ to records
-}
Expand Down Expand Up @@ -691,6 +728,7 @@ convertToHomogeneousMaps (Conversion {..}) e0 = loop (Dhall.Core.normalize e0)
Dhall.Core.Embed a ->
Dhall.Core.Embed a

-- | Parser for command-line options related to homogeneous map support
parseConversion :: Parser Conversion
parseConversion =
conversion
Expand Down

0 comments on commit 5ee813f

Please sign in to comment.