
-- map (\x -> splitOn (pack ",") pack x) $ lines rowRxDx
map (\x -> splitOn (pack ",") (pack x)) $ lines rowRxDx
Like this?
On Wed, Feb 22, 2017 at 4:33 PM, S. H. Aegis
Hello. I'm new to Haskell and this is the first time I use Data.Text module. And using stack on OSX 10.12.3 I'm try several times, but fail. and I don't understand what error message says. How can I fix this? Thank you a lot.
Code is
Main.hs : module Main where import Lib
main :: IO () main = do sam <- readSam rxDxData <- readCSV print $ makeRxDxList rxDxData
Lib.hs : module Lib -- ( someFunc -- ) where where
import Data.Text as T import Text.Regex.TDFA import Prelude hiding (take, drop, map, lines)
type RowSAM = Text type RowRxDx = Text
--makeRxDxList :: Functor f => f Text -> f [Text] --makeRxDxList rowRxDx = fmap (\x -> splitOn (pack ",") x) rowRxDx -- This code pass a compile. makeRxDxList rowRxDx = map (\x -> splitOn (pack ",") pack x) $ lines rowRxDx (whole code is below...)
Error Message is /Users/shaegis/Documents/Haskell/samChecker3/src/Lib.hs:25:35: error: • Couldn't match expected type ‘Char -> Char’ with actual type ‘[Text]’ • The function ‘splitOn’ is applied to three arguments, but its type ‘Text -> Text -> [Text]’ has only two In the expression: splitOn (pack ",") pack x In the first argument of ‘map’, namely ‘(\ x -> splitOn (pack ",") pack x)’
/Users/shaegis/Documents/Haskell/samChecker3/src/Lib.hs:25:54: error: • Couldn't match expected type ‘Text’ with actual type ‘String -> Text’ • Probable cause: ‘pack’ is applied to too few arguments In the second argument of ‘splitOn’, namely ‘pack’ In the expression: splitOn (pack ",") pack x In the first argument of ‘map’, namely ‘(\ x -> splitOn (pack ",") pack x)’
/Users/shaegis/Documents/Haskell/samChecker3/src/Lib.hs:25:64: error: • Couldn't match expected type ‘Text’ with actual type ‘[Text]’ • In the second argument of ‘($)’, namely ‘lines rowRxDx’ In the expression: map (\ x -> splitOn (pack ",") pack x) $ lines rowRxDx In an equation for ‘makeRxDxList’: makeRxDxList rowRxDx = map (\ x -> splitOn (pack ",") pack x) $ lines rowRxDx ------------------------------------------------------------ ------------------------------------------ Lib.hs module Lib -- ( someFunc -- ) where where
import Data.Text as T import Text.Regex.TDFA 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 Date = Text type PtName = Text
--makeRxDxList :: Functor f => f Text -> f [Text] --makeRxDxList rowRxDx = fmap (\x -> splitOn (pack ",") x) rowRxDx makeRxDxList rowRxDx = map (\x -> splitOn (pack ",") pack x) $ lines rowRxDx
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)
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"
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners