Re: [Haskell-cafe] Categorical description of systems with dependent types

2010-12-03 Thread wren ng thornton

On 12/2/10 4:47 PM, Iavor Diatchki wrote:

Hi,
You have it exactly right, and I don't think that there's a
particularly deep reason to prefer the one over the other.  It seems
that computer science people
tend to go with the (product-function) terminology, while math people
seem to prefer the (sum-product) version, but it is all largely a
matter of taste.


The product=function,sum=pair terminology comes from a certain 
interpretation of dependent types in set theory. I believe this 
originated with Per Martin-Löf's work, though I don't have any citations 
on hand.


That terminology conflicts with the standard product=pair,sum=either 
terminology of functional languages, however. So folks from a functional 
background tend to prefer: dependent function, dependent product, sum; 
whereas folks from a set-theoretic background tend to prefer product, 
sum, /union.


--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type families again

2010-12-03 Thread Ganesh Sittampalam

On Thu, 2 Dec 2010, Robert Greayer wrote:


On Thu, Dec 2, 2010 at 4:39 PM, Antoine Latter  wrote:

On Thu, Dec 2, 2010 at 3:29 PM, Andrew Coppin
 wrote:


What we /can't/ do is define a polymorphic map function. One might try to do
something like

 class Functor f where
   type Element f :: *
   fmap :: (Element f2 ~ y) => (x -> y) -> f -> f2

 instance Functor [x] where
   type Element [x] = x
   fmap = map

However, this fails. Put simply, the type for fmap fails to specify that f
and f2 must be /the same type of thing/, just with different element types.

The trouble is, after spending quite a bit of brainpower, I literally cannot
think of a way of writing such a constraint. Does anybody have any
suggestions?


Does this do what you need?

http://hackage.haskell.org/packages/archive/rmonad/0.6/doc/html/Control-RMonad.html#t:RFunctor

Antoine



I think this doesn't handle the ByteString case (wrong kind).  Here's
another mostly unsatisfactory (injectivity issues) solution that may
possibly not even work though it does compile:


I spent a while looking at this a couple of months ago after a similar 
question. What I came up with is below; I haven't got as far as 
deciding whether or how to incorporate this into rmonad. Also, the Const 
type actually already exists in Control.Applicative.


Cheers,

Ganesh

