{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiWayIf #-}
module Hyrax.Abif
( Abif (..)
, Header (..)
, Directory (..)
, ElemType (..)
, getElemType
, describeElemType
) where
import Protolude
import qualified Data.ByteString.Lazy as BSL
data Abif = Abif { :: !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)
data = { 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)
data Directory = Directory { Directory -> Text
dTagName :: !Text
, Directory -> Int
dTagNum :: !Int
, Directory -> ElemType
dElemType :: !ElemType
, Directory -> Int
dElemTypeCode :: !Int
, Directory -> Text
dElemTypeDesc :: !Text
, Directory -> Int
dElemSize :: !Int
, Directory -> Int
dElemNum :: !Int
, Directory -> Int
dDataSize :: !Int
, Directory -> Int
dDataOffset :: !Int
, Directory -> ByteString
dData :: !BSL.ByteString
, Directory -> [Text]
dDataDebug :: ![Text]
} 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)
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)
getElemType :: Int -> ElemType
getElemType :: Int -> ElemType
getElemType e :: 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
describeElemType :: Int -> (ElemType, Text)
describeElemType :: Int -> (ElemType, Text)
describeElemType 1 = (ElemType
ElemByte, "byte")
describeElemType 2 = (ElemType
ElemChar, "char")
describeElemType 3 = (ElemType
ElemWord, "word")
describeElemType 4 = (ElemType
ElemShort, "short")
describeElemType 5 = (ElemType
ElemLong, "long")
describeElemType 7 = (ElemType
ElemFloat, "float")
describeElemType 8 = (ElemType
ElemDouble, "double")
describeElemType 10 = (ElemType
ElemDate, "date")
describeElemType 11 = (ElemType
ElemTime, "time")
describeElemType 18 = (ElemType
ElemPString, "pString")
describeElemType 19 = (ElemType
ElemCString, "cString")
describeElemType 12 = (ElemType
ElemThumb, "thumb")
describeElemType 13 = (ElemType
ElemBool, "bool")
describeElemType 6 = (ElemType
ElemRationalUnsupported, "rational (*unsupported*)")
describeElemType 9 = (ElemType
ElemBCDUnsupported, "BCD (*unsupported*)")
describeElemType 14 = (ElemType
ElemPointUnsupported, "point (*unsupported*)")
describeElemType 15 = (ElemType
ElemRectUnsupported, "rect (*unsupported*)")
describeElemType 16 = (ElemType
ElemVPointUnsupported, "vPoint (*unsupported*)")
describeElemType 17 = (ElemType
ElemVRectUnsupported, "vRect (*unsupported*)")
describeElemType 20 = (ElemType
ElemTagUnsupported, "Tag (*unsupported*)")
describeElemType 128 = (ElemType
ElemDeltaCompUnsupported, "deltaComp (*unsupported*)")
describeElemType 256 = (ElemType
ElemLZWCompUnsupported, "LZWComp (*unsupported*)")
describeElemType 384 = (ElemType
ElemCompressedDataUnsupported, "Compressed Data (*unsupported*)")
describeElemType 1023 = (ElemType
ElemRoot, "root")
describeElemType v :: Int
v = if Int
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 1024 then (ElemType
ElemCustom, "custom") else (ElemType
ElemUnknown, "unknown")