module Bio.Prelude (
module Bio.Base,
module BasePrelude,
module System.IO,
module System.Posix.Files,
module System.Posix.IO,
module System.Posix.Types,
#if !MIN_VERSION_base_prelude(1,1,0)
module Foreign.Storable,
module Foreign.Ptr,
module Foreign.ForeignPtr,
module Foreign.StablePtr,
#endif
Bytes, LazyBytes,
HashMap,
HashSet,
IntMap,
IntSet,
Text, LazyText,
Pair(..),
#ifndef __HADDOCK__
#ifdef __GLASGOW_HASKELL__
(:!:),
#endif
#endif
#if !MIN_VERSION_base(4,7,0)
isLeft,
isRight,
#endif
#if !MIN_VERSION_base(4,8,0)
first,
second,
#endif
decodeBytes,
encodeBytes,
Hashable(..),
Unpack(..),
fdPut,
fdPutLazy,
withFd
) where
import BasePrelude
#if MIN_VERSION_base(4,9,0)
hiding ( EOF, log1p, log1pexp, log1mexp, expm1 )
#elif MIN_VERSION_base(4,7,0)
hiding ( EOF )
#else
hiding ( EOF, block )
#endif
#if !MIN_VERSION_base(4,8,0)
import Control.Arrow ( first, second )
#endif
import Bio.Base
import Data.ByteString ( ByteString )
import Data.Text ( Text )
import Data.Hashable ( Hashable(..) )
import Data.HashMap.Strict ( HashMap )
import Data.HashSet ( HashSet )
import Data.IntMap ( IntMap )
import Data.IntSet ( IntSet )
import Data.Text.Encoding ( encodeUtf8, decodeUtf8With )
import Foreign.C.Error ( throwErrnoIf_ )
import System.IO ( hPrint, hPutStr, hPutStrLn, stderr, stdout, stdin )
import System.Posix.Files
import System.Posix.IO
import System.Posix.Types
#if !MIN_VERSION_base_prelude(1,1,0)
import Foreign.Storable
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.StablePtr
#endif
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Char8 as S
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
type Bytes = ByteString
type LazyBytes = BL.ByteString
type LazyText = TL.Text
infixl 2 :!:
data Pair a b = !a :!: !b deriving(Eq, Ord, Show, Read, Bounded, Ix)
#ifndef __HADDOCK__
#ifdef __GLASGOW_HASKELL__
type (:!:) = Pair
#endif
#endif
class Unpack s where unpack :: s -> String
instance Unpack ByteString where unpack = S.unpack
instance Unpack Text where unpack = T.unpack
instance Unpack String where unpack = id
#if !MIN_VERSION_base(4,7,0)
isLeft, isRight :: Either a b -> Bool
isLeft = either (const False) (const True)
isRight = either (const True) (const False)
#endif
fdPut :: Fd -> Bytes -> IO ()
fdPut fd s = B.unsafeUseAsCStringLen s $ \(p,l) ->
throwErrnoIf_ (/= fromIntegral l) "fdPut" $
fdWriteBuf fd (castPtr p) (fromIntegral l)
fdPutLazy :: Fd -> LazyBytes -> IO ()
fdPutLazy fd = mapM_ (fdPut fd) . BL.toChunks
withFd :: FilePath -> OpenMode -> Maybe FileMode -> OpenFileFlags
-> (Fd -> IO a) -> IO a
withFd fp om fm ff k = bracket (openFd fp om fm ff) closeFd k
decodeBytes :: Bytes -> Text
decodeBytes = decodeUtf8With (const $ fmap w2c)
encodeBytes :: Text -> Bytes
encodeBytes = encodeUtf8