aboutsummaryrefslogtreecommitdiffhomepage
path: root/scaffolder/src/Text/Edifact/BundleReader/Commons.hs
diff options
context:
space:
mode:
Diffstat (limited to 'scaffolder/src/Text/Edifact/BundleReader/Commons.hs')
-rw-r--r--scaffolder/src/Text/Edifact/BundleReader/Commons.hs90
1 files changed, 90 insertions, 0 deletions
diff --git a/scaffolder/src/Text/Edifact/BundleReader/Commons.hs b/scaffolder/src/Text/Edifact/BundleReader/Commons.hs
new file mode 100644
index 0000000..0c8334a
--- /dev/null
+++ b/scaffolder/src/Text/Edifact/BundleReader/Commons.hs
@@ -0,0 +1,90 @@
1{-# LANGUAGE OverloadedStrings #-}
2
3module Text.Edifact.BundleReader.Commons where
4
5import Text.Edifact.BundleReader.Configuration
6import Text.Edifact.Scaffolder.Commons
7
8import Control.Monad.Reader (ReaderT, runReaderT)
9import Data.ByteString (ByteString)
10import Data.Char (toLower)
11import Data.List.Split (splitWhen)
12import Data.Text as T (isInfixOf, lines,
13 map, null,
14 replicate, strip,
15 unlines, unpack)
16import Data.Text.Encoding as TE (decodeLatin1,
17 decodeUtf8')
18import Data.Text.IO as TIO (writeFile)
19import Formatting
20import Text.Parsec (Parsec, runParser)
21
22type BundleReader = ReaderT BundleReaderEnv IO
23
24decodeContent :: ByteString -> Text
25decodeContent content = either (const $ cleanupAsciiArt $ decodeLatin1 content) id (decodeUtf8' content)
26
27splitFileByDash :: Int -> Text -> [Text]
28splitFileByDash n =
29 let separator = T.replicate n "-"
30 isNotEmpty = not . T.null . T.strip
31 in
32 filter isNotEmpty . fmap T.unlines . splitWhen (separator `T.isInfixOf`) . T.lines
33
34runBundleReader :: BundleReader () -> BundleReaderEnv -> IO ()
35runBundleReader = runReaderT
36
37getOutputFile :: Format String (a -> String) -> FilePath -> a -> BundleReader FilePath
38getOutputFile f d c = do
39 home <- getSpecificationHome
40 pure (formatToString (string % "/" % string % "/" % f) home d c)
41
42getSpecificationHome :: BundleReader FilePath
43getSpecificationHome = do
44 home <- getHome
45 rev <- getTargetRevision
46 pure (home </> formatToString fRevision rev)
47
48toFile :: Text -> FilePath -> BundleReader ()
49toFile specification outputFile = liftIO (TIO.writeFile outputFile specification)
50
51parseOrFail :: (Monoid u) => Text -> Parsec String u a -> BundleReader a
52parseOrFail specification parser = either (error . (\a -> show specification <> show a)) pure (runParser parser mempty "" (T.unpack specification))
53
54toFileWithParser :: (Monoid a, Monoid u) => Text -> FilePath -> Parsec String u a -> BundleReader a
55toFileWithParser specification outputFile parser = do
56 liftIO (TIO.writeFile outputFile specification)
57 either (error . show) pure (runParser parser mempty "" (T.unpack specification))
58
59lower :: Format r (String -> r)
60lower = mapf (fmap toLower) string
61
62fRevision :: Format r (Revision -> r)
63fRevision = mapf getRevision string
64
65fRevisionLower :: Format r (Revision -> r)
66fRevisionLower = mapf getRevision lower
67
68fMessageCodeLower :: Format r (MessageCode -> r)
69fMessageCodeLower = mapf getMessageCode lower
70
71fSegmentCodeLower :: Format r (SegmentCode -> r)
72fSegmentCodeLower = mapf getSegmentCode lower
73
74fCompositeCodeLower :: Format r (CompositeCode -> r)
75fCompositeCodeLower = mapf getCompositeCode lower
76
77fSimpleCodeLower :: Format r (SimpleCode -> r)
78fSimpleCodeLower = mapf getSimpleCode lower
79
80-- This might not be the proper way to do it...
81-- Use Data.Text.Encoding.decodeUtf8With instead?
82cleanupAsciiArt :: Text -> Text
83cleanupAsciiArt =
84 let f 'Ä' = '-'
85 f '¿' = '+'
86 f '³' = '|'
87 f 'Ù' = '+'
88 f 'Á' = '+'
89 f c = c
90 in T.map f