2012-09-11 3 views
9

Ho un semplice test runner per il bug che è nel mio modulo OpenPGP https://github.com/singpolyma/OpenPGP-Haskell/blob/master/Data/OpenPGP.hs:Perché questo codice si comporta diversamente con le optomisations attivate o disattivate?

module Main where 

import Data.OpenPGP 
import Data.Binary (encode, decode) 

packet = EmbeddedSignaturePacket (signaturePacket 2 168 ECDSA SHA256 [] [SignatureCreationTimePacket 1013401916,IssuerPacket "36FE856F4219F1C7"] 48065 [MPI 4,MPI 11,MPI 60,MPI 69,MPI 37,MPI 33,MPI 18,MPI 72,MPI 41,MPI 36,MPI 43,MPI 41,MPI 53,MPI 9,MPI 53,MPI 35,MPI 3,MPI 40,MPI 14,MPI 79,MPI 1,MPI 4,MPI 51,MPI 23,MPI 62,MPI 62,MPI 62,MPI 7,MPI 68,MPI 51,MPI 13,MPI 49,MPI 8,MPI 64,MPI 32,MPI 50,MPI 59,MPI 17,MPI 43,MPI 12,MPI 67,MPI 5,MPI 67,MPI 5,MPI 25,MPI 63,MPI 0,MPI 53,MPI 2,MPI 36,MPI 83,MPI 39,MPI 54,MPI 65,MPI 54,MPI 35,MPI 62,MPI 63,MPI 26,MPI 4,MPI 82,MPI 57,MPI 85,MPI 71,MPI 43,MPI 77]) 

main = print $ decode (encode packet) == packet 

Se si compila questo (su GHC 7.4.1) con:

ghc -O0 -fforce-recomp --make t.hs 

Esso funziona come previsto (vale a dire, la stampa True), ma se si compila in questo modo:

ghc -O1 -fforce-recomp --make t.hs 

o questo:

ghc -O2 -fforce-recomp --make t.hs 

Stampa False.

Non sto usando alcuna estensione (eccetto un uso banale di CPP) o chiamate di basso livello o non sicure, e il comportamento dovrebbe provenire dalla mia libreria e non da una dipendenza, poiché è solo il mio codice che viene ricompilato qui .

+5

Posso riprodurre questo errore in GHC 7.4.2 –

+1

Stai usando il binario o il cereale quando osservi questo errore? –

risposta

5

Si tratta di un errore nel codice. Considerare

MPI 63,MPI 0,MPI 53 
     ^^^^^ 

e

instance BINARY_CLASS MPI where 
    put (MPI i) = do 
     put (((fromIntegral . B.length $ bytes) - 1) * 8 
       + floor (logBase (2::Double) $ fromIntegral (bytes `B.index` 0)) 
        ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 
       + 1 :: Word16) 
    putSomeByteString bytes 
    where 
    bytes = if B.null bytes' then B.singleton 0 else bytes' 
    bytes' = B.reverse $ B.unfoldr (\x -> 
        if x == 0 then Nothing else 
          Just (fromIntegral x, x `shiftR` 8) 
      ) (assertProp (>=0) i) 

Ora, se noi codificare MPI 0, bytes' è vuota, quindi bytes = B.singleton 0 e quindi bytes `B.index` 0 è 0.

Ma logBase 2 0 è -Infinity, e floor è solo ben definito per valori finiti (all'interno dell'intervallo del tipo di destinazione).

Durante la compilazione senza ottimizzazioni, floor utilizza il modello di bit tramite decodeFloat. Quindi floor (logBase 2 0) restituisce 0 per tutti i tipi di interi con larghezza fissa standard.

Con le ottimizzazioni, una regola di riscrittura è attiva e floor utilizza il primop double2Int#, che restituisce tutto ciò che l'hardware esegue, su x86 risp. x86-64, che è minBound :: Int, per quanto ne so, indipendentemente dal pattern di bit.Il codice rilevante è