{-# LANGUAGE GADTs, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, 
ScopedTypeVariables, RankNTypes #-}

module Control.RMonad.Wibble where

import Control.RMonad
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import Data.Suitable
import GHC.Word (Word8)

-- Part I

-- a little warmup: ByteStrings

-- We have two choices for BSWrapper. Either make
-- it a GADT, which means we can leave out the match on the
-- argument constraints below, or make it a H98 phantom.
-- The second option seems cleaner and more symmetric.
-- It also means we can us newtype to avoid runtime overhead.

-- data BSWrapper a where
--   BSWrapper :: ByteString -> BSWrapper Word8

newtype BSWrapper a = BSWrapper ByteString

data instance Constraints BSWrapper a = (a ~ Word8) => BSConstraints

instance Suitable BSWrapper Word8 where
  constraints = BSConstraints

instance RFunctor BSWrapper where
  -- We could also use withResConstraints by rearranging the arguments to mymap 
so Constraints is last
  fmap = mymap constraints constraints
where mymap :: forall x y . Constraints BSWrapper x -> Constraints BSWrapper y -> (x 
-> y) -> BSWrapper x -> BSWrapper y
  mymap BSConstraints BSConstraints f (BSWrapper x) = BSWrapper (BS.map 
f x)

-- Part II

-- OK, now let's generalise:

-- Having a class here rather than a plain type family isn't really necessary,
-- but it feels natural
class SingletonContainer c where
   type ContainedType c :: *

-- data SingletonWrapper c a where
--   SingletonWrapper :: SingletonContainer c => c -> SingletonWrapper c 
(ContainedType c)

-- This is just a generic Const type. Is there a standard one somewhere else?
newtype SingletonWrapper c a = SingletonWrapper c

data instance Constraints (SingletonWrapper c) a = (a ~ ContainedType c) => 
SingletonConstraints

-- important to use the type equality constraint here instead of inlining it
-- on the RHS, as otherwise instance resolution would get stuck
instance (a ~ ContainedType c) => Suitable (SingletonWrapper c) a where
  constraints = SingletonConstraints

class SingletonContainer c => Mappable c where
   lmap :: (ContainedType c -> ContainedType c) -> c -> c

instance Mappable c => RFunctor (SingletonWrapper c) where
  fmap = mymap constraints constraints
where mymap :: forall x y
 . Constraints (SingletonWrapper c) x
-> Constraints (SingletonWrapper c) y
-> (x -> y)
-> SingletonWrapper c x
-> SingletonWrapper c y
  mymap SingletonConstraints SingletonConstraints f (SingletonWrapper 
x) = SingletonWrapper (lmap f x)


-- so, why is Word8 the blessed instance? Why not Char (from 
Data.ByteString.Char8)?
instance SingletonContainer ByteString where
   type ContainedType ByteString = Word8


-- Part III

-- and finally, let's try to generalise the Singleton concept:

-- using the Const concept again...
newtype Const a b = Const a

instance Show a => Show (Const a b) where
  show (Const x) = show x

data instance Constraints (Const ByteString) a =
   (a ~ Word8) => BSConstraintsWord8
 | (a ~ Char) => BSConstraintsChar

instance Suitable (Const ByteString) Word8 where
   constraints = BSConstraintsWord8

instance Suitable (Const ByteString) Char where
   constraints = BSConstraintsChar

instance RFunctor (Const ByteString) where
  fmap = mymap constraints constraints
where mymap :: forall x y
 . Constraints (Const ByteString) x
-> Constraints (Const ByteString) y
-> (x -> y) -> Const ByteString x -> Const ByteString y

   

Re: [Haskell-cafe] Digests

2010-12-03 Thread Serguey Zefirov
2010/12/4 Permjacov Evgeniy :
>> near cryptographic) security. To quote Wikipedia again: "The avalanche
>> effect is evident if, when an input is changed slightly (for example,
>> flipping a single bit) the output changes significantly (e.g., half
>> the output bits flip)."
> This simply means, that active set of bits must be at least of the size
> of final value and value to be added must be added somehow to every byte
> in active set. The simplest way to do it is multiplication of vector
> [active-state-bits++current-byte] and some matrix of size [resulting
> bytes count|resulting bytes count + 1] (of cource, not in floating-point
> math, but, for example, using modulo-256 arithmetic or even hand-coded
> tables for "mul" and "sum"). This, of course, means, that byte-streaming
> hashes needs some initial seed (that must be paired with resulting value
> to check) and that every byte will cause much operations to perform,
> resulting in poor performance. So, the conclusion is: byte-streaming
> hashes are possible, but because of requirements definitly will have
> poor performance, much worse then block ones. Am I correct?

I think you are correct.

PS
The note about matrices is interesting one.

The total matrix should be dense, but we could factor it. For example,
by multiplying two N wide and M wide band matrices we will get (N+M)
wide band matrix.

You are free to choose multiplication and addition operations, like
addition could be XOR and multiplication could be ROTATE_LEFT (like in
RC5).

I did a little experiment: http://thesz.mskhug.ru/svn/cryptomatrix/

Just to demonstrate interesting properties of your suggestion.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Digests

2010-12-03 Thread Permjacov Evgeniy
On 12/03/2010 11:40 AM, Serguey Zefirov wrote:
> 2010/12/3 Permjacov Evgeniy :
 */me wrote it into to_read list. The problem is, however, that block
 ciphers are quite unfriendly to plain word8 streams. It is not a deadly
 problem, but i'd like to avoid block collections.
