Skip to content

Commit

Permalink
Merge pull request #33 from obsidiansystems/ghc-9.10
Browse files Browse the repository at this point in the history
Build with ghc 9.10
  • Loading branch information
alexfmpe authored Jan 14, 2025
2 parents 0cbfbee + 36b1699 commit 6dd977c
Show file tree
Hide file tree
Showing 5 changed files with 42 additions and 37 deletions.
14 changes: 8 additions & 6 deletions .github/workflows/haskell.yml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ jobs:
build:
strategy:
matrix:
ghc: ['8.4.4', '8.6.5', '8.8.4', '8.10.7', '9.0.2', '9.2.5']
ghc: ['8.6.5', '8.8.4', '8.10.7', '9.0.2', '9.2.5', '9.4.5', '9.6.1', '9.8.2', '9.10.1']
os: ['ubuntu-latest', 'macos-latest']
runs-on: ${{ matrix.os }}

Expand All @@ -16,7 +16,6 @@ jobs:
- uses: haskell/actions/setup@v2
with:
ghc-version: ${{ matrix.ghc }}
cabal-version: '3.10.1.0'
- name: Cache
uses: actions/cache@v3
env:
Expand All @@ -31,12 +30,15 @@ jobs:
${{ runner.os }}
- name: Install dependencies
run: cabal build --only-dependencies --enable-tests --enable-benchmarks
run: |
cabal update
cabal build --only-dependencies --enable-tests --enable-benchmarks
- name: Build
run: cabal build --enable-tests --enable-benchmarks all

- name: Run tests
run: cabal test --enable-tests all
- if: matrix.ghc != '8.4.4'
# docs aren't built on ghc 8.4.4 because some dependency docs don't build on older GHCs
name: Build Docs

- name: Build Docs
run: cabal haddock
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1 +1,2 @@
dist/
dist-newstyle/
51 changes: 26 additions & 25 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -16,74 +16,75 @@ Example Usage:
> {-# LANGUAGE UndecidableInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# OPTIONS_GHC -ddump-splices #-}
>

> import Data.Aeson
> import Data.Aeson.GADT.TH
> import Data.Dependent.Map (DMap)
> import Data.Dependent.Sum (DSum)
> import Data.Functor.Identity
> import Data.GADT.Compare
> import Data.GADT.Show.TH
> import Data.Kind (Type)
> import Data.Some (Some(..))
>
> data A :: * -> * where

> data A :: Type -> Type where
> A_a :: A a
> A_b :: Int -> A ()
>

> deriveJSONGADT ''A
> deriveGShow ''A
>
> data B c :: * -> * where

> data B c :: Type -> Type where
> B_a :: c -> A a -> B c a
> B_x :: B c a
>

> deriveJSONGADT ''B
>
> data C t :: * -> * where

> data C t :: Type -> Type where
> C_t :: t -> C t t
>

> deriveJSONGADT ''C
>
> data D t x :: * -> * where

> data D t x :: Type -> Type where
> D_t :: t -> D t x t
> D_x :: x -> D t x x
> D_i :: Int -> D t x Int
>

> deriveJSONGADT ''D
>

> data Auth token a where
> Auth_Login :: String -> String -> Auth token (Either String token)
>

> deriveJSONGADT ''Auth
>

> -- Some real-world-ish examples.
>

> -- | Edit operations for `LabelledGraph`
> data LabelledGraphEdit v vm em :: * -> * where
> data LabelledGraphEdit v vm em :: Type -> Type where
> LabelledGraphEdit_ClearAll :: LabelledGraphEdit v vm em ()
> LabelledGraphEdit_AddVertex :: vm -> LabelledGraphEdit v vm em v
> LabelledGraphEdit_AddEdge :: v -> v -> em -> LabelledGraphEdit v vm em ()
> LabelledGraphEdit_SetVertexProperties :: v -> vm -> LabelledGraphEdit v vm em ()
> LabelledGraphEdit_SetEdgeProperties :: v -> v -> em -> LabelledGraphEdit v vm em ()
>

> -- | PropertyGraphEdit operatios for `PropertyGraph`
> data PropertyGraphEdit v vp ep r where
> PropertyGraphEdit_ClearAll :: PropertyGraphEdit v vp ep ()
> PropertyGraphEdit_AddVertex :: (DMap vp Identity) -> PropertyGraphEdit v vp ep v
> PropertyGraphEdit_AddEdge :: v -> v -> (DMap ep Identity) -> PropertyGraphEdit v vp ep ()
> PropertyGraphEdit_SetVertexProperty :: GCompare vp => v -> DSum vp Identity -> PropertyGraphEdit v vp ep ()
> PropertyGraphEdit_SetEdgeProperty :: GCompare ep => v -> v -> DSum ep Identity -> PropertyGraphEdit v vp ep ()
>

> -- | View operations for `LabelledGraph`
> data LabelledGraphView v vm em :: * -> * where
> data LabelledGraphView v vm em :: Type -> Type where
> LabelledGraphView_All :: LabelledGraphView v vm em ()
> LabelledGraphView_GetVertexProperties :: v -> LabelledGraphView v vm em vm
> LabelledGraphView_GetEdgeProperties :: v -> v -> LabelledGraphView v vm em em
>

> deriveJSONGADT ''LabelledGraphEdit
> deriveJSONGADT ''PropertyGraphEdit
> deriveJSONGADT ''LabelledGraphView
>

> main :: IO ()
> main = do
> putStrLn $ unlines
Expand All @@ -92,14 +93,14 @@ Example Usage:
> , "Decoding of encoded A_a:"
> , show (decode $ encode A_a :: Maybe (Some A))
> ]
>

