{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Hyrax.Abif.Write
( createAbifBytes
, writeAbif
, putAbif
, putTextStr
, putHeader
, putDirectory
, mkHeader
, mkRoot
, mkData
, mkComment
, mkSampleName
, mkBaseOrder
, mkLane
, mkCalledBases
, mkMobilityFileName
, mkDyeSignalStrength
, mkPeakLocations
, addDirectory
, Base (..)
) where
import Protolude
import qualified Data.Text as Txt
import qualified Data.Text.Encoding as TxtE
import qualified Data.Binary as B
import qualified Data.Binary.Put as B
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import Hyrax.Abif
data Base = BaseA | BaseC | BaseG | BaseT
createAbifBytes :: Abif -> BSL.ByteString
createAbifBytes :: Abif -> ByteString
createAbifBytes ab1 :: Abif
ab1 =
Put -> ByteString
B.runPut (Abif -> Put
putAbif Abif
ab1)
writeAbif :: FilePath -> Abif -> IO ()
writeAbif :: FilePath -> Abif -> IO ()
writeAbif destPath :: FilePath
destPath ab1 :: Abif
ab1 = do
let b :: ByteString
b = Abif -> ByteString
createAbifBytes Abif
ab1
FilePath -> ByteString -> IO ()
BS.writeFile FilePath
destPath (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BSL.toStrict ByteString
b
putAbif :: Abif -> B.Put
putAbif :: Abif -> Put
putAbif (Abif header :: Header
header root :: Directory
root dirs :: [Directory]
dirs) = do
let dataSize :: Int
dataSize = (Int -> Int -> Int) -> Int -> [Int] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\acc :: Int
acc i :: Int
i -> if Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 4 then Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i else Int
acc) 0 ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ Directory -> Int
dDataSize (Directory -> Int) -> [Directory] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Directory]
dirs
Header -> Put
putHeader Header
header
let startDataOffset :: Int
startDataOffset = 128
Int -> Directory -> Put
putDirectory (Int
startDataOffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dataSize) (Directory -> Put) -> Directory -> Put
forall a b. (a -> b) -> a -> b
$ Directory
root { dDataSize :: Int
dDataSize = 28 Int -> Int -> Int
forall a. Num a => a -> a -> a
* [Directory] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Directory]
dirs
, dElemNum :: Int
dElemNum = [Directory] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Directory]
dirs
}
(Int16 -> Put) -> [Int16] -> Put
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Int16 -> Put
B.putInt16be ([Int16] -> Put) -> [Int16] -> Put
forall a b. (a -> b) -> a -> b
$ Int -> Int16 -> [Int16]
forall a. Int -> a -> [a]
replicate 47 0
(Directory -> Put) -> [Directory] -> Put
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (ByteString -> Put
B.putLazyByteString (ByteString -> Put)
-> (Directory -> ByteString) -> Directory -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Directory -> ByteString
dData) ([Directory] -> Put) -> [Directory] -> Put
forall a b. (a -> b) -> a -> b
$ (Directory -> Bool) -> [Directory] -> [Directory]
forall a. (a -> Bool) -> [a] -> [a]
filter (\d :: Directory
d -> Directory -> Int
dDataSize Directory
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 4) [Directory]
dirs
(Int -> Directory -> PutM Int) -> Int -> [Directory] -> Put
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m ()
foldM_ Int -> Directory -> PutM Int
writeDir Int
startDataOffset [Directory]
dirs
where
writeDir :: Int -> Directory -> PutM Int
writeDir offset :: Int
offset dir :: Directory
dir = do
Int -> Directory -> Put
putDirectory Int
offset Directory
dir
Int -> PutM Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int -> PutM Int) -> Int -> PutM Int
forall a b. (a -> b) -> a -> b
$ if Directory -> Int
dDataSize Directory
dir Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 4
then Int
offset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Directory -> Int
dDataSize Directory
dir
else Int
offset
putTextStr :: Text -> B.Put
putTextStr :: Text -> Put
putTextStr t :: Text
t = ByteString -> Put
B.putByteString (ByteString -> Put) -> ByteString -> Put
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TxtE.encodeUtf8 Text
t
putPStr :: Text -> B.Put
putPStr :: Text -> Put
putPStr t :: Text
t = do
Int8 -> Put
B.putInt8 (Int8 -> Put) -> (Int -> Int8) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Text -> Int
Txt.length Text
t
ByteString -> Put
B.putByteString (ByteString -> Put) -> ByteString -> Put
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TxtE.encodeUtf8 Text
t
putHeader :: Header -> B.Put
h :: Header
h = do
Text -> Put
putTextStr (Text -> Put) -> Text -> Put
forall a b. (a -> b) -> a -> b
$ Header -> Text
hName Header
h
Int16 -> Put
B.putInt16be (Int16 -> Put) -> (Int -> Int16) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Header -> Int
hVersion Header
h
putDirectory :: Int -> Directory -> B.Put
putDirectory :: Int -> Directory -> Put
putDirectory dirOffset :: Int
dirOffset d :: Directory
d = do
let name :: Text
name = Int -> Char -> Text -> Text
Txt.justifyLeft 4 ' ' (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> Text
Txt.take 4 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Directory -> Text
dTagName Directory
d
Text -> Put
putTextStr Text
name
Int32 -> Put
B.putInt32be (Int32 -> Put) -> (Int -> Int32) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Directory -> Int
dTagNum Directory
d
Int16 -> Put
B.putInt16be (Int16 -> Put) -> (Int -> Int16) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Directory -> Int
dElemTypeCode Directory
d
Int16 -> Put
B.putInt16be (Int16 -> Put) -> (Int -> Int16) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Directory -> Int
dElemSize Directory
d
Int32 -> Put
B.putInt32be (Int32 -> Put) -> (Int -> Int32) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Directory -> Int
dElemNum Directory
d
Int32 -> Put
B.putInt32be (Int32 -> Put) -> (Int -> Int32) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Directory -> Int
dDataSize Directory
d
if Directory -> Int
dDataSize Directory
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 4
then Int32 -> Put
B.putInt32be (Int32 -> Put) -> (Int -> Int32) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ Int
dirOffset
else ByteString -> Put
B.putLazyByteString (ByteString -> Put)
-> (ByteString -> ByteString) -> ByteString -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> ByteString -> ByteString
BSL.take 4 (ByteString -> Put) -> ByteString -> Put
forall a b. (a -> b) -> a -> b
$ Directory -> ByteString
dData Directory
d ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> "\0\0\0\0"
Int32 -> Put
B.putInt32be 0
mkHeader :: Header
=
$WHeader :: Text -> Int -> Header
Header { hName :: Text
hName = "ABIF"
, hVersion :: Int
hVersion = 101
}
mkRoot :: Directory
mkRoot :: Directory
mkRoot =
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "tdir"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 1023
, dElemTypeDesc :: Text
dElemTypeDesc = "root"
, dElemType :: ElemType
dElemType = ElemType
ElemRoot
, dElemSize :: Int
dElemSize = 28
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ""
, dDataSize :: Int
dDataSize = 0
, dElemNum :: Int
dElemNum = 0
}
mkComment :: Text -> Directory
comment' :: Text
comment' =
let comment :: ByteString
comment = Put -> ByteString
B.runPut (Put -> ByteString) -> (Text -> Put) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Put
putPStr (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
comment' in
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "CMNT"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 18
, dElemTypeDesc :: Text
dElemTypeDesc = "pString"
, dElemType :: ElemType
dElemType = ElemType
ElemPString
, dElemSize :: Int
dElemSize = 1
, dElemNum :: Int
dElemNum = 1
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ByteString
comment
, dDataSize :: Int
dDataSize = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BSL.length ByteString
comment)
}
mkSampleName :: Text -> Directory
mkSampleName :: Text -> Directory
mkSampleName sampleName' :: Text
sampleName' =
let sampleName :: ByteString
sampleName = Put -> ByteString
B.runPut (Put -> ByteString) -> (Text -> Put) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Put
putPStr (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
sampleName' in
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "SMPL"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 18
, dElemTypeDesc :: Text
dElemTypeDesc = "pString"
, dElemType :: ElemType
dElemType = ElemType
ElemPString
, dElemSize :: Int
dElemSize = 1
, dElemNum :: Int
dElemNum = 10
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ByteString
sampleName
, dDataSize :: Int
dDataSize = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BSL.length ByteString
sampleName)
}
mkBaseOrder :: Base -> Base -> Base -> Base -> Directory
mkBaseOrder :: Base -> Base -> Base -> Base -> Directory
mkBaseOrder w :: Base
w x :: Base
x y :: Base
y z :: Base
z =
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "FWO_"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 2
, dElemTypeDesc :: Text
dElemTypeDesc = "char"
, dElemType :: ElemType
dElemType = ElemType
ElemChar
, dElemSize :: Int
dElemSize = 1
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = Base -> ByteString
forall p. IsString p => Base -> p
getBase Base
w ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Base -> ByteString
forall p. IsString p => Base -> p
getBase Base
x ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Base -> ByteString
forall p. IsString p => Base -> p
getBase Base
y ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Base -> ByteString
forall p. IsString p => Base -> p
getBase Base
z
, dDataSize :: Int
dDataSize = 4
, dElemNum :: Int
dElemNum = 4
}
where
getBase :: Base -> p
getBase BaseA = "A"
getBase BaseC = "C"
getBase BaseG = "G"
getBase BaseT = "T"
mkLane :: Int16 -> Directory
mkLane :: Int16 -> Directory
mkLane lane :: Int16
lane =
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "LANE"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 4
, dElemTypeDesc :: Text
dElemTypeDesc = "short"
, dElemType :: ElemType
dElemType = ElemType
ElemShort
, dElemSize :: Int
dElemSize = 2
, dElemNum :: Int
dElemNum = 1
, dDataSize :: Int
dDataSize = 2
, dDataOffset :: Int
dDataOffset = 0
, dData :: ByteString
dData = Put -> ByteString
B.runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ Int16 -> Put
B.putInt16be Int16
lane
, dDataDebug :: [Text]
dDataDebug = []
}
mkCalledBases :: Text -> Directory
mkCalledBases :: Text -> Directory
mkCalledBases fasta :: Text
fasta =
let
generatedFastaLen :: Int
generatedFastaLen = Text -> Int
Txt.length Text
fasta
pbas :: ByteString
pbas = ByteString -> ByteString
BSL.fromStrict (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TxtE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
fasta
in
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "PBAS"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 2
, dElemTypeDesc :: Text
dElemTypeDesc = "char"
, dElemType :: ElemType
dElemType = ElemType
ElemChar
, dElemSize :: Int
dElemSize = 1
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ByteString
pbas
, dDataSize :: Int
dDataSize = Int
generatedFastaLen
, dElemNum :: Int
dElemNum = Int
generatedFastaLen
}
mkMobilityFileName :: Int -> Text -> Directory
mkMobilityFileName :: Int -> Text -> Directory
mkMobilityFileName tagNum :: Int
tagNum fileName :: Text
fileName =
let pdfm :: ByteString
pdfm = Put -> ByteString
B.runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> Put
putPStr Text
fileName in
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "PDMF"
, dTagNum :: Int
dTagNum = Int
tagNum
, dElemTypeCode :: Int
dElemTypeCode = 18
, dElemTypeDesc :: Text
dElemTypeDesc = "pString"
, dElemType :: ElemType
dElemType = ElemType
ElemPString
, dElemSize :: Int
dElemSize = 1
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ByteString
pdfm
, dDataSize :: Int
dDataSize = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BSL.length ByteString
pdfm)
, dElemNum :: Int
dElemNum = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BSL.length ByteString
pdfm)
}
mkDyeSignalStrength :: Int16 -> Int16 -> Int16 -> Int16 -> Directory
mkDyeSignalStrength :: Int16 -> Int16 -> Int16 -> Int16 -> Directory
mkDyeSignalStrength w :: Int16
w x :: Int16
x y :: Int16
y z :: Int16
z =
let sigStrength :: ByteString
sigStrength = Put -> ByteString
B.runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ do
Int16 -> Put
B.putInt16be Int16
w
Int16 -> Put
B.putInt16be Int16
x
Int16 -> Put
B.putInt16be Int16
y
Int16 -> Put
B.putInt16be Int16
z
in
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "S/N%"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 4
, dElemTypeDesc :: Text
dElemTypeDesc = "short"
, dElemType :: ElemType
dElemType = ElemType
ElemShort
, dElemSize :: Int
dElemSize = 2
, dElemNum :: Int
dElemNum = 4
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ByteString
sigStrength
, dDataSize :: Int
dDataSize = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BSL.length ByteString
sigStrength)
}
mkPeakLocations :: [Int16] -> Directory
mkPeakLocations :: [Int16] -> Directory
mkPeakLocations locs :: [Int16]
locs =
let peakLocations :: ByteString
peakLocations = Put -> ByteString
B.runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ (Int16 -> Put) -> [Int16] -> Put
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Int16 -> Put
B.putInt16be [Int16]
locs in
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "PLOC"
, dTagNum :: Int
dTagNum = 1
, dElemTypeCode :: Int
dElemTypeCode = 4
, dElemTypeDesc :: Text
dElemTypeDesc = "short"
, dElemType :: ElemType
dElemType = ElemType
ElemShort
, dElemSize :: Int
dElemSize = 2
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ByteString
peakLocations
, dDataSize :: Int
dDataSize = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> Int64 -> Int
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
BSL.length ByteString
peakLocations
, dElemNum :: Int
dElemNum = [Int16] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int16]
locs
}
mkData :: Int -> [Int16] -> Directory
mkData :: Int -> [Int16] -> Directory
mkData tagNum :: Int
tagNum ds :: [Int16]
ds =
let ds' :: ByteString
ds' = Put -> ByteString
B.runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ (Int16 -> Put) -> [Int16] -> Put
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Int16 -> Put
B.putInt16be [Int16]
ds in
$WDirectory :: Text
-> Int
-> ElemType
-> Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> [Text]
-> Directory
Directory { dTagName :: Text
dTagName = "DATA"
, dTagNum :: Int
dTagNum = Int
tagNum
, dElemTypeCode :: Int
dElemTypeCode = 4
, dElemTypeDesc :: Text
dElemTypeDesc = "short"
, dElemType :: ElemType
dElemType = ElemType
ElemShort
, dElemSize :: Int
dElemSize = 2
, dDataOffset :: Int
dDataOffset = 0
, dDataDebug :: [Text]
dDataDebug = []
, dData :: ByteString
dData = ByteString
ds'
, dDataSize :: Int
dDataSize = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BSL.length ByteString
ds')
, dElemNum :: Int
dElemNum = [Int16] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int16]
ds
}
addDirectory :: Abif -> Directory -> Abif
addDirectory :: Abif -> Directory -> Abif
addDirectory abif :: Abif
abif dir :: Directory
dir =
Abif
abif { aDirs :: [Directory]
aDirs = Abif -> [Directory]
aDirs Abif
abif [Directory] -> [Directory] -> [Directory]
forall a. Semigroup a => a -> a -> a
<> [Directory
dir] }