>>> All one-way hashes do block collections. This is unavoidable.
>> Why ? Is there some math behind this proposition ?
> This is hard - to add single byte into the sum with cryptographic (or
> near cryptographic) security. To quote Wikipedia again: "The avalanche
> effect is evident if, when an input is changed slightly (for example,
> flipping a single bit) the output changes significantly (e.g., half
> the output bits flip)."
This simply means, that active set of bits must be at least of the size
of final value and value to be added must be added somehow to every byte
in active set. The simplest way to do it is multiplication of vector
[active-state-bits++current-byte] and some matrix of size [resulting
bytes count|resulting bytes count + 1] (of cource, not in floating-point
math, but, for example, using modulo-256 arithmetic or even hand-coded
tables for "mul" and "sum"). This, of course, means, that byte-streaming
hashes needs some initial seed (that must be paired with resulting value
to check) and that every byte will cause much operations to perform,
resulting in poor performance. So, the conclusion is: byte-streaming
hashes are possible, but because of requirements definitly will have
poor performance, much worse then block ones. Am I correct?
> http://en.wikipedia.org/wiki/Avalanche_effect
>
> This is true for hashes too. Hash should change about half of the
> random output bits when single bit of input changes. Especially if you
> aim to tamper-proof hashes. You have to have that property on every
> round of hashing, because you don't know when to stop. For bytes, you
> have to guarantee that you get an avalanche effect for every byte - it
> means, that you have to transform your entire block plus input byte in
> an expensive way. MD5 and all other hashes have internal state of
> various size, they all keep input blocks to make hashing transform
> less expensive.
>
> Fast methods like sum-modulo-poly (CRC variants) or linear
> congruential generators do not have good avalanche property when used
> for stream hashing or encryption. Even their combination (one in ZIP
> encryption) wasn't strong enough.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bifold: a simultaneous foldr and foldl

2010-12-03 Thread Larry Evans
On 12/01/10 21:35, Larry Evans wrote:
> On 11/30/10 13:43, Noah Easterly wrote:
[snip]
>> Thanks, Larry, this is some interesting stuff.
>>
>> I'm not sure yet whether Q is equivalent - it may be, but I haven't been
>> able to thoroughly grok it yet.
>>
[snip]
> 
> Hi Noah,
> 
> The attached is my attempt at reproducing your code and also
> contains an alternative attempt at emulating the code in
> section 12.5 of:
> 
>   http://www.thocp.net/biographies/papers/backus_turingaward_lecture.pdf
> 
The attached code is a revision of my previous if_recur attempt
at emulated the section 12.5 code.  This revision added the i
function from the seciton 12.5 (instead of delegating that
task to the h function).  The 2nd attachment shows the output.
It shows that by modifying the args to if_recur, you can
reproduce the output from foldl or foldr.
{-
  Purpose:
create a function, if_recur, like the f in section 12.5 of:
  [BAC77]
 http://www.thocp.net/biographies/papers/backus_turingaward_lecture.pdf
-}

module IfRecur where

