Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Execution error in using text-icu on windows (S. H. Aegis)
   2. Re:  Execution error in using text-icu on windows
      (Francesco Ariis)


----------------------------------------------------------------------

Message: 1
Date: Sat, 4 Mar 2017 08:57:02 +0900
From: "S. H. Aegis" <shae...@gmail.com>
To: "beginners@haskell.org" <beginners@haskell.org>
Subject: [Haskell-beginners] Execution error in using text-icu on
        windows
Message-ID:
        <cajp-nqz4s+w-8un5q-mpdsunr4jq2psoscku1c73tjhnehh...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi.

I worte some code. and fixed some errors with the help of good persons.
Now, this utility works properly in Stack environment.
How can I install this utility in other computer?
This utility use text-icu and I coded this utility on windows. Of course, I
want to work this utility on other windows OS.

I copied %stackPath%\.stack-work\install\~\bin\samCheceker-exe.exe to some
other folder, and execution through CMD.
But I got error message that says "libicuuc57.dll dose not exist. so
program can't start. please re-install the program."
I copied libicuuc57.dll, and so... as like programming newbees, but failed.
"stack install" command was the same result.

How can I install the Executable File to other windows system?

Thank you.

Sincerely, S. Chang.



------------------
samChecker.cabal
------------------
name:                samChecker3
version:             0.1.0.0
-- synopsis:
-- description:
homepage:            https://github.com/githubuser/samChecker3#readme
license:             BSD3
license-file:        LICENSE
author:              Author name here
maintainer:          exam...@example.com
copyright:           2017 Author name here
category:            Web
build-type:          Simple
extra-source-files:  README.md
cabal-version:       >=1.10

library
  hs-source-dirs:      src
  exposed-modules:     Lib
  build-depends:       base >= 4.7 && < 5
                     , text
                     , text-icu
                     , bytestring
                     , regex-tdfa
  default-language:    Haskell2010

executable samChecker3-exe
  hs-source-dirs:      app
  main-is:             Main.hs
  ghc-options:         -threaded -rtsopts -with-rtsopts=-N
  build-depends:       base
                     , samChecker3
                     , text
                     , text-icu
                     , bytestring
                     , regex-tdfa
  default-language:    Haskell2010

test-suite samChecker3-test
  type:                exitcode-stdio-1.0
  hs-source-dirs:      test
  main-is:             Spec.hs
  build-depends:       base
                     , samChecker3
  ghc-options:         -threaded -rtsopts -with-rtsopts=-N
  default-language:    Haskell2010

source-repository head
  type:     git
  location: https://github.com/githubuser/samChecker3

-----------
Main.hs
-----------
module Main where

import Lib
import System.Environment
--import System.FilePath.Windows
import Data.Text.ICU.Convert       -- There is Codec.Text.IConv, too.
import qualified Data.Text         as T
import qualified Data.Text.IO      as TIO
import qualified Data.ByteString   as BS

main :: IO ()
main = do
        args <- getArgs    -- 1st=SAM 2nd=csv
        conv <- open "MS949" Nothing
        -- byteSAM :: ByteString
        --byteSAM <- BS.readFile
"C:\\Users\\shaeg\\Documents\\Haskell\\samChecker3\\BoHom.dat"
        byteSAM <- BS.readFile (args !! 0)
        -- byteRxDxData :: ByteString
        --byteRxDxData <- BS.readFile
"C:\\Users\\shaeg\\Documents\\Haskell\\samChecker3\\RxDxData.csv"
        byteRxDxData <- BS.readFile (args !! 1)
        TIO.putStrLn $ T.concat $ checkRxDxSAM (toUnicode conv
byteRxDxData) (toUnicode conv byteSAM)

-----------
Lib.hs
-----------
module Lib
--    ( readSAM
--    , readCSV
--    , checkRxDxSAM
--    ) where
      where

import Data.Text                 as T
import Data.Text.IO              as TIO
import Data.Text.ICU.Convert
import qualified Data.ByteString as BS
import Text.Regex.TDFA
import Data.Text.ICU             as I
import Prelude hiding (take, drop, map, lines)

type RowSAM = Text
type SAM = [Text]
type Case = Text
type RowRxDx = Text
type RxDx = [Text]
type RxDxList = [[Text]]
type Rx = Text
type Dx = Text
type MediName = Text
type Message = Text
type ErrorMessage = Text
type Date = Text
type PtName = Text

checkRxDxSAM :: RowRxDx -> RowSAM -> [ErrorMessage]
checkRxDxSAM rxDx sam = [pickupError r s | r <- (makeTuple rxDx), s <-
makeSamData sam]

