Re: [Haskell-cafe] A question regarding reading CPP definitions from a C header

2013-10-07 Thread Carl Howells
Have you looked into using hsc2hs? If I understand your problem, it's
designed exactly to solve it.

-- 
Carl


On Mon, Oct 7, 2013 at 12:20 PM, Ömer Sinan Ağacan omeraga...@gmail.comwrote:

 Thanks for your answer, looks like this is my only option to do this.

 Can you provide some information about what does parameters of
 runCpphsReturningSymTab stands for? I made several attempts but
 couldn't get any useful return value.

 For example, I have no idea what does third parameter does. Also,
 second parameter.

 Thanks,

 ---
 Ömer Sinan Ağacan
 http://osa1.net


 2013/10/7 Malcolm Wallace malcolm.wall...@me.com:
  If you use cpphs as a library, there is an API called
 runCpphsReturningSymTab.  Thence you can throw away the actual
 pre-preprocessed result text, keep only the symbol table, and lookup
 whatever macros you wish to find their values.  I suggest you make this
 into a little code-generator, to produce a Haskell module containing the
 values you need.
 
  On 5 Oct 2013, at 21:37, Ömer Sinan Ağacan wrote:
 
  Hi all,
 
  Let's say I want to #include a C header file in my Haskell library
  just to read some macro definitions. The C header file also contains
  some C code. Is there a way to load only macro definitions and not C
  code in #include declarations in Haskell?
 
  What I'm trying to do is I'm linking my library against this C library
  but I want to support different versions of this C library, so I want
  to read it's version from one of it's header files. The problem is the
  header file contains some C code and makes my Haskell source code
  mixed with C source before compilation.
 
  Any suggestions would be appreciated,
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Carl Howells
Monoid and Alternative are not the same.  There is a very important
difference between them:

class Alternative f where
(|) :: f a - f a - f a
...

class Monoid a where
mappend :: a - a - a
...

The equivalent to Alternative is MonadPlus, not Monoid.  The kinds
matter.  In Alternative, you are guaranteed that the type that f is
applied to cannot affect the semantics of (|).  As has been already
demonstrated aptly, the type a in the instance Monoid a = Monoid
(Maybe a) matters quite a lot.

Carl

On Thu, Dec 15, 2011 at 8:04 AM, Yves Parès limestr...@gmail.com wrote:
 So why don't we use First and Last with the Alternative interface too?

 It's indeed weird the Maybe doesn't react the same way with Alternative and
 Monoid.


 2011/12/15 Anthony Cowley acow...@gmail.com

 On Dec 15, 2011, at 10:19 AM, Brent Yorgey wrote:

  On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:
 
  So at the end of the day... what is the point of even making Maybe and
  [] instances of Alternative?
 
  The Alternative and Monoid instances for [] are equivalent.  However,
  the Alternative and Monoid instances for Maybe are not. To wit:
 
  (Just (Sum  4)) | (Just (Sum 3))
   Just (Sum {getSum = 4})
 
  (Just (Sum 4)) `mappend` (Just (Sum 3))
   Just (Sum {getSum = 7})

 We already have,

  First (Just (Sum 4)) `mappend` First (Just (Sum 3))
 First {getFirst = Just (Sum {getSum = 4})}

 So the overlap of apparent Alternative and Monoid functionality remains.
 This just represents an opportunity for the caller to select the monoid they
 want.

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



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


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


Re: [Haskell-cafe] Splitting off many/some from Alternative

2011-12-12 Thread Carl Howells
 There is absolutely no implication of consuming anything in the definitions
 of many or some. This is how they happen to behave when used in the context
 of some parsing libraries, but that's all. If many or some always go into an
 infinite loop for some Alternative instance, then I suspect that the
 instance itself is either broken or shouldn't exist.

So, then...  The instance for Maybe shouldn't exist?

Prelude Control.Applicative some Nothing
Nothing
Prelude Control.Applicative some $ Just ()
^CInterrupted.

Carl

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


Re: [Haskell-cafe] Splitting off many/some from Alternative

2011-12-12 Thread Carl Howells
 Don't be silly. The purpose of some and many is to be used with combinators
 that are expected to fail sometimes. If you use them with combinators that
 always succeed, of course you're going to get an infinite loop. Would you
 propose to ban recursive functions because they might not terminate?

 Apparently the confusion here lies with the fact that the documentation for
 some and many are too terse for their behaviour to be easily understood.
 That's a whole different category of problem than ban them!.

