small updates, use BL and withFile

This commit is contained in:
Mahdi Dibaiee 2016-10-26 12:48:04 +03:30
parent 728df02fbd
commit 68540cc192
2 changed files with 5657 additions and 23 deletions

View File

@ -9,7 +9,7 @@ module Main where
import System.IO import System.IO
import Data.Default.Class import Data.Default.Class
import Data.List (genericLength) import Data.List (genericLength)
import qualified Data.ByteString.Lazy.Char8 as BSL import qualified Data.ByteString.Lazy.Char8 as BL
main = do main = do
texts <- lines <$> readFile "examples/reddit.csv" texts <- lines <$> readFile "examples/reddit.csv"
@ -21,9 +21,6 @@ module Main where
let x0 = reverse . drop 1 . reverse $ indexes !! 0 let x0 = reverse . drop 1 . reverse $ indexes !! 0
y0 = drop 1 $ indexes !! 0 y0 = drop 1 $ indexes !! 0
print $ x0
print $ y0
let xs = map (reverse . drop 1 . reverse) indexes let xs = map (reverse . drop 1 . reverse) indexes
ys = map (drop 1) indexes ys = map (drop 1) indexes
@ -32,34 +29,32 @@ module Main where
let newr = sgd r (take 1 xs) (take 1 vys) 0.005 1 let newr = sgd r (take 1 xs) (take 1 vys) 0.005 1
saveRecurrent "recurrent.trained" (show newr) 512
--writeFile "recurrent.trained" (show newr)
let newpredicted = predict newr x0 let newpredicted = predict newr x0
print $ y0 print $ y0
print $ newpredicted print $ newpredicted
print $ loss (tov y0) (tov newpredicted) print $ loss (tov y0) (tov newpredicted)
{-let (dU, dV, dW) = backprop r x0 (fromList $ map fromIntegral y0)-}
{-print $ seq u "u"-}
{-print $ seq v "v"-}
{-print $ seq w "w"-}
--print $ dW
print "done" print "done"
saveRecurrent "recurrent.trained" (show newr) 512
saveRecurrent :: FilePath -> String -> Int -> IO () saveRecurrent :: FilePath -> String -> Int -> IO ()
saveRecurrent path str chunkSize = do saveRecurrent path str chunkSize = do
handle <- openFile path AppendMode let b = BL.pack str
hSetBuffering handle NoBuffering withFile path AppendMode (process b)
loop handle str
hClose handle
where where
loop _ [] = return () process :: BL.ByteString -> Handle -> IO ()
loop handle s = do process b handle = do
hPutStr handle $ take chunkSize s hSetBuffering handle NoBuffering
hFlush handle loop handle b
putStr $ take chunkSize s
loop handle $ drop chunkSize s loop :: Handle -> BL.ByteString -> IO ()
loop handle s
| s == BL.empty = return ()
| otherwise = do
let (current, next) = BL.splitAt (fromIntegral chunkSize) s
BL.hPutStr handle current
hFlush handle
loop handle next

5639
recurrent.trained Normal file

File diff suppressed because it is too large Load Diff