Tighten package constraints

Before Hackage, we should probably pick some actual library versions to
depend on. This commit does that, and removes the lens dependency, which
should make installation much faster.
This commit is contained in:
Tom Harding 2019-04-12 14:17:13 +01:00
parent 4a9113b127
commit 17b8786547
3 changed files with 22 additions and 14 deletions

View File

@ -24,10 +24,9 @@ library
-- other-modules:
-- other-extensions:
build-depends: base ^>=4.12.0.0
, barbies
, generic-lens
, lens
, QuickCheck
, barbies ^>=1.1.0.0
, generic-lens ^>=1.1.0.0
, QuickCheck ^>=2.12.0
hs-source-dirs: src
default-language: Haskell2010

View File

@ -23,9 +23,10 @@ module Data.Generic.HKD.Field
( HasField' (..)
) where
import Control.Lens (Lens', dimap)
import Data.Coerce (coerce)
import Data.Generic.HKD.Types (HKD (..), HKD_)
import Data.Kind (Constraint, Type)
import Data.Void (Void)
import GHC.TypeLits (ErrorMessage (..), Symbol, TypeError)
import qualified Data.GenericLens.Internal as G
import qualified Data.Generics.Internal.VL.Lens as G
@ -68,7 +69,7 @@ class HasField'
(structure :: Type)
(focus :: Type)
| field f structure -> focus where
field :: Lens' (HKD structure f) (f focus)
field :: G.Lens' (HKD structure f) (f focus)
data HasTotalFieldPSym :: Symbol -> (G.TyFun (Type -> Type) (Maybe Type))
type instance G.Eval (HasTotalFieldPSym sym) tt = G.HasTotalFieldP sym tt
@ -77,7 +78,10 @@ instance
( ErrorUnless field structure (G.CollectField field (HKD_ f structure))
, G.GLens' (HasTotalFieldPSym field) (HKD_ f structure) (f focus)
) => HasField' field f structure focus where
field = G.ravel (dimap runHKD HKD . G.glens @(HasTotalFieldPSym field))
field = coerced . G.ravel (G.glens @(HasTotalFieldPSym field))
where
coerced :: G.Lens' (HKD structure f) (HKD_ f structure Void)
coerced f = fmap coerce . f . coerce
-- We'll import this from actual generic-lens as soon as possible:

View File

@ -5,6 +5,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
@ -25,7 +26,7 @@ module Data.Generic.HKD.Position
import Data.Coerce (Coercible, coerce)
import Data.Type.Bool (type (&&))
import Control.Lens (Lens', dimap)
import Data.Void (Void)
import GHC.Generics
import Data.Generic.HKD.Types (HKD (..), HKD_)
import Data.Kind (Constraint, Type)
@ -55,7 +56,7 @@ import Data.Generics.Internal.Profunctor.Lens (ALens)
-- ...
class HasPosition' (index :: Nat) (f :: Type -> Type) (structure :: Type) (focus :: Type)
| index f structure -> focus where
position :: Lens' (HKD structure f) (f focus)
position :: G.Lens' (HKD structure f) (f focus)
data HasTotalPositionPSym :: Nat -> (G.TyFun (Type -> Type) (Maybe Type))
type instance G.Eval (HasTotalPositionPSym t) tt = G.HasTotalPositionP t tt
@ -64,16 +65,20 @@ instance
( Generic structure
, ErrorUnless index structure (0 <? index && index <=? G.Size (Rep structure))
, G.GLens' (HasTotalPositionPSym index) (CRep f structure) (f focus)
, G.HasTotalPositionP index (CRep f structure) ~ 'Just (f focus)
, G.HasTotalPositionP index (CRep f (G.Indexed structure)) ~ 'Just (f' focus')
, Coercible (HKD structure f) (CRep f structure Void)
, structure ~ G.Infer structure (f' focus') (f focus)
, Coercible (CRep f structure) (HKD_ f structure)
) => HasPosition' index f structure focus where
position = G.ravel (dimap runHKD HKD . go . G.glens @(HasTotalPositionPSym index))
position = coerced . glens
where
go :: ALens (f focus) (f focus) (CRep f structure p) (CRep f structure p)
-> ALens (f focus) (f focus) (HKD_ f structure p) (HKD_ f structure p)
go = coerce
glens :: G.Lens' (CRep f structure Void) (f focus)
glens = G.ravel (G.glens @(HasTotalPositionPSym index))
coerced :: G.Lens' (HKD structure f) (CRep f structure Void)
coerced f = fmap coerce . f . coerce
-- Again: to be imported from generic-lens.