{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiWayIf #-}

{-|
Module      : Hyax.Abif
Description : Core AB1 types 
Copyright   : (c) HyraxBio, 2018
License     : BSD3
Maintainer  : andre@hyraxbio.co.za, andre@andrevdm.com
Stability   : beta

This module contains the core types for working with AB1 files.

See

  * <https://github.com/hyraxbio/hyraxAbif/#readme Source code on github>

  * <http://www6.appliedbiosystems.com/support/software_community/ABIF_File_Format.pdf The ABIF spec>
-}
module Hyrax.Abif
    ( Abif (..)
    , Header (..)
    , Directory (..)
    , ElemType (..)
    , getElemType
    , describeElemType
    ) where

import           Protolude
import qualified Data.ByteString.Lazy as BSL


-- | A single ABIF
data Abif = Abif { Abif -> Header
aHeader :: !Header
                 , Abif -> Directory
aRootDir :: !Directory
                 , Abif -> [Directory]
aDirs :: ![Directory]
                 } deriving (Int -> Abif -> ShowS
[Abif] -> ShowS
Abif -> String
(Int -> Abif -> ShowS)
-> (Abif -> String) -> ([Abif] -> ShowS) -> Show Abif
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Abif] -> ShowS
$cshowList :: [Abif] -> ShowS
show :: Abif -> String
$cshow :: Abif -> String
showsPrec :: Int -> Abif -> ShowS
$cshowsPrec :: Int -> Abif -> ShowS
Show, Abif -> Abif -> Bool
(Abif -> Abif -> Bool) -> (Abif -> Abif -> Bool) -> Eq Abif
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Abif -> Abif -> Bool
$c/= :: Abif -> Abif -> Bool
== :: Abif -> Abif -> Bool
$c== :: Abif -> Abif -> Bool
Eq)


-- | ABIF header
data Header = Header { Header -> Text
hName :: !Text
                     , Header -> Int
hVersion :: !Int
                     } deriving (Int -> Header -> ShowS
[Header] -> ShowS
Header -> String
(Int -> Header -> ShowS)
-> (Header -> String) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Header] -> ShowS
$cshowList :: [Header] -> ShowS
show :: Header -> String
$cshow :: Header -> String
showsPrec :: Int -> Header -> ShowS
$cshowsPrec :: Int -> Header -> ShowS
Show, Header -> Header -> Bool
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c== :: Header -> Header -> Bool
Eq)

-- | ABIF directory entry.
-- The 'dData' field contains the data for the entry
data Directory = Directory { Directory -> Text
dTagName :: !Text        -- ^ Tag name
                           , Directory -> Int
dTagNum :: !Int          -- ^ Tag number, see e.g. how DATA entries use this
                           , Directory -> ElemType
dElemType :: !ElemType   -- ^ Type of an element
                           , Directory -> Int
dElemTypeCode :: !Int    -- ^ Integer value of 'dElemType'
                           , Directory -> Text
dElemTypeDesc :: !Text   -- ^ Description of 'dElemType'
                           , Directory -> Int
dElemSize :: !Int        -- ^ Size in bytes of each element
                           , Directory -> Int
dElemNum :: !Int         -- ^ Number of elements in the data. See the spec per data type. E.g. for a string this is the number of characters
                           , Directory -> Int
dDataSize :: !Int        -- ^ Number of bytes in the data
                           , Directory -> Int
dDataOffset :: !Int      -- ^ Offset of this directory entry's data in the file. For data that is four
                                                      --    bytes or less, the data itself is stored in this field.
                                                      --    This value will be recalculated when writing an ABIF so you do not need to manually set it.
                           , Directory -> ByteString
dData :: !BSL.ByteString -- ^ The entry's data
                           , Directory -> [Text]
dDataDebug :: ![Text]    -- ^ Optinal debug data, populated by 'Hyrax.Abif.Read.getDebug' when a ABIF is parsed
                           } deriving (Int -> Directory -> ShowS
[Directory] -> ShowS
Directory -> String
(Int -> Directory -> ShowS)
-> (Directory -> String)
-> ([Directory] -> ShowS)
-> Show Directory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Directory] -> ShowS
$cshowList :: [Directory] -> ShowS
show :: Directory -> String
$cshow :: Directory -> String
showsPrec :: Int -> Directory -> ShowS
$cshowsPrec :: Int -> Directory -> ShowS
Show, Directory -> Directory -> Bool
(Directory -> Directory -> Bool)
-> (Directory -> Directory -> Bool) -> Eq Directory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Directory -> Directory -> Bool
$c/= :: Directory -> Directory -> Bool
== :: Directory -> Directory -> Bool
$c== :: Directory -> Directory -> Bool
Eq)