makeSamData :: RowSAM -> SAM
makeSamData sam = splitIntoCase sam

makeTuple :: RowRxDx -> [(Rx, Dx, MediName)]
makeTuple rxDx = zip3 (makeRxList rxDx) (makeDxList rxDx) (makeMediNameList
rxDx)

makeMediNameList :: RowRxDx -> [MediName]
makeMediNameList rxDx = fmap pickupMediName $ makeRxDxList rxDx

makeDxList :: RowRxDx -> [Dx]
makeDxList rxDx = fmap pickupDx $ makeRxDxList rxDx

makeRxList :: RowRxDx -> [Rx]
makeRxList rxDx = fmap pickupRx $ makeRxDxList rxDx

makeRxDxList :: RowRxDx -> RxDxList
makeRxDxList rowRxDx = fmap f (lines rowRxDx)
    where
        f :: Text -> [Text]
        f x = splitOn (pack ",") x

pickupError :: (Rx, Dx, Message) -> Case -> ErrorMessage
pickupError (rxCode, dxCode, errMsg) ptCase =
    case isErrorRxDx rxCode dxCode ptCase of
        --True  -> append (pickupCaseDate ptCase) $ append (pack " ") $
append (pickupPtName ptCase) $ append (pack " Omit ") $ append dxCode $
append (pack " for ") errMsg
        True  -> append (pickupCaseDate ptCase) $ append (pack " ") $
append (pickupPtName ptCase) $ append (pack " Omit ") $ append dxCode $
append (pack " for ") $ append errMsg (pack "\n")
        False -> T.empty

pickupMediName :: RxDx -> MediName
pickupMediName rxDx = rxDx !! 0

pickupDx :: RxDx -> Dx
pickupDx rxDx = rxDx !! 2

pickupRx :: RxDx -> Rx
pickupRx rxDx = rxDx !! 1

pickupPtName :: Case -> PtName
pickupPtName ptCase = take 3 $ drop 45 ptCase

pickupCaseDate :: Case -> Date
pickupCaseDate ptCase = take 8 $ drop (348 + 2) ptCase

isErrorRxDx :: Rx -> Dx -> Case -> Bool
isErrorRxDx rxCode dxCode ptCase =
    case isExistRx rxCode ptCase of
        True  -> if (isExistDx dxCode ptCase) then False else True
        False -> False

isExistDx :: Dx -> Case -> Bool
--isExistDx dxCode ptCase = (unpack ptCase) =~ (unpack dxCode)
isExistDx dxCode ptCase =
    case (I.find (regex [] dxCode) ptCase) of
        Just x  -> True
        Nothing -> False

isExistRx :: Rx -> Case -> Bool
isExistRx rxCode ptCase = rxCode `isInfixOf` ptCase

splitIntoCase :: RowSAM -> SAM
splitIntoCase = splitOn $ pack "AH021"

--readCSV :: IO Text
--readCSV = pack <$> readFile
"/Users/shaegis/Documents/Haskell/samChecker3/RxDxData.csv"

--readSAM:: IO Text
--readSAM = pack <$> readFile
"/Users/shaegis/Documents/Haskell/samChecker3/BoHomUTF8.dat"
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170304/986ad9c6/attachment-0001.html>

------------------------------

Message: 2
Date: Sat, 4 Mar 2017 08:12:15 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Execution error in using text-icu on
        windows
Message-ID: <20170304071215.ga1...@casa.casa>
Content-Type: text/plain; charset=us-ascii

On Sat, Mar 04, 2017 at 08:57:02AM +0900, S. H. Aegis wrote:
> Hi.
> 
> I worte some code. and fixed some errors with the help of good persons.
> Now, this utility works properly in Stack environment.
> How can I install this utility in other computer?
> This utility use text-icu and I coded this utility on windows. Of course, I
> want to work this utility on other windows OS.
> 
> I copied %stackPath%\.stack-work\install\~\bin\samCheceker-exe.exe to some
> other folder, and execution through CMD.
> But I got error message that says "libicuuc57.dll dose not exist. so
> program can't start. please re-install the program."
> I copied libicuuc57.dll, and so... as like programming newbees, but failed.
> "stack install" command was the same result.
> 
> How can I install the Executable File to other windows system?

Hello, maybe you can try compiling with:

    stack build  --ghc-options '-static -optl-static'

(and stack clean before, probably).

I am not a windows or stack user, so this I cannot test this. Report
back and let us know if it worked or not.


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 105, Issue 2
*****************************************

Reply via email to