small updates, use BL and withFile
This commit is contained in:
parent
728df02fbd
commit
68540cc192
@ -9,7 +9,7 @@ module Main where
|
||||
import System.IO
|
||||
import Data.Default.Class
|
||||
import Data.List (genericLength)
|
||||
import qualified Data.ByteString.Lazy.Char8 as BSL
|
||||
import qualified Data.ByteString.Lazy.Char8 as BL
|
||||
|
||||
main = do
|
||||
texts <- lines <$> readFile "examples/reddit.csv"
|
||||
@ -21,9 +21,6 @@ module Main where
|
||||
let x0 = reverse . drop 1 . reverse $ indexes !! 0
|
||||
y0 = drop 1 $ indexes !! 0
|
||||
|
||||
print $ x0
|
||||
print $ y0
|
||||
|
||||
let xs = map (reverse . drop 1 . reverse) 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
|
||||
|
||||
saveRecurrent "recurrent.trained" (show newr) 512
|
||||
--writeFile "recurrent.trained" (show newr)
|
||||
|
||||
let newpredicted = predict newr x0
|
||||
print $ y0
|
||||
print $ 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"
|
||||
|
||||
saveRecurrent "recurrent.trained" (show newr) 512
|
||||
|
||||
saveRecurrent :: FilePath -> String -> Int -> IO ()
|
||||
saveRecurrent path str chunkSize = do
|
||||
handle <- openFile path AppendMode
|
||||
hSetBuffering handle NoBuffering
|
||||
loop handle str
|
||||
hClose handle
|
||||
let b = BL.pack str
|
||||
withFile path AppendMode (process b)
|
||||
where
|
||||
loop _ [] = return ()
|
||||
loop handle s = do
|
||||
hPutStr handle $ take chunkSize s
|
||||
hFlush handle
|
||||
putStr $ take chunkSize s
|
||||
loop handle $ drop chunkSize s
|
||||
process :: BL.ByteString -> Handle -> IO ()
|
||||
process b handle = do
|
||||
hSetBuffering handle NoBuffering
|
||||
loop handle b
|
||||
|
||||
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
5639
recurrent.trained
Normal file
File diff suppressed because it is too large
Load Diff
Loading…
Reference in New Issue
Block a user