> putStrLn $ unlines
> [ "Encoding of (A_b 1):"
> , show $ encode (A_b 1)
> , "Decoding of encoded (A_b 1):"
> , show (decode $ encode (A_b 1) :: Maybe (Some A))
> ]
>

> putStrLn $ unlines
> [ "Encoding of (B_a 'a' (A_b 1)):"
> , show $ encode (B_a 'a' (A_b 1))
Expand Down
6 changes: 3 additions & 3 deletions aeson-gadt-th.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -20,12 +20,12 @@ flag build-readme

library
exposed-modules: Data.Aeson.GADT.TH
build-depends: base >= 4.8 && < 4.20
build-depends: base >= 4.9 && < 4.21
, aeson >= 1.3 && < 2.3
, containers >= 0.5 && < 0.7
, containers >= 0.5 && < 0.8
, dependent-sum >= 0.4 && < 0.8
, transformers >= 0.5 && < 0.7
, template-haskell >= 2.11.0 && < 2.22
, template-haskell >= 2.11.0 && < 2.23
, th-abstraction >= 0.4 && < 0.8
if impl(ghc < 8.2)
build-depends: dependent-sum < 0.6.2.2
Expand Down
7 changes: 4 additions & 3 deletions src/Data/Aeson/GADT/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,8 @@ import Control.Monad (forM, replicateM)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Writer (WriterT, runWriterT, tell)
import Data.Aeson (FromJSON(..), ToJSON(..))
import Data.List (group, intercalate, partition, sort)
import Data.List (intercalate, partition, sort)
import qualified Data.List.NonEmpty as NonEmpty
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
Expand Down Expand Up @@ -117,7 +118,7 @@ deriveToJSONGADTWithOptions opts n = do
topVars <- makeTopVars n
let n' = foldl (\c v -> AppT c (VarT v)) (ConT n) topVars
(matches, constraints') <- runWriterT (mapM (fmap pure . conMatchesToJSON opts topVars) cons)
let constraints = map head . group . sort $ constraints' -- This 'head' is safe because 'group' returns a list of non-empty lists
let constraints = map NonEmpty.head . NonEmpty.group . sort $ constraints'
impl <- funD 'toJSON
[ clause [] (normalB $ lamCaseE matches) []
]
Expand Down Expand Up @@ -149,7 +150,7 @@ deriveFromJSONGADTWithOptions opts n = do
topVars <- makeTopVars n
let n' = foldl (\c v -> AppT c (VarT v)) (ConT n) $ init topVars
(matches, constraints') <- runWriterT $ mapM (conMatchesParseJSON opts topVars [|_v'|]) cons
let constraints = map head . group . sort $ constraints' -- This 'head' is safe because 'group' returns a list of non-empty lists
let constraints = map NonEmpty.head . NonEmpty.group . sort $ constraints'
v <- newName "v"
parser <- funD 'parseJSON
[ clause [varP v] (normalB [e|
Expand Down

0 comments on commit 6dd977c

Please sign in to comment.