Well, as I read it, the whole point of this thread was They don't
make sense for many instances of Alternative.  They should be moved to
a different class.  It sounded like you were arguing that any
instance of Alternative where they don't make sense shouldn't be an
instance of Alternative, instead.

Carl

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


Re: [Haskell-cafe] pointer equality

2011-07-20 Thread Carl Howells
On Tue, Jul 19, 2011 at 11:14 PM, yi huang yi.codepla...@gmail.com wrote:
 2011/7/20 Eugene Kirpichov ekirpic...@gmail.com

 reallyUnsafePointerEq#, and it really is as unsafe as it sounds :)

 Why is it so unsafe? i can't find any documentation on it.
 I think always compare pointer first is a good optimization.

False positives and false negatives are both possible, depending on GC
timing.  Don't use it, unless you know why it can result in both false
positives and false negatives, and you know why neither of those are
bad for your use case.

I'm not aware of any use case that's resilient to both failure modes, offhand.

Carl

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


Re: [Haskell-cafe] The Typeable class is changing

2011-07-11 Thread Carl Howells
This will affect snap-core and heist, of the things I've provided
Typeable instances for.

In snap-core, deriving makes it use the internal module name, rather
than the canonical location of the type.  This causes issues with the
Hint library, so it's worked around by using a manual instance of
Typeable.

Alternatively, heist involves a monad transformer.  deriving
Typeable fails for monad transformers, because it can't handle TyCons
with arguments of kind other than *.

So, this change will hit me for two different reasons, and sadly
involve using CPP to control how things are compiled.

Carl

On Mon, Jul 11, 2011 at 11:18 AM, Yitzchak Gale g...@sefer.org wrote:
 Simon Marlow has announced[1] on the Haskell Libraries
 list that the Typeable class is changing.

 The standard way to create a Typeable instance is
 just to derive it. If you do that, you will not be affected
 by this change.

 But it seems that many packages create Typeable
 instances by explicitly using mkTyCon. If your package
 does this, it will eventually break, after a deprecation
 period.

 Please respond to this thread if you own a package
 that will be affected by this change.

 Can someone who has quick access to the entire contents
 of Hackage please do a grep and find out exactly which
 packages on Hackage will be affected? Thanks.

 -Yitz

 [1] http://www.haskell.org/pipermail/libraries/2011-July/016546.html

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


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


Re: [Haskell-cafe] Examples for the problem

2011-03-02 Thread Carl Howells
Actually, It's not | that's different, it's the string combinator.
In Parsec, string matches each character one at a time.  If the match
fails, any partial input it matched is consumed.  In attoparsec,
string matches either the entire thing or not, as a single step.  If
it fails to match, no input is consumed.

Carl

On Wed, Mar 2, 2011 at 9:51 AM, Stephen Tetley stephen.tet...@gmail.com wrote:
 Actually this is stranger than I thought - from testing it seems like
 Attoparsec's (|) is different to Parsec's. From what I'm seeing
 Attoparsec appears to do a full back track for (|) regardless of
 whether the string lexer is wrapped in try, whereas Parsec needs try
 to backtrack.

 On 2 March 2011 16:24, Stephen Tetley stephen.tet...@gmail.com wrote:


 *try* means backtrack on failure, and try the next parser. So if you
 want ill formed strings to throw an error if they aren't properly
 enclosed in double quotes don't use try.

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


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


