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. Re: Type error when using splitOn function. (yi lu) 2. Re: Type error when using splitOn function. (Francesco Ariis) 3. Re: Type error when using splitOn function. (S. H. Aegis) ---------------------------------------------------------------------- Message: 1 Date: Wed, 22 Feb 2017 17:31:55 +0800 From: yi lu <zhiwudazhanjiang...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] Type error when using splitOn function. Message-ID: <cakcmqqw9efg-rpkxm_wwwskrp2kdravsizz8makh6j4yhfm...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" -- 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 <shae...@gmail.com> 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/ > 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 > > -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20170222/fcb18bca/attachment-0001.html> ------------------------------ Message: 2 Date: Wed, 22 Feb 2017 10:35:57 +0100 From: Francesco Ariis <fa...@ariis.it> To: beginners@haskell.org Subject: Re: [Haskell-beginners] Type error when using splitOn function. Message-ID: <20170222093557.ga9...@casa.casa> Content-Type: text/plain; charset=us-ascii 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 ------------------------------ Message: 3 Date: Wed, 22 Feb 2017 20:53:58 +0900 From: "S. H. Aegis" <shae...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] Type error when using splitOn function. Message-ID: <cajp-nqwlmgj_uie+sh7xnkmjbycz98ge_6xckach+ewzses...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" 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 <zhiwudazhanjiang...@gmail.com>: > -- 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 <shae...@gmail.com> 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 -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20170222/2b7f9a0e/attachment.html> ------------------------------ Subject: Digest Footer _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ End of Beginners Digest, Vol 104, Issue 14 ******************************************