Skip to content

Commit

Permalink
Support aeson >= 2 (#313)
Browse files Browse the repository at this point in the history
* Support aeson >= 2

* Add changelog entry for aeson 2.0

* Adapt tests to aeson >= 2
  • Loading branch information
fendor authored Oct 28, 2021
1 parent 0c84343 commit df7c429
Show file tree
Hide file tree
Showing 4 changed files with 48 additions and 5 deletions.
5 changes: 5 additions & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,10 @@
# ChangeLog hie-bios

## TBD - 0.8.0

* Support aeson >= 2.0. [#313](https://github.com/haskell/hie-bios/pull/313)
* Remove CradleOpt Type [#293](https://github.com/haskell/hie-bios/pull/293)

## 2021-08-30 - 0.7.6

* Don't look for NIX_GHC_LIBDIR as it is redundant [#294](https://github.com/mpickering/hie-bios/pull/294)
Expand Down
3 changes: 2 additions & 1 deletion hie-bios.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -146,7 +146,7 @@ Library
autogen-modules: Paths_hie_bios
Build-Depends:
base >= 4.8 && < 5,
aeson >= 1.4.5 && < 2,
aeson >= 1.4.5 && < 2.1,
base16-bytestring >= 0.1.1 && < 1.1,
bytestring >= 0.10.8 && < 0.12,
deepseq >= 1.4.3 && < 1.5,
Expand Down Expand Up @@ -191,6 +191,7 @@ test-suite parser-tests
default-language: Haskell2010
build-depends:
base,
aeson,
filepath,
hie-bios,
hspec-expectations,
Expand Down
27 changes: 25 additions & 2 deletions src/HIE/Bios/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE CPP #-}
-- | Logic and datatypes for parsing @hie.yaml@ files.
module HIE.Bios.Config(
readConfig,
Expand All @@ -24,14 +25,36 @@ module HIE.Bios.Config(
import Control.Exception
import qualified Data.Text as T
import qualified Data.Vector as V
#if MIN_VERSION_aeson(2,0,0)
import Data.Aeson.Key (fromText)
import Data.Aeson.KeyMap (KeyMap)
import qualified Data.Aeson.KeyMap as Map
#else
import qualified Data.HashMap.Strict as Map
#endif
import Data.Maybe (mapMaybe)
import Data.Monoid (Last(..))
import Data.Foldable (foldrM)
import Data.Aeson (JSONPath)
import Data.Yaml
import Data.Yaml.Internal (Warning(..))


#if !MIN_VERSION_aeson(2,0,0)
-- | Backwards compatible type-def for Key
-- This used to be just a Text, but since aeson >= 2
-- this is an opaque datatype.
type Key = T.Text
-- | Backwards compatible type-def for KeyMap
-- This used to be just a HashMap, but since aeson >= 2
-- this is an opaque datatype.
type KeyMap v = Map.HashMap T.Text v

-- | Create a Key from a Text.
fromText :: T.Text -> Key
fromText = id
#endif

-- | Configuration that can be used to load a 'Cradle'.
-- A configuration has roughly the following form:
--
Expand Down Expand Up @@ -149,7 +172,7 @@ parseSingleOrMultiple
:: Monoid x
=> (x -> CradleType a)
-> (x -> [(FilePath, x)] -> CradleType a)
-> (Map.HashMap T.Text Value -> Parser x)
-> (KeyMap Value -> Parser x)
-> Value
-> Parser (CradleType a)
parseSingleOrMultiple single multiple parse = doParse where
Expand Down Expand Up @@ -224,7 +247,7 @@ parseBios (Object x) =
exclusive l Nothing = l
exclusive Nothing r = r
stringTypeFromMap :: (String -> t) -> T.Text -> Maybe t
stringTypeFromMap constructor name = constructor <$> (intoString =<< Map.lookup name x)
stringTypeFromMap constructor name = constructor <$> (intoString =<< Map.lookup (fromText name) x)
intoString :: Value -> Maybe String
intoString (String s) = Just (T.unpack s)
intoString _ = Nothing
Expand Down
18 changes: 16 additions & 2 deletions tests/ParserTests.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,20 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Main where

import Test.Hspec.Expectations
import Test.Tasty
import Test.Tasty.HUnit
import HIE.Bios.Config
#if MIN_VERSION_aeson(2,0,0)
import Data.Aeson.Key ( Key )
import qualified Data.Aeson.KeyMap as Map
#else
import qualified Data.HashMap.Strict as Map
import qualified Data.Text as T
#endif
import Data.Void
import Data.Yaml
import qualified Data.Text as T
import System.FilePath
import Control.Applicative ( (<|>) )
import Control.Exception
Expand Down Expand Up @@ -120,11 +126,19 @@ instance FromJSON CabalHelper where

parseJSON _ = fail "Not a valid cabal-helper specification"

simpleCabalHelperYaml :: T.Text -> Value
simpleCabalHelperYaml :: Key -> Value
simpleCabalHelperYaml tool =
object
[ ( "cabal-helper", object
[ (tool, Null)
]
)
]

-- ------------------------------------------------------------------
-- Helper functions to support aeson < 2
-- ------------------------------------------------------------------

#if !MIN_VERSION_aeson(2,0,0)
type Key = T.Text
#endif

0 comments on commit df7c429

Please sign in to comment.