Type error when using splitOn function.

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"

-- 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

Thank you to your answer.
I try to like these, but still got error
map (\x -> splitOn (pack ",") (pack x)) $ lines rowRxDx
map (\x -> splitOn (pack ",") x) $ lines rowRxDx
map (\x -> splitOn "," x) $ lines rowRxDx
etc...
2017-02-22 18:31 GMT+09:00 yi lu
-- 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
wrote: 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/Hask ell/samChecker3/RxDxData.csv"
readSam :: IO Text readSam = pack <$> readFile "/Users/shaegis/Documents/Hask ell/samChecker3/BoHomUTF8.dat"
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Sok Ha, CHANG Dr. Chang's Clinic. #203. 503-23. AmSa-Dong, GangDong-Gu, Seoul. Tel: +82-2-442-7585

On Wed, Feb 22, 2017 at 05:33:01PM +0900, S. H. Aegis wrote:
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.
Hello SH, Text.map has signature `(Char -> Char) -> Text -> Text`, so I expect you to need fmap too if the return value of makeRxDxList has type f [Text] makeRxDxList rowRxDx = fmap _ rowRxDx -- or base map _ is a hole and if the compiler will tell you which function needs to go there, in this case one with signature `Text -> [Text]`. Does that help? If not, provide makeRxDxList signature and a brief description so it's easier to diagnose the problem -F

Thank you so much.
--makeRxDxList :: Functor f => f Text -> f [Text]
Above signature comes from ghci using command :t
My intention is
makeRxDxList :: Text -> [[Text]]
but, I got error, and try several times and below codes pass a complier.
makeRxDxList rowRxDx = fmap (\x -> splitOn (pack ",") x) rowRxDx -- This
code pass a compile.
and then, I run ghci, type :t, and got below signature.
makeRxDxList :: Functor f => f Text -> f [Text]
Your kind answer says, I cannot help using fmap. right? ^^;
Thanks again.
2017-02-22 18:35 GMT+09:00 Francesco Ariis
On Wed, Feb 22, 2017 at 05:33:01PM +0900, S. H. Aegis wrote:
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.
Hello SH, Text.map has signature `(Char -> Char) -> Text -> Text`, so I expect you to need fmap too if the return value of makeRxDxList has type f [Text]
makeRxDxList rowRxDx = fmap _ rowRxDx -- or base map
_ is a hole and if the compiler will tell you which function needs to go there, in this case one with signature `Text -> [Text]`.
Does that help? If not, provide makeRxDxList signature and a brief description so it's easier to diagnose the problem -F _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Sok Ha, CHANG Dr. Chang's Clinic. #203. 503-23. AmSa-Dong, GangDong-Gu, Seoul. Tel: +82-2-442-7585

On Wed, Feb 22, 2017 at 09:02:22PM +0900, S. H. Aegis wrote:
Thank you so much.
--makeRxDxList :: Functor f => f Text -> f [Text] Above signature comes from ghci using command :t My intention is makeRxDxList :: Text -> [[Text]] but, I got error, and try several times and below codes pass a complier. makeRxDxList rowRxDx = fmap (\x -> splitOn (pack ",") x) rowRxDx -- This code pass a compile. and then, I run ghci, type :t, and got below signature. makeRxDxList :: Functor f => f Text -> f [Text]
Your kind answer says, I cannot help using fmap. right? ^^; Thanks again.
Then this: makeRxDxList :: Text -> [[Text]] makeRxDxList rowRxDx = fmap f (lines rowRxDx) -- you imported Prelude hiding map, so we will use fmap where f :: Text -> [Text] f x = splitOn (pack ",") x should do (at least it typechecks). GHC errors may not have the prettiest formatting ever, but they are very useful, the most important bits being line & column of the offending expression plus the "expected this but got that" part; get acquainted with them!

It works !!! (^O^)
Thank you so much.
Have a nice day~!
2017-02-22 22:31 GMT+09:00 Francesco Ariis
On Wed, Feb 22, 2017 at 09:02:22PM +0900, S. H. Aegis wrote:
Thank you so much.
--makeRxDxList :: Functor f => f Text -> f [Text] Above signature comes from ghci using command :t My intention is makeRxDxList :: Text -> [[Text]] but, I got error, and try several times and below codes pass a complier. makeRxDxList rowRxDx = fmap (\x -> splitOn (pack ",") x) rowRxDx -- This code pass a compile. and then, I run ghci, type :t, and got below signature. makeRxDxList :: Functor f => f Text -> f [Text]
Your kind answer says, I cannot help using fmap. right? ^^; Thanks again.
Then this:
makeRxDxList :: Text -> [[Text]] makeRxDxList rowRxDx = fmap f (lines rowRxDx) -- you imported Prelude hiding map, so we will use fmap where f :: Text -> [Text] f x = splitOn (pack ",") x
should do (at least it typechecks).
GHC errors may not have the prettiest formatting ever, but they are very useful, the most important bits being line & column of the offending expression plus the "expected this but got that" part; get acquainted with them!
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Sok Ha, CHANG Dr. Chang's Clinic. #203. 503-23. AmSa-Dong, GangDong-Gu, Seoul. Tel: +82-2-442-7585
participants (3)
-
Francesco Ariis
-
S. H. Aegis
-
yi lu