-- {*if_recur
  if_recur :: state_down
   -> (state_down -> Bool) 
   -> (state_down -> state_down)
   -> (state_down -> state_saved)
   -> ((state_saved,state_up) -> state_up) 
   -> (state_down -> state_up)
   -> state_up
  
  if_recur state_now  -- current state
   recur_ -- continue recursion?
   then_down  -- ::state_down -> state_down
   save_state -- ::state_down -> state_saved
   now_up -- ::((state_saved,state_up)->state_up
   else_  -- ::state_down -> state_up
   {- The following table shows the corresponndence
  between the f in section 12.5 of [BAC77]
  and the arguments to this function:

  [BAC77]   [if_recur]
  ===   ==
p   recur_
g   else_
j   then_down
i   save_state
h   now_up
   -}
   = if recur_ state_now
 then now_up
  ( save_state state_now
  , if_recur (then_down state_now)
 recur_
 then_down
 save_state
 now_up
 else_
  )
 else else_ state_now

-- }*if_recur

{--}
  palindrome :: [a] -> [a]

  palindrome x = if_recur 
   (x,[]) --state_now
   (not.null.fst) --recur_
   (\(sn,cd) -> (tail sn,(head sn):cd)) --then_down
   (\(sn,cd) -> head sn) --save_state
   (\(ss,cu) -> ss:cu) --now_up
   (\(sn,cd) -> cd) --else_

  if_recur_foldl :: [a] -> [a]

  if_recur_foldl x = if_recur 
   (x,[]) --state_now
   (not.null.fst) --recur_
   (\(sn,cd) -> (tail sn,(head sn):cd)) --then_down
   (\(sn,cd) -> ()) --save_state
   (\(ss,cu) -> cu) --now_up
   (\(sn,cd) -> cd) --else_

  if_recur_foldr :: [a] -> [a]

  if_recur_foldr x = if_recur 
   (x,[]) --state_now
   (not.null.fst) --recur_
   (\(sn,cd) -> (tail sn,cd)) --then_down
   (\(sn,cd) -> head sn) --save_state
   (\(ss,cu) -> ss:cu) --now_up
   (\(sn,cd) -> cd) --else_

  test = sequence
 [ print "palindrome [1,2,3]:"
 , print (palindrome [1,2,3])
 , print "if_recur_foldl [1,2,3]:"
 , print (if_recur_foldl [1,2,3])
 , print "(foldl (flip(:)) [] [1,2,3]):"
 , print (foldl (flip(:)) [] [1,2,3])
 , print "if_recur_foldr [1,2,3]:"
 , print (if_recur_foldr [1,2,3])
 , print "(foldr (:) [] [1,2,3]):"
 , print (foldr (:) [] [1,2,3])
 ]
{--}
/home/evansl/prog_dev/haskell/my-code $ ghci IfRecur.hs
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling IfRecur  ( IfRecur.hs, interpreted )
Ok, modules loaded: IfRecur.
*IfRecur> test
"palindrome [1,2,3]:"
[1,2,3,3,2,1]
"if_recur_foldl [1,2,3]:"
[3,2,1]
"(foldl (flip(:)) [] [1,2,3]):"
[3,2,1]
"if_recur_foldr [1,2,3]:"
[1,2,3]
"(foldr (:) [] [1,2,3]):"
[1,2,3]
[(),(),(),(),(),(),(),(),(),()]
*IfRecur> 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Digests

2010-12-03 Thread Brandon Moore
I may be missing something, but it is not clear to me if you want
cryptographic security. If you do, then the only safe choice
is to use a standard algorithm (or block cipher construction,
perhaps). Sorry if that's already what you are discussing -
I don't know whether there are any established algorithms
that mix in a byte at a time. (though the argument that they
are aiming for avalanche properties is pretty strong).

(The history of the submissions to the SHA3 contest
http://csrc.nist.gov/groups/ST/hash/sha-3/index.html
shows it's not easy for even the experts to get it right, and
that it can take a long time for problems to be noticed,
even if you can convince tons of other experts to look
over an algorithm)

If you don't want cryptographic security, there may are
probably cheap things you could consider.

Brandon


  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In what language...?

2010-12-03 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 11/28/10 08:47 , Florian Weimer wrote:
> * Gregory Collins:
> 
>> * Andrew Coppin:
>>> Hypothesis: The fact that the average Haskeller thinks that this
>>> kind of dense cryptic material is "pretty garden-variety" notation
>>> possibly explains why normal people think Haskell is scary.
>>
>> That's ridiculous. You're comparing apples to oranges: using Haskell
>> and understanding the underlying theory are two completely different
>> things.
> 
> I could imagine that the theory could be quite helpful for accepting
> nagging limitations.  I'm not an experienced Haskell programmer,
> though, but that's what I noticed when using other languages.

Yes and no; for example, it's enough to know that System F (the type system
used by GHC) can't describe dependent types, without needing to know *why*.
 A brief overview is more useful in this case.

This is true of most of the ML-ish languages:  they're based on rigorous
mathematical principles, but those principles are sufficiently high level
that there isn't a whole lot of point in teaching them as part of teaching
the languages.  The concepts behind other languages are rarely based in
anything quite as high level, and moreover often take structural rather than
mathematical form, so understanding them *does* help.  (An example of this
is C++ templates; as I understand it, there *is* mathematics behind them,
but many of their behaviors come from their structure rather than the math.)

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkz5ROsACgkQIn7hlCsL25VdGQCeLuDo6HS8sfnFG1EuA4oDO56y
5soAoLexEtjRKYIVFFCpWk86u0/woZGF
=Fn2e
-END PGP SIGNATURE-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HStringTemplate and syb-with-class usage

