Search code examples
haskellyamldhall

How to represent "Data.Map Text Text" in Dhall?


If I have a type in Haskell like this:

data MyType = MyType
  { env :: Map Text Text
  }

How can I represent a value of MyType in Dhall?

{ env = ???
}

What I want to do is to write values of MyType in Dhall and then read it in from Haskell and unmarshal it into MyType, like this:

main :: IO ()
main = do
    x <- input auto "./config"
    print (x :: MyType)

I'm coming from Data.Aeson and YAML where you can represent maps like this:

env:
  KEY1: "foo"
  KEY2: "bar"

(you would be able to parse the above into the MyType type using Aeson's decodeFileEither).


Solution

  • After some digging, I found three workarounds. Skip to the bottom if you want the best workaround until toMap lands.

    As of 2019-05-05 there is no way to represent maps in Dhall like how it is possible with Aeson/YAML (although support for a native toMap function is coming soon). So for now we basically have to use a list of homogeneous records. It's a bit clunky, but at least you get the native unmarshaling.

    If we want to use a list of tuples instead of a map, we can do this:

    {-# LANGUAGE DeriveGeneric     #-}
    {-# LANGUAGE GeneralizedNewtypeDeriving   #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE FlexibleInstances     #-}
    {-# LANGUAGE RecordWildCards     #-}
    
    module Tuple where
    
    import Dhall
    import qualified Data.Text as T
    
    data MyType = MyType { env :: [MyTuple] }
        deriving (Generic, Show)
    
    instance Interpret MyType
    
    newtype MyTuple = MyTuple (T.Text, T.Text)
        deriving (Interpret, Show)
    
    -- input auto "{env = [{_1= \"HOME\", _2 = \"foo\"}] }" :: IO MyType
    

    The above was adapted from this answer, which showed a way to parse IP addresses as 4-element tuples.

    For parsing into a Map, we can do:

    {-# LANGUAGE RecordWildCards #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE DeriveGeneric     #-}
    {-# LANGUAGE FlexibleInstances     #-}
    
    module MapA where
    
    import Data.Map (Map)
    import Data.Text (Text)
    import Dhall
    
    import qualified Data.Map
    
    data MyType = MyType { env :: Map Text Text }
        deriving (Generic, Show)
    
    data KeyValue a = KeyValue { mapKey :: Text, mapValue :: a }
        deriving (Generic, Show)
    
    toMap :: [KeyValue a] -> Map Text a
    toMap keyValues = Data.Map.fromList (map adapt keyValues)
      where
        adapt (KeyValue {..}) = (mapKey, mapValue)
    
    instance Interpret MyType
    instance Interpret a => Interpret (KeyValue a)
    
    -- Wrap `Map` in a newtype if you want to avoid an orphan instance
    instance Interpret a => Interpret (Map Text a) where
        autoWith options = fmap toMap (autoWith options)
    
    -- input auto "{env = [{mapKey = \"HOME\", mapValue = \"foo\"}] }" :: IO MapA.MyType
    

    The above was adapted from this comment. The idea is to make records that look like { mapKey = X, mapValue = Y} parseable, and then to convert any lists of such records into a Map. Notice how we support any value type, not just text (so we can have env in MyType be Map Text Int or something else, if we wanted to). This solution has just 1 type variable a for the values in the map, but I suppose it is possible to make the keys more generic as well.

    OK so after some tweaking, I got the following to compile, which supports both keys and values to be generic as well:

    {-# LANGUAGE RecordWildCards #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE DeriveGeneric     #-}
    {-# LANGUAGE FlexibleInstances     #-}
    
    module MapKV where
    
    import Data.Map (Map)
    import Data.Text (Text)
    import Dhall
    
    import qualified Data.Map
    
    data MyType = MyType { env :: Map Text Text }
        deriving (Generic, Show)
    
    data MyTypeInts = MyTypeInts { envInts :: Map Integer Integer }
        deriving (Generic, Show)
    
    data KeyValue k v = KeyValue { mapKey :: k, mapValue :: v }
        deriving (Generic, Show)
    
    toMap :: Ord k => [KeyValue k v] -> Map k v
    toMap keyValues = Data.Map.fromList (map adapt keyValues)
      where
        adapt (KeyValue {..}) = (mapKey, mapValue)
    
    instance Interpret MyType
    instance Interpret MyTypeInts
    instance (Interpret k, Interpret v) => Interpret (KeyValue k v)
    
    -- Wrap `Map` in a newtype if you want to avoid an orphan instance
    instance (Ord k, Interpret k, Interpret v) => Interpret (Map k v) where
        autoWith options = fmap toMap (autoWith options)
    
    -- input auto "{env = [{mapKey = +1, mapValue = \"foo\"}] }" :: IO MapKV.MyType
    -- input auto "{envInts = [{mapKey = +1, mapValue = -22 }] }" :: IO MapKV.MyTypeInts
    

    Lastly here is a version that avoids the orphan instance that uses an Env newtype wrapper:

    {-# LANGUAGE RecordWildCards #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE DeriveGeneric     #-}
    {-# LANGUAGE FlexibleInstances     #-}
    
    module MapKV where
    
    import Data.Map (Map)
    import Dhall
    
    import qualified Data.Map
    
    data MyType = MyType { env :: Env }
        deriving (Generic, Show)
    
    newtype Env = Env (Map Text Text)
      deriving (Eq, Generic, Show)
    
    data KeyValue k v = KeyValue { mapKey :: k, mapValue :: v }
        deriving (Generic, Show)
    
    toMap :: Ord k => [KeyValue k v] -> Map k v
    toMap keyValues = Data.Map.fromList (map adapt keyValues)
      where
        adapt (KeyValue {..}) = (mapKey, mapValue)
    
    instance Interpret MyType
    instance (Interpret k, Interpret v) => Interpret (KeyValue k v)
    
    instance Interpret Env where
        autoWith options = fmap (Env . toMap) (autoWith options)
    
    -- input auto "{env = [{mapKey = \"HOME\", mapValue = \"foo\"}] }" :: IO MapKV.MyType