Remove IO UUID functions.
This commit is contained in:
parent
8b144db6e5
commit
c9e67163fd
2 changed files with 2 additions and 17 deletions
|
@ -45,7 +45,6 @@ module Text.Pandoc.Free ( PandocActionF(..)
|
||||||
, getDefaultReferenceODT
|
, getDefaultReferenceODT
|
||||||
, newStdGen
|
, newStdGen
|
||||||
, newUniqueHash
|
, newUniqueHash
|
||||||
, newUUID
|
|
||||||
, readFileStrict
|
, readFileStrict
|
||||||
, readFileLazy
|
, readFileLazy
|
||||||
, readFileUTF8
|
, readFileUTF8
|
||||||
|
@ -81,8 +80,6 @@ import qualified Data.ByteString.Lazy as BL
|
||||||
import Control.Monad.Free
|
import Control.Monad.Free
|
||||||
import qualified Control.Exception as E
|
import qualified Control.Exception as E
|
||||||
import qualified System.Environment as IO (lookupEnv)
|
import qualified System.Environment as IO (lookupEnv)
|
||||||
import Text.Pandoc.UUID
|
|
||||||
import qualified Text.Pandoc.UUID as IO (getRandomUUID)
|
|
||||||
import qualified Text.Pandoc.UTF8 as UTF8 (readFile, toString)
|
import qualified Text.Pandoc.UTF8 as UTF8 (readFile, toString)
|
||||||
import System.FilePath.Glob (match, compile)
|
import System.FilePath.Glob (match, compile)
|
||||||
import System.FilePath ((</>))
|
import System.FilePath ((</>))
|
||||||
|
@ -100,7 +97,6 @@ data PandocActionF nxt =
|
||||||
| GetDefaultReferenceODT (Maybe FilePath) (Archive -> nxt)
|
| GetDefaultReferenceODT (Maybe FilePath) (Archive -> nxt)
|
||||||
| NewStdGen (StdGen -> nxt)
|
| NewStdGen (StdGen -> nxt)
|
||||||
| NewUniqueHash (Int -> nxt)
|
| NewUniqueHash (Int -> nxt)
|
||||||
| NewUUID (UUID -> nxt)
|
|
||||||
| ReadFileStrict FilePath (B.ByteString -> nxt)
|
| ReadFileStrict FilePath (B.ByteString -> nxt)
|
||||||
| ReadFileLazy FilePath (BL.ByteString -> nxt)
|
| ReadFileLazy FilePath (BL.ByteString -> nxt)
|
||||||
| ReadFileUTF8 FilePath (String -> nxt)
|
| ReadFileUTF8 FilePath (String -> nxt)
|
||||||
|
@ -137,9 +133,6 @@ newStdGen = liftF $ NewStdGen id
|
||||||
newUniqueHash :: PandocAction Int
|
newUniqueHash :: PandocAction Int
|
||||||
newUniqueHash = liftF $ NewUniqueHash id
|
newUniqueHash = liftF $ NewUniqueHash id
|
||||||
|
|
||||||
newUUID :: PandocAction UUID
|
|
||||||
newUUID = liftF $ NewUUID id
|
|
||||||
|
|
||||||
readFileStrict :: FilePath -> PandocAction B.ByteString
|
readFileStrict :: FilePath -> PandocAction B.ByteString
|
||||||
readFileStrict fp = liftF $ ReadFileStrict fp id
|
readFileStrict fp = liftF $ ReadFileStrict fp id
|
||||||
|
|
||||||
|
@ -183,7 +176,6 @@ runIO (Free (GetDefaultReferenceODT mfp f)) =
|
||||||
IO.getDefaultReferenceODT mfp >>= runIO . f
|
IO.getDefaultReferenceODT mfp >>= runIO . f
|
||||||
runIO (Free (NewStdGen f)) = IO.newStdGen >>= runIO . f
|
runIO (Free (NewStdGen f)) = IO.newStdGen >>= runIO . f
|
||||||
runIO (Free (NewUniqueHash f)) = hashUnique <$> IO.newUnique >>= runIO . f
|
runIO (Free (NewUniqueHash f)) = hashUnique <$> IO.newUnique >>= runIO . f
|
||||||
runIO (Free (NewUUID f)) = IO.getRandomUUID >>= runIO . f
|
|
||||||
runIO (Free (ReadFileStrict fp f)) = B.readFile fp >>= runIO . f
|
runIO (Free (ReadFileStrict fp f)) = B.readFile fp >>= runIO . f
|
||||||
runIO (Free (ReadFileLazy fp f)) = BL.readFile fp >>= runIO . f
|
runIO (Free (ReadFileLazy fp f)) = BL.readFile fp >>= runIO . f
|
||||||
runIO (Free (ReadFileUTF8 fp f)) = UTF8.readFile fp >>= runIO . f
|
runIO (Free (ReadFileUTF8 fp f)) = UTF8.readFile fp >>= runIO . f
|
||||||
|
@ -250,14 +242,6 @@ runTest (Free (NewUniqueHash f)) = do
|
||||||
modify $ \st -> st { stUniqStore = us }
|
modify $ \st -> st { stUniqStore = us }
|
||||||
return u >>= runTest . f
|
return u >>= runTest . f
|
||||||
_ -> M.fail "uniq store ran out of elements"
|
_ -> M.fail "uniq store ran out of elements"
|
||||||
runTest (Free (NewUUID f)) = do
|
|
||||||
word8s <- gets stWord8Store
|
|
||||||
case word8s of
|
|
||||||
-- note we use f' because f is a param of the function
|
|
||||||
a:b:c:d:e:f':g:h:i:j:k:l:m:n:o:p:remaining -> do
|
|
||||||
modify $ \st -> st { stWord8Store = remaining }
|
|
||||||
return (UUID a b c d e f' g h i j k l m n o p) >>= runTest . f
|
|
||||||
_ -> M.fail "word8 supply was not infinite"
|
|
||||||
runTest (Free (ReadFileStrict fp f)) = do
|
runTest (Free (ReadFileStrict fp f)) = do
|
||||||
fps <- asks envFiles
|
fps <- asks envFiles
|
||||||
case lookup fp fps of
|
case lookup fp fps of
|
||||||
|
|
|
@ -53,6 +53,7 @@ import Text.Pandoc.Options ( WriterOptions(..)
|
||||||
, ObfuscationMethod(NoObfuscation) )
|
, ObfuscationMethod(NoObfuscation) )
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Walk (walk, walkM, query)
|
import Text.Pandoc.Walk (walk, walkM, query)
|
||||||
|
import Text.Pandoc.UUID (getUUID)
|
||||||
import Control.Monad.State (modify, get, gets, State, StateT, put, evalState, evalStateT, lift)
|
import Control.Monad.State (modify, get, gets, State, StateT, put, evalState, evalStateT, lift)
|
||||||
import Control.Monad (mplus, when)
|
import Control.Monad (mplus, when)
|
||||||
import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
|
import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
|
||||||
|
@ -152,7 +153,7 @@ getEPUBMetadata opts meta = do
|
||||||
let addIdentifier m =
|
let addIdentifier m =
|
||||||
if null (epubIdentifier m)
|
if null (epubIdentifier m)
|
||||||
then do
|
then do
|
||||||
randomId <- fmap show (lift P.newUUID)
|
randomId <- (show . getUUID) <$> lift P.newStdGen
|
||||||
return $ m{ epubIdentifier = [Identifier randomId Nothing] }
|
return $ m{ epubIdentifier = [Identifier randomId Nothing] }
|
||||||
else return m
|
else return m
|
||||||
let addLanguage m =
|
let addLanguage m =
|
||||||
|
|
Loading…
Reference in a new issue