2010-12-03 Thread Christopher Lewis
I've seen questions on using HStringTemplate with syb-with-class on
the list before, but haven't seen this issue addressed. I'm hoping
it's a noob issue, and, therefore, thought I would check with the list
before spending too much time digging around for solutions.

I'm attempting to use HStringTemplate with the syb-with-class support.
I've made sure HStringTemplate is installed with
'syb-with-class=True'. 'genericToSElem' is always failing on the 'True
=' guard with an error of "Unable to serialize the primitive type
[...]" with whatever primitive Haskell type I've included in my ADT;
for example, "Unable to serialize the primitive type 'Prelude.Int'".

I've made sure to include 'Text.StringTemplate.GenericWithClass',
'Data.Generics.SYB.WithClass.Basics', and
'Data.Generics.SYB.WithClass.Derive', and to derive instances of the
'Typeable' and 'Data' classes with '$(derive [''Test])', where 'Test'
is my test ADT. This makes me think that the overloaded 'toSElem'
functions defined by the instances in 'Text.StringTemplate.Instances'
are not being called? A cursory comparison to RJson, which the
HStringTemplate syb-with-class solution is based on, didn't lead me to
any obvious differences that I was missing.

For reference, my current configuration is (Sorry, it's an older
configuration, but the one I'm stuck with for now)
GHC  6.10.4 (Mac OS X 10.6.4, Intel)
HStringTemplate 0.6.3
syb-with-class0.6

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Emacs mode for Happy?

2010-12-03 Thread Edward Amsden
I'm planning on using Happy for my compiler construction class this
quarter. The only problem so far is that emacs keeps trying to mangle
my .y files because it assumes I mean them for yacc. Is there an emacs
mode for Happy or is it maybe time to also buckle down to learning
elisp and write one myself?
--
Edward Amsden
Undergraduate
Computer Science
Rochester Institute of Technology

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Question about TagSoup

2010-12-03 Thread Alex Rozenshteyn
I really wouldn't use tag soup for this.  Haskell has libraries specifically
for XML processing which might be better suited to your needs.

On Fri, Dec 3, 2010 at 5:59 AM, David Virebayre

> wrote:

> Hello café,
>
> I have seen tutorials about extracting information from a tag soup, but I
> have a different use case:
> I want to read a xml file, find a tag, change its content, and write the
> xml file back.
>
> This is an example of the files
>
> 
> http://ns.adobe.com/AdobeInDesign/idml/1.0/packaging"; DOMVersion="7.0">
> StoryTitle="$ID/" AppliedNamedGrid="n">
> OpticalMarginSize="12" FrameType="TextFrameType"
> StoryOrientation="Horizontal" StoryDirection="LeftToRightDirection"/>
> IncludeAllResources="false"/>
> AppliedParagraphStyle="ParagraphStyle/prix">
> AppliedCharacterStyle="CharacterStyle/$ID/[No character style]">
>zzznba5
>
>
>
> 
>
> Assuming I want to change the content of the "Content" tag, this is what I
> came up with (simplified), I'm using direct recursion. Is there a better way
> ?
>
> ts = do
>  soup <- parseTags `fmap` readFile "idml/h00/Stories/Story_ub9fad.xml"
>  writeFile "test" $ renderTagsOptions renderOptions{optMinimize = const
> True}
>   $ modif soup
>
> modif [] = []
> modif (x@(TagOpen "Content" []):TagText _m : xs) = x : TagText "modified"
> : modif xs
> modif (x:xs) = x : modif xs
>
> David.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
  Alex R
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] getErrorStatus in HXT

2010-12-03 Thread Tobias Schoofs

Hi,

I have some problems with the error processing in HXT.

Here is a trivial example:

e <- runX (transformDoc [] someRules src dst)

