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: Functions as Applicatives (Olumide) 2. No instance for Show arising from a use in “main” level (T. Andrea Moruno Rodriguez) 3. Re: No instance for Show arising from a use in “main” level (T. Andrea Moruno Rodriguez) 4. putting together monadic actions (Dennis Raddle) 5. Re: putting together monadic actions (Sylvain Henry) ---------------------------------------------------------------------- Message: 1 Date: Tue, 23 Aug 2016 15:30:13 +0100 From: Olumide <50...@web.de> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] Functions as Applicatives Message-ID: <ab873731-0db5-b0cb-5643-ffe0cdb5b...@web.de> Content-Type: text/plain; charset=utf-8; format=flowed On 23/08/2016 12:39, Tony Morris wrote: > All functions in Haskell always take one argument. I know that. All functions accept one argument and return a value _or_ another function. Is f the latter type? - Olumide > > > On 23/08/16 21:28, Olumide wrote: >> I must be missing something. I thought f accepts just one argument. >> >> - Olumide >> >> On 23/08/2016 00:54, Theodore Lief Gannon wrote: >>> Yes, (g x) is the second argument to f. Consider the type signature: >>> >>> (<*>) :: Applicative f => f (a -> b) -> f a -> f b >>> >>> In this case, the type of f is ((->) r). Specialized to that type: >>> >>> (<*>) :: (r -> a -> b) -> (r -> a) -> (r -> b) >>> f <*> g = \x -> f x (g x) >>> >>> Breaking down the pieces... >>> f :: r -> a -> b >>> g :: r -> a >>> x :: r >>> (g x) :: a >>> (f x (g x)) :: b >>> >>> The example is made a bit confusing by tossing in an fmap. As far as the >>> definition above is concerned, 'f' in the example is ((+) <$> (+3)) and >>> that has to be resolved before looking at <*>. >>> >>> >>> On Mon, Aug 22, 2016 at 9:07 AM, Olumide <50...@web.de >>> <mailto:50...@web.de>> wrote: >>> >>> Hi List, >>> >>> I'm struggling to relate the definition of a function as a function >>> >>> instance Applicative ((->) r) where >>> pure x = (\_ -> x) >>> f <*> g = \x -> f x (g x) >>> >>> with the following expression >>> >>> ghci> :t (+) <$> (+3) <*> (*100) >>> (+) <$> (+3) <*> (*100) :: (Num a) => a -> a >>> ghci> (+) <$> (+3) <*> (*100) $ 5 >>> 508 >>> >>> From chapter 11 of LYH http://goo.gl/7kl2TM . >>> >>> I understand the explanation in the book: "we're making a function >>> that will use + on the results of (+3) and (*100) and return that. >>> To demonstrate on a real example, when we did (+) <$> (+3) <*> >>> (*100) $ 5, the 5 first got applied to (+3) and (*100), resulting in >>> 8 and 500. Then, + gets called with 8 and 500, resulting in 508." >>> >>> The problem is that I can't relate that explanation with the >>> definition of a function as an applicative; especially f <*> g = \x >>> -> f x (g x) . Is (g x) the second argument to f? >>> >>> Regards, >>> >>> - Olumide >>> _______________________________________________ >>> Beginners mailing list >>> Beginners@haskell.org <mailto:Beginners@haskell.org> >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> <http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners> >>> >>> >>> >>> >>> _______________________________________________ >>> 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 > > > > > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > ------------------------------ Message: 2 Date: Tue, 23 Aug 2016 20:10:34 -0400 From: "T. Andrea Moruno Rodriguez" <tatiana.mor...@gmail.com> To: beginners@haskell.org Subject: [Haskell-beginners] No instance for Show arising from a use in “main” level Message-ID: <CAFEhFEYyMvsGfU0vX=G-DaHtu-_o0_7zrb3FRQoJ=7g6uvu...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" I have a code that reads files and parses using UU.Parsing lib that returns an abstract sintax tree and shows on the screen. I received the error message "No instance for Show" in my functions originated intokensParserToByteString and applyParser using parseIO (of UU.Parsing lib) and inherited signatures until main. I fixed the signatures but my problem is in the main function. I added the instance Show in the signature but I have the next compilation error: No instance for (Show (IO J2s)) arising from a use of ‘main’ In the expression: main When checking the type of the IO action ‘main’ Some idea, about the problem? Main module ----------------------------------------------------------------------- {-# LANGUAGE FlexibleContexts #-} module Main where import UU.Parsing ... import Content main :: (Show (IO J2s)) => IO() main = do f <- getLine let command = test f command test :: (Show (IO J2s)) => String -> IO() test "testparser" = testParser Test module ----------------------------------------------------------------------- {-# LANGUAGE FlexibleContexts #-} module J2s.Parser.Test where import Content import J2s.Ast.Sintax import J2s.Parser import UU.Parsing ... testParser :: (Show (IO J2s)) => IO() testParser = (runSafeIO $ runProxy $ runEitherK $ contentsRecursive "path/of/my/tests" />/ handlerParser) :: (Show (IO J2s)) => IO() Content module ----------------------------------------------------------------------- {-# LANGUAGE FlexibleContexts #-} module Content where import Control.Monad(forM, liftM) import System.Directory (doesDirectoryExist, getDirectoryContents) import System.FilePath ((</>), splitExtension, splitFileName) import J2s.Parser import J2s.Ast.Sintax import UU.Parsing import Control.Monad (when, unless) import Control.Proxy import Control.Proxy.Safe hiding (readFileS) import J2s.Scanner.Token import Text.Show import UU.Parsing contentsRecursive :: (CheckP p) => FilePath -> () -> Producer (ExceptionP p) FilePath SafeIO () contentsRecursive path () = loop path where loop path = do contents path () //> \newPath -> do respond newPath isDir <- tryIO $ doesDirectoryExist newPath let isChild = not $ takeFileName newPath `elem` [".", ".."] when (isDir && isChild) $ loop newPath applyParser :: (Proxy p, Show (IO J2s)) => String -> Consumer p B.ByteString IO () applyParser path = runIdentityP loop where loop = do bs <- request () let sc = classify (initPos path) (B8.unpack bs) lift $ B8.putStrLn (tokensParserToByteString sc) tokensParserToByteString :: (Show (IO J2s)) => [Token] -> B.ByteString tokensParserToByteString tokens = B8.pack(show (parseIO pJ2s tokens)) handlerParser :: (CheckP p, Show (IO J2s)) => FilePath -> Session (ExceptionP p) SafeIO () handlerParser path = do canRead <- tryIO $ fmap readable $ getPermissions path isDir <- tryIO $ doesDirectoryExist path isValidExtension <- tryIO $ evaluate ((snd (splitExtension path) == ".java" || snd (splitExtension path) == ".mora") && (snd (splitFileName path) /= "EncodeTest.java") && (snd (splitFileName path) /= "T6302184.java") && (snd (splitFileName path) /= "Unmappable.java")) when (not isDir && canRead && isValidExtension) $ (readFileSP 10240 path >-> try . applyParser) path readFileSP :: (CheckP p) => Int -> FilePath -> () -> Producer (ExceptionP p) B.ByteString SafeIO () readFileSP chunkSize path () = bracket id (openFile path ReadMode) hClose $ \handle -> do let loop = do eof <- tryIO $ hIsEOF handle unless eof $ do bs <- tryIO $ B.hGetSome handle chunkSize respond bs loop loop -- Tatiana Andrea Moruno Rodriguez -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20160823/ababcc45/attachment-0001.html> ------------------------------ Message: 3 Date: Tue, 23 Aug 2016 20:44:04 -0400 From: "T. Andrea Moruno Rodriguez" <tatiana.mor...@gmail.com> To: Imants Cekusins <ima...@gmail.com>, beginners@haskell.org Subject: Re: [Haskell-beginners] No instance for Show arising from a use in “main” level Message-ID: <CAFEhFEa+18eTf_LXVR=ogf9nb+z7odhpgax1+vnxm6qosvw...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" Hi! Yes. Thanks I resolved my problem. The explanation is here: http://stackoverflow.com/questions/39112380/no-instance-for-show-arising-from-a-use-in-main-level?noredirect=1#comment65572477_39112380 2016-08-23 20:23 GMT-04:00 Imants Cekusins <ima...@gmail.com>: > Hello Tatiana, > > these signatures do not look good: > > main :: (Show (IO J2s)) => IO() > > test :: (Show (IO J2s)) => String -> IO() > > testParser :: (Show (IO J2s)) => IO() > > > constraints are used to specify type variables. IO J2s looks like * (a > fixed type). > > what errors do you see without these constraints? > -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20160823/b1d635c1/attachment-0001.html> ------------------------------ Message: 4 Date: Tue, 23 Aug 2016 18:00:34 -0700 From: Dennis Raddle <dennis.rad...@gmail.com> To: Haskell Beginners <beginners@haskell.org> Subject: [Haskell-beginners] putting together monadic actions Message-ID: <CAKxLvoo=-+eXc=ZKktv9+Ys+rKHfDFsRUPU+nPmtgSK=dvu...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" Is there a function foo that does foo :: a -> [a -> m a] -> a So foo 3 [x,x,x] = return 3 >>= x >>= x >>= x I don't think replicateM and sequence do this. At least I can't figure it out. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20160823/7cc64274/attachment-0001.html> ------------------------------ Message: 5 Date: Wed, 24 Aug 2016 03:33:01 +0200 From: Sylvain Henry <sylv...@haskus.fr> To: beginners@haskell.org Subject: Re: [Haskell-beginners] putting together monadic actions Message-ID: <b82bb6ef-2105-da15-088e-76f650330...@haskus.fr> Content-Type: text/plain; charset="utf-8"; Format="flowed" Hi, You can easily write your own: > import Control.Monad > import Data.List > let foo = flip (foldl' (>=>) return) > :t foo foo :: (Foldable t, Monad m) => b -> t (b -> m b) -> m b > let g x = return (x*2) > foo 3 [g,g,g] 24 -Sylvain On 24/08/2016 03:00, Dennis Raddle wrote: > Is there a function foo that does > > foo :: a -> [a -> m a] -> a > > So > > foo 3 [x,x,x] = return 3 >>= x >>= x >>= x > > I don't think replicateM and sequence do this. At least I can't figure > it out. > > > _______________________________________________ > 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/20160824/ece8623d/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 98, Issue 17 *****************************************