-- | Type of the elements in a directory entry. See the spec for details on each type if required.
data ElemType = ElemUnknown
              | ElemCustom
              | ElemByte
              | ElemChar
              | ElemWord
              | ElemShort
              | ElemLong
              | ElemFloat
              | ElemDouble
              | ElemDate
              | ElemTime
              | ElemPString
              | ElemCString
              | ElemThumb
              | ElemBool
              | ElemRationalUnsupported
              | ElemBCDUnsupported
              | ElemPointUnsupported
              | ElemRectUnsupported
              | ElemVPointUnsupported
              | ElemVRectUnsupported
              | ElemTagUnsupported
              | ElemDeltaCompUnsupported
              | ElemLZWCompUnsupported
              | ElemCompressedDataUnsupported
              | ElemRoot
              deriving (Int -> ElemType -> ShowS
[ElemType] -> ShowS
ElemType -> String
(Int -> ElemType -> ShowS)
-> (ElemType -> String) -> ([ElemType] -> ShowS) -> Show ElemType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ElemType] -> ShowS
$cshowList :: [ElemType] -> ShowS
show :: ElemType -> String
$cshow :: ElemType -> String
showsPrec :: Int -> ElemType -> ShowS
$cshowsPrec :: Int -> ElemType -> ShowS
Show, ElemType -> ElemType -> Bool
(ElemType -> ElemType -> Bool)
-> (ElemType -> ElemType -> Bool) -> Eq ElemType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElemType -> ElemType -> Bool
$c/= :: ElemType -> ElemType -> Bool
== :: ElemType -> ElemType -> Bool
$c== :: ElemType -> ElemType -> Bool
Eq)


-- | Get an 'ElemType' from a elem type code
getElemType :: Int -> ElemType
getElemType :: Int -> ElemType
getElemType Int
e = (ElemType, Text) -> ElemType
forall a b. (a, b) -> a
fst ((ElemType, Text) -> ElemType) -> (ElemType, Text) -> ElemType
forall a b. (a -> b) -> a -> b
$ Int -> (ElemType, Text)
describeElemType Int
e

-- | Get the description for an 'ElemType'
describeElemType :: Int -> (ElemType, Text)
describeElemType :: Int -> (ElemType, Text)
describeElemType    Int
1 = (ElemType
ElemByte,    Text
"byte")
describeElemType    Int
2 = (ElemType
ElemChar,    Text
"char")
describeElemType    Int
3 = (ElemType
ElemWord,    Text
"word")
describeElemType    Int
4 = (ElemType
ElemShort,   Text
"short")
describeElemType    Int
5 = (ElemType
ElemLong,    Text
"long")
describeElemType    Int
7 = (ElemType
ElemFloat,   Text
"float")
describeElemType    Int
8 = (ElemType
ElemDouble,  Text
"double")
describeElemType   Int
10 = (ElemType
ElemDate,    Text
"date")
describeElemType   Int
11 = (ElemType
ElemTime,    Text
"time")
describeElemType   Int
18 = (ElemType
ElemPString, Text
"pString")
describeElemType   Int
19 = (ElemType
ElemCString, Text
"cString")
describeElemType   Int
12 = (ElemType
ElemThumb,   Text
"thumb")
describeElemType   Int
13 = (ElemType
ElemBool,    Text
"bool")
describeElemType    Int
6 = (ElemType
ElemRationalUnsupported,       Text
"rational (*unsupported*)")
describeElemType    Int
9 = (ElemType
ElemBCDUnsupported,            Text
"BCD (*unsupported*)")
describeElemType   Int
14 = (ElemType
ElemPointUnsupported,          Text
"point (*unsupported*)")
describeElemType   Int
15 = (ElemType
ElemRectUnsupported,           Text
"rect (*unsupported*)")
describeElemType   Int
16 = (ElemType
ElemVPointUnsupported,         Text
"vPoint (*unsupported*)")
describeElemType   Int
17 = (ElemType
ElemVRectUnsupported,          Text
"vRect (*unsupported*)")
describeElemType   Int
20 = (ElemType
ElemTagUnsupported,            Text
"Tag (*unsupported*)")
describeElemType  Int
128 = (ElemType
ElemDeltaCompUnsupported,      Text
"deltaComp (*unsupported*)")
describeElemType  Int
256 = (ElemType
ElemLZWCompUnsupported,        Text
"LZWComp (*unsupported*)")
describeElemType  Int
384 = (ElemType
ElemCompressedDataUnsupported, Text
"Compressed Data (*unsupported*)")
describeElemType Int
1023 = (ElemType
ElemRoot, Text
"root")
describeElemType    Int
v = if Int
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1024 then (ElemType
ElemCustom, Text
"custom") else (ElemType
ElemUnknown, Text
"unknown")