transformDoc cfg rules src dst =
   configSysVars cfg >>>
   readDocument  [] src >>>
   rules >>> -- some transformations
   writeDocument [] dst >>>
   getErrStatus

I would expect "e" to contain an error value >= c_err for the case where 
any of the processing steps in transformDoc fails. But it does not, even 
with an io error on writeDocument.


I guess I misunderstand "getErrStatus" in some way. Any idea?

Thanks,

Tobias


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most images broken on haskellwiki pages

2010-12-03 Thread Edward Z. Yang
This was because, for some odd reason, the images were stored using
absolute URLs and not real wikilinks. I've fixed most of them on that
page.

Edward

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most images broken on haskellwiki pages

2010-12-03 Thread Eugene Kirpichov
Thanks to Edward Z Yang - the problem has gone.

The point is that I used raw URLs to include these images, but I
should have used [[Image:MyImage.png]].

3 декабря 2010 г. 15:22 пользователь Eugene Kirpichov
 написал:
> 2010/12/3 Thomas Schilling :
>> Should be fixed.  PDF previews are currently broken, but images should be 
>> fine.
> Unfortunately they aren't. Please take a look at
> http://www.haskell.org/haskellwiki/Timeplot .
>
>>
>> 2010/12/3 Eugene Kirpichov :
>>> Hello,
>>>
>>> Any news on this one?
>>>
>>>
>>>
>>> 01.12.2010, в 11:53, Yitzchak Gale  написал(а):
>>>
 Eugene Kirpichov wrote:
> I looked at a couple pages of mine...
> and looks
> like the vast majority of images are not displaying.

 This probably has to do with moving the wiki to the
 new server during the past few days. I forwarded your
 email to the admin team there for them to have a look.

 Regards,
 Yitz
>>>
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>
>>
>>
>> --
>> Push the envelope. Watch it bend.
>>
>
>
>
> --
> Eugene Kirpichov
> Senior Software Engineer,
> Grid Dynamics http://www.griddynamics.com/
>



-- 
Eugene Kirpichov
Senior Software Engineer,
Grid Dynamics http://www.griddynamics.com/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most images broken on haskellwiki pages

2010-12-03 Thread Eugene Kirpichov
2010/12/3 Thomas Schilling :
> Should be fixed.  PDF previews are currently broken, but images should be 
> fine.
Unfortunately they aren't. Please take a look at
http://www.haskell.org/haskellwiki/Timeplot .

>
> 2010/12/3 Eugene Kirpichov :
>> Hello,
>>
>> Any news on this one?
>>
>>
>>
>> 01.12.2010, в 11:53, Yitzchak Gale  написал(а):
>>
>>> Eugene Kirpichov wrote:
 I looked at a couple pages of mine...
 and looks
 like the vast majority of images are not displaying.
>>>
>>> This probably has to do with moving the wiki to the
>>> new server during the past few days. I forwarded your
>>> email to the admin team there for them to have a look.
>>>
>>> Regards,
>>> Yitz
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Push the envelope. Watch it bend.
>



-- 
Eugene Kirpichov
Senior Software Engineer,
Grid Dynamics http://www.griddynamics.com/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most images broken on haskellwiki pages

2010-12-03 Thread Thomas Schilling
Should be fixed.  PDF previews are currently broken, but images should be fine.

2010/12/3 Eugene Kirpichov :
> Hello,
>
> Any news on this one?
>
>
>
> 01.12.2010, в 11:53, Yitzchak Gale  написал(а):
>
>> Eugene Kirpichov wrote:
>>> I looked at a couple pages of mine...
>>> and looks
>>> like the vast majority of images are not displaying.
>>
>> This probably has to do with moving the wiki to the
>> new server during the past few days. I forwarded your
>> email to the admin team there for them to have a look.
>>
>> Regards,
>> Yitz
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Push the envelope. Watch it bend.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] haskell.org migration complete

2010-12-03 Thread Simon Marlow

On 02/12/2010 23:48, Claus Reinke wrote:

The haskell.org server migration is now complete.
Please let us know if you have any problems.


