Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Is it possible to assign a KnownNat at runtime?

I've being trying (unsuccessfully) to create an "object"* in haskell in runtime with its type defined at runtime using dependent types.

I was following this tutorial on dependent types and what they use to pass a value on runtime is a function that takes a Sing as a parameter and uses pattern matching on the value of Sing to obtain the number on runtime. But I don't have access to any Sing to pattern match.

I thought the code below could work, but what I get is actually pretty disappointing, the compiler tells me that n from the type definition for randomNetwork is not the same n that I captured in the type definition of SNat.

{-# LANGUAGE
    ScopedTypeVariables, TemplateHaskell, TypeFamilies, GADTs, KindSignatures,
    TypeOperators, FlexibleContexts, RankNTypes, UndecidableInstances,
    FlexibleInstances, InstanceSigs, DefaultSignatures, DataKinds,
    RecordWildCards, StandaloneDeriving, MultiParamTypeClasses #-}

module Main where

-- some imports to make the code below main work
import Control.Monad.Random
import GHC.TypeLits
import Data.List

--import Grenade
import Data.Singletons
import Data.Singletons.TypeLits

main = do
  let sizeHidden = toSing (20 :: Integer) :: SomeSing Nat

  net0 <- case sizeHidden of
            SomeSing (SNat :: Sing n) ->
              randomNetwork :: IO (Network '[ FullyConnected 75 n, FullyConnected n 1 ] '[ 'D1 75, 'D1 n, 'D1 1 ])
  --net0 <- randomNetwork :: IO (Network '[ FullyConnected 75 3, FullyConnected 3 1 ] '[ 'D1 75, 'D1 3, 'D1 1 ])
  print net0


-- from Grenade.Core.Network
data Network :: [*] -> [Shape] -> * where
    NNil  :: SingI i
          => Network '[] '[i]

    (:~>) :: (SingI i, SingI h, Layer x i h)
          => !x
          -> !(Network xs (h ': hs))
          -> Network (x ': xs) (i ': h ': hs)
infixr 5 :~>

instance Show (Network '[] '[i]) where
  show NNil = "NNil"
instance (Show x, Show (Network xs rs)) => Show (Network (x ': xs) (i ': rs)) where
  show (x :~> xs) = show x ++ "\n~>\n" ++ show xs

class CreatableNetwork (xs :: [*]) (ss :: [Shape]) where
  randomNetwork :: MonadRandom m => m (Network xs ss)

instance SingI i => CreatableNetwork '[] '[i] where
  randomNetwork = return NNil

instance (SingI i, SingI o, Layer x i o, CreatableNetwork xs (o ': rs)) => CreatableNetwork (x ': xs) (i ': o ': rs) where
  randomNetwork = (:~>) <$> createRandom <*> randomNetwork

-- from Grenade.Layers.FullyConnected
data FullyConnected i o = FullyConnected
                        !(FullyConnected' i o)   -- Neuron weights
                        !(FullyConnected' i o)   -- Neuron momentum

data FullyConnected' i o = FullyConnected'
                         !(R o)   -- Bias
                         !(L o i) -- Activations

instance Show (FullyConnected i o) where
  show FullyConnected {} = "FullyConnected"

instance (KnownNat i, KnownNat o) => UpdateLayer (FullyConnected i o) where
  type Gradient (FullyConnected i o) = (FullyConnected' i o)
  runUpdate = undefined
  createRandom = undefined

instance (KnownNat i, KnownNat o) => Layer (FullyConnected i o) ('D1 i) ('D1 o) where
  type Tape (FullyConnected i o) ('D1 i) ('D1 o) = S ('D1 i)
  runForwards  = undefined
  runBackwards = undefined

-- from Grenade.Core.Layer
class UpdateLayer x where
  type Gradient x :: *
  runUpdate       :: LearningParameters -> x -> Gradient x -> x
  createRandom    :: MonadRandom m => m x
  runUpdates      :: LearningParameters -> x -> [Gradient x] -> x
  runUpdates rate = foldl' (runUpdate rate)

class UpdateLayer x => Layer x (i :: Shape) (o :: Shape) where
  type Tape x i o :: *
  runForwards    :: x -> S i -> (Tape x i o, S o)
  runBackwards   :: x -> Tape x i o -> S o -> (Gradient x, S i)

-- from Grenade.Core.Shape
data Shape = D1 Nat

data S (n :: Shape) where
  S1D :: ( KnownNat len )
      => R len
      -> S ('D1 len)

deriving instance Show (S n)

instance KnownNat a => SingI ('D1 a) where
  sing = D1Sing sing

data instance Sing (n :: Shape) where
  D1Sing :: Sing a -> Sing ('D1 a)

-- from Grenade.Core.LearningParameters
data LearningParameters = LearningParameters {
    learningRate :: Double
  , learningMomentum :: Double
  , learningRegulariser :: Double
  } deriving (Eq, Show)

-- from Numeric.LinearAlgebra.Static
newtype Dim (n :: Nat) t = Dim t
  deriving (Show)
newtype R n = R (Dim n [Double])
  deriving (Show)
newtype L m n = L (Dim m (Dim n [[Double]]))

How could I define the size of the "hidden layer" on runtime (without constructing it by hand)? how could I use the value I captured in runtime at the type level?

Btw, this is the compiling error I get with the code above:

Prelude> :r
  net0 <- case sizeHidden of
            SomeSing (SNat :: KnownNat n => Sing n) -> randomNetwork :: IO (Network '[ FullyConnected 75 3, FullyConnected 3 1 ] '[ 'D1 75, 'D1 3, 'D1 1 ])
[1 of 1] Compiling Main             ( /home/helq/Downloads/NetworkOnRuntime.hs, interpreted )

/home/helq/Downloads/NetworkOnRuntime.hs:23:15: error:
    • Couldn't match type ‘a0’
                     with ‘Network
                             '[FullyConnected 75 a, FullyConnected a 1] '['D1 75, 'D1 a, 'D1 1]’
        because type variable ‘a’ would escape its scope
      This (rigid, skolem) type variable is bound by
        a pattern with constructor:
          SomeSing :: forall k k1 (k2 :: k1) (a :: k). Sing a -> SomeSing k,
        in a case alternative
        at /home/helq/Downloads/NetworkOnRuntime.hs:22:13-37
      Expected type: IO a0
        Actual type: IO
                       (Network
                          '[FullyConnected 75 a, FullyConnected a 1] '['D1 75, 'D1 a, 'D1 1])
    • In the expression:
          randomNetwork ::
            IO (Network '[FullyConnected 75 n, FullyConnected n 1] '[D1 75,
                                                                     D1 n,
                                                                     D1 1])
      In a case alternative:
          SomeSing (SNat :: Sing n)
            -> randomNetwork ::
                 IO (Network '[FullyConnected 75 n, FullyConnected n 1] '[D1 75,
                                                                          D1 n,
                                                                          D1 1])
      In a stmt of a 'do' block:
        net0 <- case sizeHidden of {
                  SomeSing (SNat :: Sing n)
                    -> randomNetwork ::
                         IO (Network '[FullyConnected 75 n, FullyConnected n 1] '[D1 75,
                                                                                  D1 n,
                                                                                  D1 1]) }

/home/helq/Downloads/NetworkOnRuntime.hs:25:3: error:
    • Ambiguous type variable ‘a0’ arising from a use of ‘print’
      prevents the constraint ‘(Show a0)’ from being solved.
      Relevant bindings include
        net0 :: a0 (bound at /home/helq/Downloads/NetworkOnRuntime.hs:21:3)
      Probable fix: use a type annotation to specify what ‘a0’ should be.
      These potential instances exist:
        instance (Show b, Show a) => Show (Either a b)
          -- Defined in ‘Data.Either’
        instance Show SomeNat -- Defined in ‘GHC.TypeLits’
        instance Show SomeSymbol -- Defined in ‘GHC.TypeLits’
        ...plus 31 others
        ...plus 170 instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In a stmt of a 'do' block: print net0
      In the expression:
        do { let sizeHidden = ...;
             net0 <- case sizeHidden of {
                       SomeSing (SNat :: Sing n)
                         -> randomNetwork ::
                              IO (Network '[FullyConnected 75 n, FullyConnected n 1] '[D1 75,
                                                                                       D1 n,
                                                                                       D1 1]) };
             print net0 }
      In an equation for ‘main’:
          main
            = do { let sizeHidden = ...;
                   net0 <- case sizeHidden of { SomeSing (SNat :: Sing n) -> ... };
                   print net0 }
Failed, modules loaded: none.

*: I know, we call them values (I think)

like image 251
helq Avatar asked Oct 01 '17 01:10

helq


1 Answers

Let's think about this line:

net0 <- case sizeHidden of
    SomeSing (SNat :: Sing n) ->
        randomNetwork :: IO (Network '[ FullyConnected 75 n, FullyConnected n 1 ] '[ 'D1 75, 'D1 n, 'D1 1 ])

What is the type of net0? It appears to be

Network '[ FullyConnected 75 n, FullyConnected n 1 ] '[ 'D1 75, 'D1 n, 'D1 1 ]

However, what is n? It's not in the environment, because the type environment of main is empty. And it's not universally quantified either. That's the problem, n can't refer to anything. You need to either do all your work with net0 inside the environment where n is bound1, as in

case sizeHidden of
   SomeSing (SNat :: Sing n) -> do
       net0 <- randomNetwork :: IO (Network '[ FullyConnected 75 n, FullyConnected n 1 ] '[ 'D1 75, 'D1 n, 'D1 1 ])
       print net0

or wrap net0 in its own existential:

data DogeNet = 
  forall n. KnownNat n => DogeNet (Network '[ FullyConnected 75 n, FullyConnected n 1 ]
                                           '[ 'D1 75, 'D1 n, 'D1 1 ])

instance Show DogeNet where    -- deriving can't handle existentials
    show (DogeNet n) = show n 

main = do
    ...
    net0 <- case sizeHidden of
        SomeSing (SNat :: Sing n) ->
            DogeNet <$> (randomNetwork 
                           :: IO (Network '[ FullyConnected 75 n, FullyConnected n 1 ]
                                          '[ 'D1 75, 'D1 n, 'D1 1 ]))
    print net0

randomNetwork still needs a type signature because we need to indicate that we really intend to use the n bound on the previous line, forcing us to write the network spec twice. But it can be cleaned up with the new TypeApplications extension:

            DogeNet @n <$> randomNetwork

1 This doesn't make things as impossible as it looks. You can still pass net0 to functions that are universally quantified in n. It just means that if you ever return a type involving a new type level number, you need to do it by CPS or use an existential like DogeNet.

like image 195
luqui Avatar answered Oct 18 '22 13:10

luqui