mirror of
https://github.com/tensorflow/haskell.git
synced 2024-11-26 21:09:44 +01:00
Fix the build with ghc-8.2.1. (#147)
- Avoid using a deprecated Cabal function - Use newer versions of proto-lens packages in stack.yaml - Work around a new type-level warning that affects `OneOf/TensorTypes`.
This commit is contained in:
parent
56038ba27e
commit
7328cb277f
3 changed files with 39 additions and 6 deletions
|
@ -20,7 +20,8 @@ extra-deps:
|
||||||
- proto-lens-protobuf-types-0.2.2.0
|
- proto-lens-protobuf-types-0.2.2.0
|
||||||
- proto-lens-0.2.2.0
|
- proto-lens-0.2.2.0
|
||||||
- proto-lens-descriptors-0.2.2.0
|
- proto-lens-descriptors-0.2.2.0
|
||||||
- proto-lens-protoc-0.2.2.1
|
- proto-lens-protoc-0.2.2.3
|
||||||
|
- lens-labels-0.1.0.2
|
||||||
|
|
||||||
# For Mac OS X, whose linker doesn't use this path by default
|
# For Mac OS X, whose linker doesn't use this path by default
|
||||||
# unless you run `xcode-select --install`.
|
# unless you run `xcode-select --install`.
|
||||||
|
|
|
@ -11,6 +11,7 @@
|
||||||
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
|
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
|
||||||
-- See the License for the specific language governing permissions and
|
-- See the License for the specific language governing permissions and
|
||||||
-- limitations under the License.
|
-- limitations under the License.
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
-- | Generates the wrappers for Ops shipped with tensorflow.
|
-- | Generates the wrappers for Ops shipped with tensorflow.
|
||||||
module Main where
|
module Main where
|
||||||
|
@ -20,7 +21,7 @@ import Distribution.PackageDescription
|
||||||
, libBuildInfo
|
, libBuildInfo
|
||||||
, hsSourceDirs
|
, hsSourceDirs
|
||||||
)
|
)
|
||||||
import Distribution.Simple.BuildPaths (autogenModulesDir)
|
import qualified Distribution.Simple.BuildPaths as BuildPaths
|
||||||
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo)
|
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo)
|
||||||
import Distribution.Simple
|
import Distribution.Simple
|
||||||
( defaultMainWithHooks
|
( defaultMainWithHooks
|
||||||
|
@ -91,3 +92,10 @@ blackList =
|
||||||
[ -- Requires the "func" type:
|
[ -- Requires the "func" type:
|
||||||
"SymbolicGradient"
|
"SymbolicGradient"
|
||||||
]
|
]
|
||||||
|
|
||||||
|
autogenModulesDir :: LocalBuildInfo -> FilePath
|
||||||
|
#if MIN_VERSION_Cabal(2,0,0)
|
||||||
|
autogenModulesDir = BuildPaths.autogenPackageModulesDir
|
||||||
|
#else
|
||||||
|
autogenModulesDir = BuildPaths.autogenModulesDir
|
||||||
|
#endif
|
||||||
|
|
|
@ -19,6 +19,7 @@
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
{-# LANGUAGE MonoLocalBinds #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
|
@ -453,10 +454,10 @@ infixr 5 /:/
|
||||||
--
|
--
|
||||||
-- using an enumeration of all the possible 'TensorType's.
|
-- using an enumeration of all the possible 'TensorType's.
|
||||||
type OneOf ts a
|
type OneOf ts a
|
||||||
-- Assert `TensorTypes ts` to make error messages a little better.
|
-- Assert `TensorTypes' ts` to make error messages a little better.
|
||||||
= (TensorType a, TensorTypes ts, NoneOf (AllTensorTypes \\ ts) a)
|
= (TensorType a, TensorTypes' ts, NoneOf (AllTensorTypes \\ ts) a)
|
||||||
|
|
||||||
type OneOfs ts as = (TensorTypes as, TensorTypes ts,
|
type OneOfs ts as = (TensorTypes as, TensorTypes' ts,
|
||||||
NoneOfs (AllTensorTypes \\ ts) as)
|
NoneOfs (AllTensorTypes \\ ts) as)
|
||||||
|
|
||||||
type family NoneOfs ts as :: Constraint where
|
type family NoneOfs ts as :: Constraint where
|
||||||
|
@ -486,6 +487,29 @@ instance TensorTypes '[] where
|
||||||
instance (TensorType t, TensorTypes ts) => TensorTypes (t ': ts) where
|
instance (TensorType t, TensorTypes ts) => TensorTypes (t ': ts) where
|
||||||
tensorTypes = TensorTypeProxy :/ tensorTypes
|
tensorTypes = TensorTypeProxy :/ tensorTypes
|
||||||
|
|
||||||
|
-- | A simpler version of the 'TensorTypes' class, that doesn't run
|
||||||
|
-- afoul of @-Wsimplifiable-class-constraints@.
|
||||||
|
--
|
||||||
|
-- In more detail: the constraint @OneOf '[Double, Float] a@ leads
|
||||||
|
-- to the constraint @TensorTypes' '[Double, Float]@, as a safety-check
|
||||||
|
-- to give better error messages. However, if @TensorTypes'@ were a class,
|
||||||
|
-- then GHC 8.2.1 would complain with the above warning unless @NoMonoBinds@
|
||||||
|
-- were enabled. So instead, we use a separate type family for this purpose.
|
||||||
|
-- For more details: https://ghc.haskell.org/trac/ghc/ticket/11948
|
||||||
|
type family TensorTypes' (ts :: [*]) :: Constraint where
|
||||||
|
-- Specialize this type family when `ts` is a long list, to avoid deeply
|
||||||
|
-- nested tuples of constraints. Works around a bug in ghc-8.0:
|
||||||
|
-- https://ghc.haskell.org/trac/ghc/ticket/12175
|
||||||
|
TensorTypes' (t1 ': t2 ': t3 ': t4 ': ts)
|
||||||
|
= (TensorType t1, TensorType t2, TensorType t3, TensorType t4
|
||||||
|
, TensorTypes' ts)
|
||||||
|
TensorTypes' (t1 ': t2 ': t3 ': ts)
|
||||||
|
= (TensorType t1, TensorType t2, TensorType t3, TensorTypes' ts)
|
||||||
|
TensorTypes' (t1 ': t2 ': ts)
|
||||||
|
= (TensorType t1, TensorType t2, TensorTypes' ts)
|
||||||
|
TensorTypes' (t ': ts) = (TensorType t, TensorTypes' ts)
|
||||||
|
TensorTypes' '[] = ()
|
||||||
|
|
||||||
-- | A constraint checking that two types are different.
|
-- | A constraint checking that two types are different.
|
||||||
type family a /= b :: Constraint where
|
type family a /= b :: Constraint where
|
||||||
a /= a = TypeError a ~ ExcludedCase
|
a /= a = TypeError a ~ ExcludedCase
|
||||||
|
@ -529,7 +553,7 @@ type family as \\ bs where
|
||||||
-- Assumes that @a@ and each of the elements of @ts@ are 'TensorType's.
|
-- Assumes that @a@ and each of the elements of @ts@ are 'TensorType's.
|
||||||
type family NoneOf ts a :: Constraint where
|
type family NoneOf ts a :: Constraint where
|
||||||
-- Specialize this type family when `ts` is a long list, to avoid deeply
|
-- Specialize this type family when `ts` is a long list, to avoid deeply
|
||||||
-- nested tuples of constraints. Works around a bug in ghc-8:
|
-- nested tuples of constraints. Works around a bug in ghc-8.0:
|
||||||
-- https://ghc.haskell.org/trac/ghc/ticket/12175
|
-- https://ghc.haskell.org/trac/ghc/ticket/12175
|
||||||
NoneOf (t1 ': t2 ': t3 ': t4 ': ts) a
|
NoneOf (t1 ': t2 ': t3 ': t4 ': ts) a
|
||||||
= (a /= t1, a /= t2, a /= t3, a /= t4, NoneOf ts a)
|
= (a /= t1, a /= t2, a /= t3, a /= t4, NoneOf ts a)
|
||||||
|
|
Loading…
Reference in a new issue