module Graphics.Helpers where
import Data.Binary.Get
import qualified Data.ByteString.Lazy as B
import Control.Monad (replicateM)
import Data.Char (chr, isDigit, ord)
hush :: Either a b -> Maybe b
hush :: forall a b. Either a b -> Maybe b
hush = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just
runEitherGet :: Get a -> B.ByteString -> Either String a
runEitherGet :: forall a. Get a -> ByteString -> Either String a
runEitherGet Get a
get ByteString
bs = case forall a.
Get a
-> ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
runGetOrFail Get a
get ByteString
bs of
Left (ByteString
_,ByteOffset
_,String
errorMsg) -> forall a b. a -> Either a b
Left String
errorMsg
Right (ByteString
_,ByteOffset
_,a
x) -> forall a b. b -> Either a b
Right a
x
runMaybeGet :: Get a -> B.ByteString -> Maybe a
runMaybeGet :: forall a. Get a -> ByteString -> Maybe a
runMaybeGet Get a
get = forall a b. Either a b -> Maybe b
hush forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Get a -> ByteString -> Either String a
runEitherGet Get a
get
getCharWhere :: (Char->Bool) -> Get Char
getCharWhere :: (Char -> Bool) -> Get Char
getCharWhere Char -> Bool
wher = do
Char
char <- Int -> Char
chr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
if Char -> Bool
wher Char
char
then forall (m :: * -> *) a. Monad m => a -> m a
return Char
char
else forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"no parse"
getDigit :: Get Char
getDigit :: Get Char
getDigit = (Char -> Bool) -> Get Char
getCharWhere Char -> Bool
isDigit
getCharValue :: Char -> Get Char
getCharValue :: Char -> Get Char
getCharValue Char
char = (Char -> Bool) -> Get Char
getCharWhere (forall a. Eq a => a -> a -> Bool
==Char
char)
readDigit :: Read a => Int -> Get a
readDigit :: forall a. Read a => Int -> Get a
readDigit Int
x = forall a. Read a => String -> a
read forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Int -> Get a -> Get [a]
count Int
x Get Char
getDigit
count :: Int -> Get a -> Get [a]
count :: forall a. Int -> Get a -> Get [a]
count = forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM
stringToByteString :: String -> B.ByteString
stringToByteString :: String -> ByteString
stringToByteString = [Word8] -> ByteString
B.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord)