Fix 7.10 builds

This commit is contained in:
Huw Campbell 2017-01-14 21:36:13 +11:00
parent cc70f1fc0c
commit 20e7e483d7
4 changed files with 9 additions and 37 deletions

View File

@ -32,6 +32,7 @@ module Grenade.Core.Shape (
import Control.DeepSeq (NFData (..))
import Control.Monad.Random ( MonadRandom, getRandom )
import Data.Proxy
import Data.Singletons
import Data.Singletons.TypeLits
import Data.Vector.Storable ( Vector )

View File

@ -1,37 +0,0 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
module Grenade.Graph.Network (
Layer (..)
, UpdateLayer (..)
) where
import Control.Monad.Random (MonadRandom)
import Data.Singletons
import Data.Singletons.Prelude
import GHC.TypeLits
import Grenade.Core.Shape
import Grenade.Core.Network ( UpdateLayer (..), Layer (..) )
-- | Type of a DAG network
data Fin :: Nat -> * where
Fin0 :: Fin (n + 1)
FinS :: Fin n -> Fin (n + 1)
data Edge :: Nat -> * where
Edge :: Shape -> Fin n -> Edge n
data Node a n where
Node :: a -> [Edge n] -> Node a n

View File

@ -6,11 +6,16 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
-- GHC 7.10 doesn't see recurrent run functions as total.
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
module Grenade.Recurrent.Layers.BasicRecurrent (
BasicRecurrent (..)
, randomBasicRecurrent
) where
import Control.Monad.Random ( MonadRandom, getRandom )
import Data.Singletons.TypeLits

View File

@ -8,6 +8,9 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ViewPatterns #-}
-- GHC 7.10 doesn't see recurrent run functions as total.
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
module Grenade.Recurrent.Layers.LSTM (
LSTM (..)
, LSTMWeights (..)