floorDoubleInt :: Double -> Int 
floorDoubleInt (D# x) = 
    case double2Int# x of 
     n | x <## int2Double# n -> I# (n -# 1#) 
     | otherwise    -> I# n 

e, naturalmente, -Infinity < int2Double minBound, quindi il valore diventa minBound - 1, che di solito è maxBound.

Naturalmente che provoca un risultato errato, dato che ora la "lunghezza" cioè put per MPI 0 diventa 0, e 0 byte mettere dopo il campo "lunghezza" viene interpretato come parte della "lunghezza" del prossimo MPI .

+0

Grazie! Non mi sarei mai aspettato che il comportamento di 'floor' cambiasse con' -O', ma hai ragione che avevo comunque un bug nelle mie supposizioni. – singpolyma

+1

Esistono alcuni punti in cui le regole di riscrittura modificano il comportamento. Principalmente quando non c'è comunque un risultato corretto, come con valori fuori range per 'floor' et al. Ma a volte anche in luoghi con risultati significativi, ad es. '(realToFrac :: Float -> Double) (0/0)' produce '-5.104235503814077e38' senza ottimizzazioni,' NaN' con ottimizzazioni. Il rapporto sulla lingua dice 'realToFrac = fromRational. toRational', che produce il primo. Dato che 'Rational' non può gestire veramente' NaN' e infiniti, non c'è un buon modo per trattarli in quella conversione e sono sbalorditi. Il primop li conserva. –

+0

Le cose sono sempre molto più divertenti quando è coinvolto NaN ... –

5

Il problema è correlato all'istanza BINARY_CLASS per MPI. Se cambio

main = do 
    print packet 
    print (decode (encode packet) :: SignatureSubpacket) 
    print $ decode (encode packet) == packet 

vedo l'uscita (compilato con -O2)

EmbeddedSignaturePacket (SignaturePacket {version = 2, signature_type = 168, key_algorithm = ECDSA, hash_algorithm = SHA256, hashed_subpackets = [], unhashed_subpackets = [SignatureCreationTimePacket 1013401916,IssuerPacket "36FE856F4219F1C7"], hash_head = 48065, signature = [MPI 4,MPI 11,MPI 60,MPI 69,MPI 37,MPI 33,MPI 18,MPI 72,MPI 41,MPI 36,MPI 43,MPI 41,MPI 53,MPI 9,MPI 53,MPI 35,MPI 3,MPI 40,MPI 14,MPI 79,MPI 1,MPI 4,MPI 51,MPI 23,MPI 62,MPI 62,MPI 62,MPI 7,MPI 68,MPI 51,MPI 13,MPI 49,MPI 8,MPI 64,MPI 32,MPI 50,MPI 59,MPI 17,MPI 43,MPI 12,MPI 67,MPI 5,MPI 67,MPI 5,MPI 25,MPI 63,MPI 0,MPI 53,MPI 2,MPI 36,MPI 83,MPI 39,MPI 54,MPI 65,MPI 54,MPI 35,MPI 62,MPI 63,MPI 26,MPI 4,MPI 82,MPI 57,MPI 85,MPI 71,MPI 43,MPI 77], trailer = Chunk "\168" (Chunk "<gI<" Empty)}) 
EmbeddedSignaturePacket (SignaturePacket {version = 2, signature_type = 168, key_algorithm = ECDSA, hash_algorithm = SHA256, hashed_subpackets = [], unhashed_subpackets = [SignatureCreationTimePacket 1013401916,IssuerPacket "36FE856F4219F1C7"], hash_head = 48065, signature = [MPI 4,MPI 11,MPI 60,MPI 69,MPI 37,MPI 33,MPI 18,MPI 72,MPI 41,MPI 36,MPI 43,MPI 41,MPI 53,MPI 9,MPI 53,MPI 35,MPI 3,MPI 40,MPI 14,MPI 79,MPI 1,MPI 4,MPI 51,MPI 23,MPI 62,MPI 62,MPI 62,MPI 7,MPI 68,MPI 51,MPI 13,MPI 49,MPI 8,MPI 64,MPI 32,MPI 50,MPI 59,MPI 17,MPI 43,MPI 12,MPI 67,MPI 5,MPI 67,MPI 5,MPI 25,MPI 63,MPI 0,MPI 0,MPI 339782829898145924110968965855122255180100961470274369007196973863828909184332476115285611703086303618816635857833592912611149], trailer = Chunk "\168" (Chunk "<gI<" Empty)}) 

Cambiare l'istanza MPI per questo più semplice implementazione:

newtype MPI = MPI Integer deriving (Show, Read, Eq, Ord) 
instance BINARY_CLASS MPI where 
    put (MPI i) = do 
    put (fromIntegral $ B.length bytes :: Word16) 
    putSomeByteString bytes 
    where 
    bytes = if B.null bytes' then B.singleton 0 else bytes' 
    bytes' = B.pack . map (read . (:[])) $ show i 
    get = do 
    length <- fmap fromIntegral (get :: Get Word16) 
    bytes <- getSomeByteString length 
    return (MPI $ read $ concatMap show $ B.unpack bytes) 

risolve il problema.

Ci sono alcune cose che potrebbero essere la fonte del problema. È possibile che il tuo codice sia corretto (non ho controllato questo in un modo o nell'altro), nel qual caso GHC sta eseguendo alcune trasformazioni non valide che portano a un overflow/underflow da qualche parte. È anche possibile che il tuo codice stia facendo qualcosa di sbagliato che è esposto solo a determinate ottimizzazioni.