aboutsummaryrefslogtreecommitdiffhomepage
path: root/scaffolder/src/Text/Edifact/BundleReader/Extractor.hs
blob: f4be7e9ec24956dfc7848ec51f6a254e705ed02d (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
{-# LANGUAGE NamedFieldPuns    #-}
{-# LANGUAGE OverloadedStrings #-}

module Text.Edifact.BundleReader.Extractor
  ( FileContents(..)
  , readZip
  ) where

import           Text.Edifact.Scaffolder.Commons (Revision (..))

import           Codec.Archive.Zip
import           Data.ByteString                 as B (ByteString, isInfixOf,
                                                       isPrefixOf, readFile)
import           Data.ByteString.Lazy            as BS (fromStrict, toStrict)
import           Data.Char                       (toLower)
import           Data.List                       as L (intercalate, isPrefixOf)
import           Data.List.Split                 (splitOn)
import           Data.Maybe                      (maybeToList)

data FileContent =
  FileContent
    { fileType :: FileType
    , fileContent :: ByteString
    }

data FileType = Message | Segment | Composite | Simple | CodedSimple deriving Eq

data FileContents =
  FileContents
    { messages     :: [ByteString]
    , segments     :: [ByteString]
    , composites   :: [ByteString]
    , simples      :: [ByteString]
    , codedSimples :: [ByteString]
    }

readZip :: Revision -> FilePath -> IO FileContents
readZip specification f = toFileContents . parseFile (getExtension f) (getName f) specification <$> B.readFile f

toFileContents :: [FileContent] -> FileContents
toFileContents t = FileContents
  { messages     = fileContent <$> filter ((==) Message . fileType) t
  , segments     = fileContent <$> filter ((==) Segment . fileType) t
  , composites   = fileContent <$> filter ((==) Composite . fileType) t
  , simples      = fileContent <$> filter ((==) Simple . fileType) t
  , codedSimples = fileContent <$> filter ((==) CodedSimple . fileType) t
  }

getName :: FilePath -> String
getName = intercalate "." . init . splitOn "." . last . splitOn "/"

getExtension :: FilePath -> String
getExtension = fmap toLower . last . splitOn "."

parseFile :: String -> String -> Revision -> ByteString -> [FileContent]
parseFile "zip" _ specification content = unzipAndRead specification content
parseFile extension name specification content
  | ("d" <> extension) == (toLower <$> getRevision specification) = maybeToList $ identifyFile name content
parseFile _ _ _ _ = []

unzipAndRead :: Revision -> ByteString -> [FileContent]
unzipAndRead specification content = let
    archive = zEntries $ toArchive $ BS.fromStrict content
    toContents e@Entry{eRelativePath} = parseFile (getExtension eRelativePath) (getName eRelativePath) specification (BS.toStrict $ fromEntry e)
  in
    concatMap toContents archive

identifyFile :: String -> ByteString -> Maybe FileContent
identifyFile name content
  | "                                  Message Type : " `isInfixOf` content = pure $ FileContent Message content
  | "2.   Composite specifications" `B.isPrefixOf` content = pure $ FileContent Composite content
  | "2.   Segment specifications" `B.isPrefixOf` content = pure $ FileContent Segment content
  | "2.   Data element specifications" `B.isPrefixOf` content = pure $ FileContent Simple content
  | "UNCL" `L.isPrefixOf` name = pure $ FileContent CodedSimple content
identifyFile _ _ = Nothing