Skip to content

Commit 5e6c70a

Browse files
authored
Merge pull request #15 from odr/master
Add: lts-13.7 (base-4.12)
2 parents 27474d8 + ae27c60 commit 5e6c70a

File tree

5 files changed

+39
-8
lines changed

5 files changed

+39
-8
lines changed

schematic.cabal

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ library
6565
, TypeOperators
6666
, TypeSynonymInstances
6767
, UndecidableInstances
68-
build-depends: base >=4.11 && <4.12
68+
build-depends: base >=4.11 && <4.13
6969
, bytestring
7070
, aeson >= 1
7171
, containers
@@ -95,7 +95,7 @@ test-suite spec
9595
default-language: Haskell2010
9696
build-depends: HUnit
9797
, aeson >= 1
98-
, base >=4.11 && <4.12
98+
, base >=4.11 && <4.13
9999
, bytestring
100100
, containers
101101
, hjsonschema

src/Data/Schematic/DSL.hs

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE AllowAmbiguousTypes #-}
2+
{-# LANGUAGE CPP #-}
23

34
module Data.Schematic.DSL where
45

@@ -17,11 +18,19 @@ import Data.Vinyl
1718
import Data.Vinyl.Functor
1819

1920

21+
#if MIN_VERSION_base(4,12,0)
2022
type Constructor a
21-
= forall fields b. (fields ~ FieldsOf a, FSubset fields b (FImage fields b))
23+
= forall fields b
24+
. (fields ~ FieldsOf a, FSubset fields b (FImage fields b), RMap fields)
2225
=> Rec (Tagged fields :. FieldRepr) b
2326
-> JsonRepr ('SchemaObject fields)
24-
27+
#else
28+
type Constructor a
29+
= forall fields b
30+
. (fields ~ FieldsOf a, FSubset fields b (FImage fields b))
31+
=> Rec (Tagged fields :. FieldRepr) b
32+
-> JsonRepr ('SchemaObject fields)
33+
#endif
2534
withRepr :: Constructor a
2635
withRepr = ReprObject . rmap (unTagged . getCompose) . fcast
2736

src/Data/Schematic/Migration.hs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE AllowAmbiguousTypes #-}
2-
{-# LANGUAGE TemplateHaskell #-}
2+
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE TemplateHaskell #-}
34

45
module Data.Schematic.Migration where
56

@@ -8,7 +9,7 @@ import Data.Schematic.DSL
89
import Data.Schematic.Lens
910
import Data.Schematic.Path
1011
import Data.Schematic.Schema
11-
import Data.Singletons.Prelude hiding (All, (:.))
12+
import Data.Singletons.Prelude hiding ((:.), All)
1213
import Data.Singletons.TypeLits
1314
import Data.Tagged
1415
import Data.Vinyl
@@ -156,10 +157,17 @@ data MList :: (Type -> Type) -> [Schema] -> Type where
156157

157158
infixr 7 :&&
158159

160+
#if MIN_VERSION_base(4,12,0)
161+
migrateObject
162+
:: forall m fs fh. (FSubset fs fs (FImage fs fs), Monad m, RMap fh, RMap fs)
163+
=> (Rec (Tagged fs :. FieldRepr) fh -> m (Rec (Tagged fs :. FieldRepr) fs))
164+
-> Tagged ('SchemaObject fs) (JsonRepr ('SchemaObject fh) -> m (JsonRepr ('SchemaObject fs)))
165+
#else
159166
migrateObject
160167
:: forall m fs fh. (FSubset fs fs (FImage fs fs), Monad m)
161168
=> (Rec (Tagged fs :. FieldRepr) fh -> m (Rec (Tagged fs :. FieldRepr) fs))
162169
-> Tagged ('SchemaObject fs) (JsonRepr ('SchemaObject fh) -> m (JsonRepr ('SchemaObject fs)))
170+
#endif
163171
migrateObject f = Tagged $ \(ReprObject r) -> do
164172
res <- f $ rmap (Compose . Tagged) r
165173
pure $ withRepr @('SchemaObject fs) res

src/Data/Schematic/Schema.hs

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE AllowAmbiguousTypes #-}
2-
{-# LANGUAGE OverloadedLists #-}
3-
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE OverloadedLists #-}
4+
{-# LANGUAGE OverloadedStrings #-}
45
{-# OPTIONS_GHC -fprint-explicit-kinds #-}
56

67
module Data.Schematic.Schema where
@@ -376,8 +377,16 @@ instance Show (JsonRepr 'SchemaNull) where show _ = "ReprNull"
376377
instance Show (JsonRepr s) => Show (JsonRepr ('SchemaArray acs s)) where
377378
show (ReprArray v) = "ReprArray " P.++ show v
378379

380+
#if MIN_VERSION_base(4,12,0)
381+
instance
382+
( V.RecAll FieldRepr fs Show, RMap fs, ReifyConstraint Show FieldRepr fs
383+
, RecordToList fs )
384+
=> Show (JsonRepr ('SchemaObject fs)) where
385+
show (ReprObject fs) = "ReprObject " P.++ show fs
386+
#else
379387
instance V.RecAll FieldRepr fs Show => Show (JsonRepr ('SchemaObject fs)) where
380388
show (ReprObject fs) = "ReprObject " P.++ show fs
389+
#endif
381390

382391
instance Show (JsonRepr s) => Show (JsonRepr ('SchemaOptional s)) where
383392
show (ReprOptional s) = "ReprOptional " P.++ show s

stack-13.7.yaml

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
resolver: lts-13.7
2+
extra-deps:
3+
- hjsonpointer-1.4.0@rev:0
4+
- hjsonschema-1.9.0@rev:0
5+
- validationt-0.2.1.0

0 commit comments

Comments
 (0)