Re: [Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-19 Thread Carl Howells
Sequence isn't necessarily strict.  Sequence, rather necessarily,
depends on the semantics of (=) in that monad.

Prelude Control.Monad.Identity runIdentity $ take 10 `liftM` sequence
(map return $ repeat 5)
[5,5,5,5,5,5,5,5,5,5]

What matters is if (=) is strict in its first argument.  The
Identity Monad provided by mtl and transformers is not strict in the
first argument of (=).  Hence sequence isn't strict in that Identity
Monad.

Compare to IO, where (=) is strict in its first argument:

Prelude Control.Monad.Identity take 10 `liftM` sequence (map return $
repeat 5) :: IO [Int]
^CInterrupted.

After a while, I got bored and interrupted it.

Anyway.  There's no documentation on the (non-)strictness of sequence,
because it isn't actually defined.  It depends on the choice of m.

Carl Howells

On Sun, Dec 19, 2010 at 1:58 PM, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 On Sunday 19 December 2010 22:18:59, Jacek Generowicz wrote:
 
  The reason this doesn't stop where you expect it to is that sequence
  is
  effectively strict

 That would explain it. Thank you.

 Where is this fact documented? I mostly rely on Hoogle, which gets me to


 http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude
.html#v

 :sequence

 which says nothing about strictness.

 How could I have known this without having to bother anyone else?


 Well, you can deduce it from sequence's type. That's of course not
 something you immediately see, but in hindsight, it's pretty easy to
 understand.

 sequence :: Monad m = [m a] - m [a]

 So, basically all sequence can do is use (=) and return.
 Reasonably,

 sequence [] = return []

 is the only thing that's possible. For nonempty lists,

 sequence (x:xs) = ?

 Well, what can sequence do? It has to do something with x and something
 with xs, the only reasonable thing is to call sequence on the tail and run
 x, combining x's result and the result of sequence xs.

 One can choose the order, but

 sequence (x:xs) = do
   a - x
   as - sequence xs
   return (a:as)

 is the most sensible thing.

 Now, that means before sequence can deliver anything, it has to run all
 actions (because if any action fails, sequence fails and that can't be
 known before all actions have been run).


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


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


Re: [Haskell-cafe] Haskellers.com profiles: advice requested

2010-10-06 Thread Carl Howells
 Complete side note: it's kind of funny that OpenID let's you specify
 some completely arbitrary string to appear in the resulting
 webpage[2].

Any server with that behavior is out of spec.  Operating securely
requires checking the return_to value against the trust_root, and
checking that the return_to value is a valid url.

But wordpress being out of spec is what was observed to start this,
anyway.  So what's the surprise?

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


Re: [Haskell-cafe] Can't make a derived instance of `Typeable (A B)': `A' has arguments of kind other than `*'

2010-09-24 Thread Carl Howells
You can't automatically derive Typeable for any type with a kind that
has any arguments that aren't of type *.

For instance, you can derive an instance for a type with a kind *, *
- *, or even * - * - * - * - * - *, but not one with a kind (*
- *) - *.

And your type A there has kind (* - *) - *.  You'll have to manually
write a Typeable instance if you want one.  The process is somewhat
trickier than you might expect, due to the fact that Typeable does
some unsafe stuff.  But there are plenty of examples for how to do it
safely.

Enjoy the fun of not having kind polymorphism!

Carl Howells

On Fri, Sep 24, 2010 at 1:18 PM, Christopher Done
chrisd...@googlemail.com wrote:
 Suppose I have a data type:

 data A f = A { a :: f Integer }

 why can't I derive a Typeable instance like so?

 deriving instance Typeable (A Maybe)

 I get:

    Can't make a derived instance of `Typeable (A Maybe)':
      `A' has arguments of kind other than `*'
    In the stand-alone deriving instance for `Typeable (A Maybe)'

 I would have expected that the arguments are instantiated by the Maybe
 type constructor and thus the type of A would be:

 Maybe Integer - A

 What am I missing?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] MonadCatchIO and bracket.

2010-06-28 Thread Carl Howells
While working this weekend on the Snap web framework, I ran into a
problem.  Snap implements MonadCatchIO, so I thought I could just use
bracket to handle resource acquisition/release in a safe manner.
Imagine my surprise when bracket simply failed to run the release
action sometimes.

I quickly determined the times when it doesn't run are when Snap's
monadic short-circuiting is used.  I dug into the source of bracket
(in the transformers branch, though the mtl branch has the same
behavior in these cases, with slightly different code), and the reason
why quickly became obvious:

-- | Generalized version of 'E.bracket'
bracket :: MonadCatchIO m = m a - (a - m b) - (a - m c) - m c
bracket before after thing = block $ do
  a - before
  r - unblock (thing a) `onException` after a
  _ - after a
  return r

When monadic short-circuiting applies, the _ - after a line gets
completely ignored.  In discussions with #haskell on this topic, it
quickly became clear that for any monad transformer that can affect
control flow, the definition of bracket in MonadCatchIO doesn't keep
the guarantee provided by bracket in Control.Exception, which is that
the after action will be run exactly once.

Because of that, I think bracket needs to be a class function.
Furthermore, I think it needs to be a new class, ie

class MonadCatchIO m = MonadBracketIO m where
   bracket :: m a - (a - m b) - (a - m c) - m c

This would allow its definition in cases where it makes sense (Snap or
MaybeT IO), but it could be left out in cases where it doesn't make
sense, like ListT IO, even though MonadCatchIO makes sense there.

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