Beginning this week, the majority of mails from haskell.org
lists seem to end up in my ISP's spam filter. That would be
Yahoo! - I wonder whether others here have seen a similar
effect when checking their spam filters?

I don't know whether this is caused by the migration, but
it made me wonder about something I recalled reading
about whitelisting mailing list senders with ISPs, and a
little search found the following:

http://en.wikipedia.org/wiki/Whitelist
http://help.yahoo.com/l/us/yahoo/mail/postmaster/basics/
http://help.yahoo.com/l/us/yahoo/mail/postmaster/forms_index.html
http://help.yahoo.com/l/us/yahoo/mail/postmaster/bulkv2.html
http://www.novablog.info/2008/10/21/5-simple-steps-to-improving-e-mail-deliverability/


So it might be related to the new server. Is whitelisting
something the mailing list hosting service should deal
with, or is that left to the customer?


I'm fairly sure GMail at least whitelists haskell.org, because I get 
spam sent via the -ow...@haskell.org aliases that invariably ends 
up in my inbox, apparently bypassing GMail's usually very good spam 
filtering.


Cheers,
Simon

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Question about TagSoup

2010-12-03 Thread David Virebayre
Hello café,

I have seen tutorials about extracting information from a tag soup, but I
have a different use case:
I want to read a xml file, find a tag, change its content, and write the xml
file back.

This is an example of the files


http://ns.adobe.com/AdobeInDesign/idml/1.0/packaging"; DOMVersion="7.0">
   
   
   
   
   
   zzznba5
   
   
   


Assuming I want to change the content of the "Content" tag, this is what I
came up with (simplified), I'm using direct recursion. Is there a better way
?

ts = do
 soup <- parseTags `fmap` readFile "idml/h00/Stories/Story_ub9fad.xml"
 writeFile "test" $ renderTagsOptions renderOptions{optMinimize = const
True}
  $ modif soup

modif [] = []
modif (x@(TagOpen "Content" []):TagText _m : xs) = x : TagText "modified" :
modif xs
modif (x:xs) = x : modif xs

David.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Digests

2010-12-03 Thread Serguey Zefirov
2010/12/3 Permjacov Evgeniy :
>>> */me wrote it into to_read list. The problem is, however, that block
>>> ciphers are quite unfriendly to plain word8 streams. It is not a deadly
>>> problem, but i'd like to avoid block collections.
>> All one-way hashes do block collections. This is unavoidable.
> Why ? Is there some math behind this proposition ?

This is hard - to add single byte into the sum with cryptographic (or
near cryptographic) security. To quote Wikipedia again: "The avalanche
effect is evident if, when an input is changed slightly (for example,
flipping a single bit) the output changes significantly (e.g., half
the output bits flip)."

http://en.wikipedia.org/wiki/Avalanche_effect

This is true for hashes too. Hash should change about half of the
random output bits when single bit of input changes. Especially if you
aim to tamper-proof hashes. You have to have that property on every
round of hashing, because you don't know when to stop. For bytes, you
have to guarantee that you get an avalanche effect for every byte - it
means, that you have to transform your entire block plus input byte in
an expensive way. MD5 and all other hashes have internal state of
various size, they all keep input blocks to make hashing transform
less expensive.

Fast methods like sum-modulo-poly (CRC variants) or linear
congruential generators do not have good avalanche property when used
for stream hashing or encryption. Even their combination (one in ZIP
encryption) wasn't strong enough.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Digests

2010-12-03 Thread Permjacov Evgeniy
On 12/03/2010 10:48 AM, Serguey Zefirov wrote:
> 2010/12/3 Permjacov Evgeniy :
>>> Most of the time you can get away with usual block ciphers (and even
>>> with weaker parameters). There is a scheme that transforms block
>>> cipher into hash function:
>>> http://en.wikipedia.org/wiki/CRHF#Hash_functions_based_on_block_ciphers
>> */me wrote it into to_read list. The problem is, however, that block
>> ciphers are quite unfriendly to plain word8 streams. It is not a deadly
>> problem, but i'd like to avoid block collections.
> All one-way hashes do block collections. This is unavoidable.
Why ? Is there some math behind this proposition ?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe