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. crypto random UUID generation (Ovidiu Deac) 2. Re: crypto random UUID generation (David McBride) 3. Parse file with existentials (Dmitriy Matrosov) 4. Re: crypto random UUID generation (Ovidiu Deac) ---------------------------------------------------------------------- Message: 1 Date: Mon, 12 Dec 2016 19:52:17 +0200 From: Ovidiu Deac <ovidiud...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: [Haskell-beginners] crypto random UUID generation Message-ID: <CAKVsE7v7Qr5+eaWEvxcL9Wp2ez=-42wywpcuu-lhtnmrzys...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" I have to produce a crypto random UUID. I haven't found simple examples. and I used the one from hre (see type CRand) http://hackage.haskell.org/package/monadcryptorandom-0.7.0/docs/Control-Monad-CryptoRandom.html#v:getCRandomR My attempt is the following: cryptoRandomUUID :: IO UUID.UUID cryptoRandomUUID = do g <- newGenIO:: IO SystemRandom case runCRand impl g of Left err -> throwIO err Right (v, g') -> return v where impl = do w1 <- getCRandom w2 <- getCRandom w3 <- getCRandom w4 <- getCRandom return $ UUID.fromWords w1 w2 w3 w4 ...but the compilation fails miserably with: • Ambiguous type variable ‘e0’ arising from a use of ‘runCRand’ prevents the constraint ‘(ContainsGenError e0)’ from being solved. Relevant bindings include impl :: CRandT SystemRandom e0 Data.Functor.Identity.Identity UUID.UUID (bound at src/Party.hs:75:9) Probable fix: use a type annotation to specify what ‘e0’ should be. These potential instance exist: instance ContainsGenError GenError -- Defined in ‘Control.Monad.CryptoRandom’ • In the expression: runCRand impl g In a stmt of a 'do' block: case runCRand impl g of { Left err -> throwIO err Right (v, g') -> return v } In the expression: do { g <- newGenIO :: IO SystemRandom; case runCRand impl g of { Left err -> throwIO err Right (v, g') -> return v } } ... What's the problem here? Are there some good examples for generating crypto-randoms? Thanks! -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20161212/7014f93c/attachment-0001.html> ------------------------------ Message: 2 Date: Mon, 12 Dec 2016 13:15:09 -0500 From: David McBride <toa...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] crypto random UUID generation Message-ID: <can+tr40y+ntgtmqfr0txmavaflrgowqj7dayydvgw4z_gfi...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" The problem is with Left err -> throwIO err Because of the type of 'runCRand', we know err is an instance of ContainsGenError e0, but which one? We need a concrete error type before we can run this code. Looking at the docs there seems to be only one instance of ContainsGenError, GenError, so a quick an dirty solution would be to change it to Left err -> throwIO (err :: GenError) -- should work But keep in mind, if there were any other ContainsGenError instances, like from an external library that is adding a new type of random generator to this library that fails in a new way, you would not be catching that. On Mon, Dec 12, 2016 at 12:52 PM, Ovidiu Deac <ovidiud...@gmail.com> wrote: > I have to produce a crypto random UUID. > > I haven't found simple examples. and I used the one from hre (see type > CRand) http://hackage.haskell.org/package/monadcryptorandom-0.7. > 0/docs/Control-Monad-CryptoRandom.html#v:getCRandomR > > My attempt is the following: > > cryptoRandomUUID :: IO UUID.UUID > cryptoRandomUUID = do > g <- newGenIO:: IO SystemRandom > case runCRand impl g of > Left err -> throwIO err > Right (v, g') -> return v > > where impl = do > w1 <- getCRandom > w2 <- getCRandom > w3 <- getCRandom > w4 <- getCRandom > return $ UUID.fromWords w1 w2 w3 w4 > > ...but the compilation fails miserably with: > > • Ambiguous type variable ‘e0’ arising from a use of ‘runCRand’ > prevents the constraint ‘(ContainsGenError e0)’ from being solved. > Relevant bindings include > impl :: CRandT > SystemRandom e0 Data.Functor.Identity.Identity UUID.UUID > (bound at src/Party.hs:75:9) > Probable fix: use a type annotation to specify what ‘e0’ should be. > These potential instance exist: > instance ContainsGenError GenError > -- Defined in ‘Control.Monad.CryptoRandom’ > • In the expression: runCRand impl g > In a stmt of a 'do' block: > case runCRand impl g of { > Left err -> throwIO err > Right (v, g') -> return v } > In the expression: > do { g <- newGenIO :: IO SystemRandom; > case runCRand impl g of { > Left err -> throwIO err > Right (v, g') -> return v } } > ... > > What's the problem here? > Are there some good examples for generating crypto-randoms? > > Thanks! > > _______________________________________________ > 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/20161212/cac008e6/attachment-0001.html> ------------------------------ Message: 3 Date: Tue, 13 Dec 2016 12:24:32 +0300 From: Dmitriy Matrosov <sgf....@gmail.com> To: beginners@haskell.org Subject: [Haskell-beginners] Parse file with existentials Message-ID: <fe224a38-0db6-5cb8-54d0-df9305520...@gmail.com> Content-Type: text/plain; charset=utf-8; format=flowed > {-# LANGUAGE GADTs #-} > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE KindSignatures #-} > {-# LANGUAGE StandaloneDeriving #-} > {-# LANGUAGE FlexibleInstances #-} > {-# LANGUAGE DeriveDataTypeable #-} > > import Prelude hiding (getLine) > import Data.Maybe > import Data.List > import Data.Typeable > import Control.Monad.Identity > import Control.Monad.Trans.Identity > import Control.Monad.Writer > import Control.Applicative > import System.FilePath Hi. I ask for an opinion about interface (implemented below) for parsing `rsync` filter files. The parser does not parse full syntax, i wrote it for determining rsync filter dependencies, when installing them using `shake`. So, i distinguish two kinds of lines: include of another filter file, which looks like . file and any other. I want to distinguish them at type level, so e.g. a record function for one constructor can't be applied to another, etc. I know, that i can prevent this at runtime by exporting only smart constructor, but i want a type check. > data RsyncFilterT = IncludeT | LineT > type IncludeT = 'IncludeT > type LineT = 'LineT > > -- Particular rsync filters distinguishable at type-level. > data RsyncFilter :: RsyncFilterT -> * where > Include :: {getInclude :: FilePath} -> RsyncFilter 'IncludeT > Line :: {getLine :: String} -> RsyncFilter 'LineT > deriving instance Show (RsyncFilter a) > deriving instance Typeable RsyncFilter For accessing records i use lenses redefined here. I redefine them with `Applicative` instead of `Functor` to make modify/set work even if value does not have a required record (by returning original (unmodified) value using `pure`). > type LensA a b = forall f. Applicative f => (b -> f b) -> a -> f a > > viewA :: LensA a b -> a -> b > viewA l = fromJust . getLast . getConst . l (Const . Last . Just) > viewAmaybe :: LensA a b -> a -> Maybe b > viewAmaybe l = getLast . getConst . l (Const . Last . Just) > > modifyA :: LensA a b -> (b -> b) -> a -> a > modifyA l f = runIdentity . l (Identity . f) > > modifyAA :: Applicative t => LensA a b -> (b -> t b) -> a -> t a > modifyAA l f = runIdentityT . l (IdentityT . f) > > setA :: LensA a b -> b -> a -> a > setA l s = modifyA l (const s) Here're lenses for `RsyncFilter` (its constructors are distinguishable at type-level, so i don't really need `Applicative` lenses here): > includeL :: LensA (RsyncFilter 'IncludeT) FilePath > includeL f z@Include {getInclude = x} = > fmap (\x' -> z{getInclude = x'}) (f x) > lineL :: LensA (RsyncFilter 'LineT) FilePath > lineL f z@Line {getLine = x} = > fmap (\x' -> z{getLine = x'}) (f x) The order of lines (may) matter, so i need to store all `RsyncFilter a` values in a list in original file order. But now the values are of different type. So.. i use existential container: > -- Generic container for any type of rsync filter. > data AnyFilter = forall (a :: RsyncFilterT). Typeable a => > AnyFilter (RsyncFilter a) > deriving instance Show AnyFilter > deriving instance Typeable AnyFilter And still i want to work on values of certain type to have some guarantees against misuse, so i need to cast `AnyFilter` back into `RsyncFilter` value: > -- Extract rsync filter from AnyFilter. > getFilter :: (forall (a :: RsyncFilterT). Typeable a => > RsyncFilter a -> b) -> AnyFilter -> b > getFilter f (AnyFilter x) = f x and here i also want to use lenses, but now the value may be of different type, that the lens expect, so i really need `Applicative` lenses here: > rsyncIncludeL' :: LensA AnyFilter (RsyncFilter 'IncludeT) > rsyncIncludeL' f z = maybe (pure z) (fmap AnyFilter . f) (getFilter cast z) > rsyncIncludeL :: LensA AnyFilter FilePath > rsyncIncludeL = rsyncIncludeL' . includeL > > rsyncLineL' :: LensA AnyFilter (RsyncFilter 'LineT) > rsyncLineL' f z = maybe (pure z) (fmap AnyFilter . f) > (getFilter cast z) > rsyncLineL :: LensA AnyFilter String > rsyncLineL = rsyncLineL' . lineL Then i define another Read/Show class just to be able to keep default Read/Show instances: > class Serialize a where > fromString :: String -> Maybe a > toString :: a -> String > > instance Serialize (RsyncFilter 'LineT) where > fromString = Just . Line > toString (Line xs) = xs > > -- RULE and PATTERN separator is space (`_` not supported). > -- Only short rule names without modifiers are supported. > instance Serialize (RsyncFilter 'IncludeT) where > fromString = go . break (== ' ') > where > go :: (String, String) -> Maybe (RsyncFilter 'IncludeT) > go (r, _ : x : xs) > | r == "." = Just (Include (x : xs)) > go _ = Nothing > toString (Include xs) = ". " ++ xs > > instance Serialize AnyFilter where > fromString x = > fmap AnyFilter (fromString x :: Maybe (RsyncFilter 'IncludeT)) > <|> fmap AnyFilter (fromString x :: Maybe (RsyncFilter 'LineT)) > toString x = fromMaybe "" $ > fmap toString (viewAmaybe rsyncIncludeL' x) > <|> fmap toString (viewAmaybe rsyncLineL' x) and a lens from String to AnyFilter, which effectively parses file and writes it back: > rsyncAnyL :: LensA String AnyFilter > rsyncAnyL f z = maybe (pure z) (fmap toString . f) (fromString z) And here is how i use this: > -- | Replace path prefix, if matched. > replacePrefix :: FilePath -> FilePath -> FilePath -> FilePath > replacePrefix old new x = maybe x (combine new . joinPath) $ > -- For ensuring that path prefix starts and ends at path > -- components (directories) boundaries, i first split them. > stripPrefix (splitDirectories old) (splitDirectories x) > > -- | Rewrite path in rsync inlcude line @line@ from source path > -- @srcdir@ to install path @prefix@ > -- > -- > usedIncludes srcdir prefix line > -- > -- and collect (rewritten) rsync include pathes in @Writer@ monad. > -- Other lines return as is. > usedIncludes :: FilePath -- ^ Source path. > -> FilePath -- ^ Install path. > -> String -- ^ Line from rsync filter file. > -> Writer [FilePath] String > usedIncludes srcdir prefix = > modifyAA (rsyncAnyL . rsyncIncludeL) $ \x -> do > let x' = replacePrefix srcdir prefix x > tell [x'] > return x' and then a shake rule: -- | Add file rule for instaling rsync filters with extension -- @ext@, rewriting source path @srcdir@ to install path @prefix@ -- in any rsync includes: -- -- > rsyncFilter ext srcdir prefix -- rsyncFilter :: String -- ^ Extension. -> FilePath -- ^ Install path. -> FilePath -- ^ Source path. -> Rules () rsyncFilter ext prefix srcdir = prefix ++ "//*" <.> ext %> \out -> do let src = replacePrefix prefix srcdir out ls <- readFileLines src let (rs, incs) = runWriter $ mapM (usedIncludes srcdir prefix) ls need incs putNormal $ "> Write " ++ out writeFileChanged out . unlines $ rs I probably won't think too much about this API, if i haven't read [Luke Palmer's post about existentials][1] . And now i doubt, did i fall into the same trap with existentials and does not see an obvious solution with functions? [1]: https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/ -- Dmitriy Matrosov ------------------------------ Message: 4 Date: Tue, 13 Dec 2016 13:41:45 +0200 From: Ovidiu Deac <ovidiud...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] crypto random UUID generation Message-ID: <cakvse7vjjsghhkga9ffteeceopts8ck2yqipvscxff6nwcv...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" Thanks! It works. Why is this a "quick and dirty" fix and what would be the "clean" fix? On Mon, Dec 12, 2016 at 8:15 PM, David McBride <toa...@gmail.com> wrote: > The problem is with > Left err -> throwIO err > > Because of the type of 'runCRand', we know err is an instance of > ContainsGenError e0, but which one? We need a concrete error type before > we can run this code. Looking at the docs there seems to be only one > instance of ContainsGenError, GenError, so a quick an dirty solution would > be to change it to > > Left err -> throwIO (err :: GenError) -- should work > > But keep in mind, if there were any other ContainsGenError instances, like > from an external library that is adding a new type of random generator to > this library that fails in a new way, you would not be catching that. > > > On Mon, Dec 12, 2016 at 12:52 PM, Ovidiu Deac <ovidiud...@gmail.com> > wrote: > >> I have to produce a crypto random UUID. >> >> I haven't found simple examples. and I used the one from hre (see type >> CRand) http://hackage.haskell.org/package/monadcryptorandom-0.7.0/ >> docs/Control-Monad-CryptoRandom.html#v:getCRandomR >> >> My attempt is the following: >> >> cryptoRandomUUID :: IO UUID.UUID >> cryptoRandomUUID = do >> g <- newGenIO:: IO SystemRandom >> case runCRand impl g of >> Left err -> throwIO err >> Right (v, g') -> return v >> >> where impl = do >> w1 <- getCRandom >> w2 <- getCRandom >> w3 <- getCRandom >> w4 <- getCRandom >> return $ UUID.fromWords w1 w2 w3 w4 >> >> ...but the compilation fails miserably with: >> >> • Ambiguous type variable ‘e0’ arising from a use of ‘runCRand’ >> prevents the constraint ‘(ContainsGenError e0)’ from being solved. >> Relevant bindings include >> impl :: CRandT >> SystemRandom e0 Data.Functor.Identity.Identity UUID.UUID >> (bound at src/Party.hs:75:9) >> Probable fix: use a type annotation to specify what ‘e0’ should be. >> These potential instance exist: >> instance ContainsGenError GenError >> -- Defined in ‘Control.Monad.CryptoRandom’ >> • In the expression: runCRand impl g >> In a stmt of a 'do' block: >> case runCRand impl g of { >> Left err -> throwIO err >> Right (v, g') -> return v } >> In the expression: >> do { g <- newGenIO :: IO SystemRandom; >> case runCRand impl g of { >> Left err -> throwIO err >> Right (v, g') -> return v } } >> ... >> >> What's the problem here? >> Are there some good examples for generating crypto-randoms? >> >> Thanks! >> >> _______________________________________________ >> 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 > > -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20161213/66d2a46a/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 102, Issue 1 *****************************************