2013-03-09 6 views
6

Desidero implementare un algoritmo di programmazione dinamica polimorfico nel tipo di partitura; Ecco una versione 1D semplificata senza condizioni limite:Rivisitazione di STUArray polimorfi con tipi di vincoli

{-# LANGUAGE ConstraintKinds, FlexibleContexts, RankNTypes, ScopedTypeVariables #-} 

import Control.Monad 
import Control.Monad.ST.Strict 
import Data.Array.ST 
import Data.Array.Unboxed 

dynamicProgrammingSTU 
    :: forall e i . (
    IArray UArray e, 
    forall s. MArray (STUArray s) e (ST s), 
    Ix i 
) 
    => (forall m . Monad m => (i -> m e) -> (i -> m e)) 
    -> (i, i) 
    -> (i -> e) 
dynamicProgrammingSTU prog bnds = (arr !) where 
    arr :: UArray i e 
    arr = runSTUArray resultArrayST 

    resultArrayST :: forall s . ST s (STUArray s i e) 
    resultArrayST = do 
    marr <- newArray_ bnds 
    forM_ (range bnds) $ \i -> do 
     result <- prog (readArray marr) i 
     writeArray marr i result 
    return marr 

Il vincolo non funziona;

Could not deduce (MArray (STUArray s) e (ST s)) 
     arising from a use of `newArray_' 
    from the context (IArray UArray e, 
         forall s. MArray (STUArray s) e (ST s), 
         Ix i) 
     bound by the type signature for 
       dynamicProgrammingSTU :: (IArray UArray e, 
              forall s. MArray (STUArray s) e (ST s 
), Ix i) => 
              (forall (m :: * -> *). Monad m => (i - 
> m e) -> i -> m e) 
              -> (i, i) -> i -> e 
     at example2.hs:(17,1)-(27,15) 
    Possible fix: 
     add (MArray (STUArray s) e (ST s)) to the context of 
     the type signature for resultArrayST :: ST s (STUArray s i e) 
     or the type signature for 
      dynamicProgrammingSTU :: (IArray UArray e, 
             forall s. MArray (STUArray s) e (ST s), I 
x i) => 
             (forall (m :: * -> *). Monad m => (i -> m 
e) -> i -> m e) 
             -> (i, i) -> i -> e 
     or add an instance declaration for (MArray (STUArray s) e (ST s)) 
    In a stmt of a 'do' block: marr <- newArray_ bnds 
    In the expression: 
     do { marr <- newArray_ bnds; 
      forM_ (range bnds) $ \ i -> do { ... }; 
      return marr } 
    In an equation for `resultArrayST': 
     resultArrayST 
      = do { marr <- newArray_ bnds; 
       forM_ (range bnds) $ \ i -> ...; 
       return marr } 
Failed, modules loaded: none. 

Per riepilogare, Could not deduce (MArray (STUArray s) e (ST s)) from the context forall s. MArray (STUArray s) e (ST s i). Si noti che aggiungendo il vincolo a resultArrayST è sufficiente trasferire il problema a runSTUArray.

Io attualmente a conoscenza di quattro soluzioni imperfetti:

  1. Evitando il problema con boxed STArray s o semplicemente non monadici Array s, magari utilizzando seq e bang modelli per alleviare i problemi di memoria che ne derivano.
  2. Interruzione del sistema di tipi con unsafeFreeze e unsafePerformIO, per il quale il vincolo dannoso MArray IOUArray e IO funziona correttamente.
  3. This soluzione a un problema simile utilizzando un typeclass e le istanze di scrittura per ogni tipo 'Unboxable'.
  4. This uno utilizza le regole di riscrittura GHC per selezionare una funzione diversa per ogni tipo (e una versione generica STArray).

Tuttavia, mi sto chiedendo questa domanda nella speranza che estensioni del linguaggio moderni, come ConstraintKinds può permettere di esprimere l'intento del mio codice originale di forall s. MArray (STUArray s) e (ST s).

+1

ghc-7.6.1 dice "predicato malformato" per tutti i s. MArray (STUArray s) e (ST s) ''', che per me ha più senso. –

+0

Se la funzione 'prog' è monadica solo per le prestazioni, penso che la tua p. 1 (calcoli puri con probabili schemi di scoppio) sarebbe il minimo dei mali. – leventov

risposta

1

Data la leggendaria disponibilità della comunità Haskell, la mancanza di una risposta a questo punto è una forte indicazione che non esiste una buona soluzione nell'attuale sistema di tipi.

Ho già delineato le soluzioni difettose nella domanda, quindi pubblicherò solo una versione completa del mio esempio. Questo è fondamentalmente quello che ho usato per risolvere la maggior parte dei problemi di allineamento su Rosalind:

{-# LANGUAGE FlexibleContexts, RankNTypes, ScopedTypeVariables #-} 

import Control.Applicative 
import Control.Monad 
import Control.Monad.ST 
import Data.Maybe 

import Data.Array.ST 
import Data.Array.Unboxed 

class IArray UArray e => Unboxable e where 
    newSTUArray_ :: forall s i. Ix i => (i, i) -> ST s (STUArray s i e) 
    readSTUArray :: forall s i. Ix i => STUArray s i e -> i -> ST s e 
    writeSTUArray :: forall s i. Ix i => STUArray s i e -> i -> e -> ST s() 


instance Unboxable Bool where 
    newSTUArray_ = newArray_ 
    readSTUArray = readArray 
    writeSTUArray = writeArray 

instance Unboxable Double where 
    newSTUArray_ = newArray_ 
    readSTUArray = readArray 
    writeSTUArray = writeArray 
{- 
Same for Char, Float, (Int|Word)(|8|16|32|64)... 
-} 

{-# INLINE dynamicProgramming2DSTU #-} 
dynamicProgramming2DSTU 
    :: forall e i j . (
    Unboxable e, 
    Ix i, 
    Ix j, 
    Enum i, 
    Enum j 
) 
    => (forall m . (Monad m, Applicative m) => (i -> j -> m e) -> (i -> j -> m e)) 
    -> (i -> j -> Maybe e) 
    -> (i, i) 
    -> (j, j) 
    -> (i -> j -> e) 
dynamicProgramming2DSTU program boundaryConditions (xl, xh) (yl, yh) = arrayLookup where 
    arrayLookup :: i -> j -> e 
    arrayLookup xi yj = fromMaybe (resultArray ! (xi, yj)) $ boundaryConditions xi yj 

    arrB :: ((i, j), (i, j)) 
    arrB = ((xl, yl), (xh, yh)) 

    resultArray :: UArray (i, j) e 
    resultArray = runSTUArray resultArrayST 

    resultArrayST :: forall s. ST s (STUArray s (i, j) e) 
    resultArrayST = do 
    arr <- newSTUArray_ arrB 
    let acc xi yj = maybe (readSTUArray arr (xi, yj)) return $ boundaryConditions xi yj 

    forM_ [xl..xh] $ \xi -> do 
     forM_ [yl..yh] $ \yj -> do 
     result <- program acc xi yj 
     writeSTUArray arr (xi, yj) result 

    return arr 
Problemi correlati