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.  FFI foreignPtr construction (PICCA Frederic-Emmanuel)
   2. Re:  Parsing 'A's and then ('A's or 'B's) (Francesco Ariis)
   3. Re:  Custom type classes (Guillaume Bouchard)
   4. Re:  Ambigous type variable, why this error? (David McBride)
   5. Re:  Parsing 'A's and then ('A's or 'B's) (Ulrik Rasmussen)


----------------------------------------------------------------------

Message: 1
Date: Wed, 27 Jan 2016 12:50:17 +0000
From: PICCA Frederic-Emmanuel
        <frederic-emmanuel.pi...@synchrotron-soleil.fr>
To: "beginners@haskell.org" <beginners@haskell.org>
Subject: [Haskell-beginners] FFI foreignPtr construction
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53b3020...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="Windows-1252"

Hello,

since the last time I think that I understand how to manage Ptr, now I woud 
like to masterize the ForeignPtr in order to let haskell managed the life of my 
C objects.
So I try to create a Geoemtry object like this.

-- data Geometry
newtype Geometry = Geometry (Ptr Geometry) deriving (Show, Storable)

newGeometry :: Factory -> ForeignPtr Geometry
newGeometry f = unsafePerformIO $ do
                  geometry <- c_hkl_factory_create_new_geometry f
                  newForeignPtr c_hkl_geometry_free geometry

foreign import ccall safe "hkl.h hkl_factory_create_new_geometry"
  c_hkl_factory_create_new_geometry :: Factory
                                    -> IO (Geometry)

foreign import ccall safe "hkl.h &hkl_geometry_free"
  c_hkl_geometry_free :: FunPtr (Geometry -> IO ())



the C signature are 

HKLAPI HklGeometry *hkl_factory_create_new_geometry(const HklFactory *self) 
HKL_ARG_NONNULL(1);

HKLAPI void hkl_geometry_free(HklGeometry *self) HKL_ARG_NONNULL(1);


But when I try to compile this code, I get this error message


1 of 1] Compiling Hkl.C            ( src/Hkl/C.hs, dist/build/Hkl/C.o )

src/Hkl/C.hs:51:33:
    Couldn't match type ?Geometry? with ?Ptr Geometry?
    Expected type: GHC.ForeignPtr.FinalizerPtr Geometry
      Actual type: FunPtr (Geometry -> IO ())
    In the first argument of ?newForeignPtr?, namely
      ?c_hkl_geometry_free?
    In a stmt of a 'do' block:
      newForeignPtr c_hkl_geometry_free geometry

src/Hkl/C.hs:51:53:
    Couldn't match expected type ?Ptr Geometry?
                with actual type ?Geometry?
    In the second argument of ?newForeignPtr?, namely ?geometry?
    In a stmt of a 'do' block:
      newForeignPtr c_hkl_geometry_free geometry

I do not understand what is wrong in my code

thanks if you can help

Frederic 

------------------------------

Message: 2
Date: Wed, 27 Jan 2016 13:48:55 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Parsing 'A's and then ('A's or 'B's)
Message-ID: <20160127124855.ga32...@casa.casa>
Content-Type: text/plain; charset=us-ascii

On Wed, Jan 27, 2016 at 01:34:29PM +0100, Ulrik Rasmussen wrote:
> The language is recognized by a relatively simple DFA (attached), so the
> simplest solution (I think) is to just encode that:
> 
>     module Main where
> 
>     import Text.Parsec
>     import Text.Parsec.String
> 
>     p :: Parser ()
>     p = char 'A' >> ((char 'A' >> sA) <|> (char 'B' >> sB))
>       where
>         sA = (char 'A' >> sA) <|> (char 'B' >> sB) <|> return ()
>         sB = (char 'B' >> sB) <|> return ()

I am probably missing something: say we have an "AAB" string, how does
this check that it is `compatible` with [x,y] or [x,x,y] or [x,y,y]
(or not compatible with [x,x,x], etc.)?


------------------------------

Message: 3
Date: Wed, 27 Jan 2016 14:28:55 +0100
From: Guillaume Bouchard <guillaum.bouchard+hask...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Custom type classes
Message-ID:
        <CAGh0HCC1ZmipGg47jZ=xa4ryt8d3+c+kq8h4+twxw_j9a+h...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Wed, Jan 27, 2016 at 11:11 AM, Imants Cekusins <ima...@gmail.com> wrote:
>> `fmap` types mean that `a` should be anything, and not something
> constrained.
>
> just wondering: is it something specific to Functor class or does this
> hold for any class declaration:
>
> (a -> b)
> is not the same as
> ... a => (a -> b)

a => (a -> b) does not really mean anything as far as I know because a
is not a constraint (i.e: a typeclass).

Perhaps you mean something such as

Constraint a => (a -> b)

> in other words, if class expects (a -> b) with any a, instance must
> not constrain a.

However I discovered the `ConstraintKinds` extension which may improve
the situation.

-- 
G.


------------------------------

Message: 4
Date: Wed, 27 Jan 2016 09:57:33 -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] Ambigous type variable, why this
        error?
Message-ID:
        <CAN+Tr42KkGWgc8c8kYipx=spx9vy1pf1oghcvvmso3lsqbg...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

If I had to guess, it is ambiguous because there are many valid instances
it could use.

>:t  (Open [undefined :: Int]) <: (undefined)
(Open [undefined :: Int]) <: (undefined) :: Bool
>:t  (Open [undefined :: Crust Int]) <: (undefined)
(Open [undefined :: Crust Int]) <: (undefined) :: Bool
>:t  (Open [undefined :: Crust (Crust Int)]) <: (undefined)
(Open [undefined :: Crust (Crust Int)]) <: (undefined) :: Bool

However, I do not get the same error as you do on ghc 7.10.3, so I am
unsure.

<interactive>:2:9:
    No instance for (Num a0) arising from the literal ?1?
    The type variable ?a0? is ambiguous
    Note: there are several potential instances:
      instance Num Integer -- Defined in ?GHC.Num?
      instance Num Double -- Defined in ?GHC.Float?
      instance Num Float -- Defined in ?GHC.Float?
      ...plus two others
    In the expression: 1
    In the first argument of ?Open?, namely ?[1, 2, 3]?
    In the first argument of ?(<:)?, namely ?(Open [1, 2, 3])?

<interactive>:2:17:
    No instance for (Ord a0) arising from a use of ?<:?
    The type variable ?a0? is ambiguous
    Note: there are several potential instances:
      instance (Ord a, Ord b) => Ord (Either a b)
        -- Defined in ?Data.Either?
      instance forall (k :: BOX) (s :: k). Ord (Data.Proxy.Proxy s)
        -- Defined in ?Data.Proxy?
      instance (GHC.Arr.Ix i, Ord e) => Ord (GHC.Arr.Array i e)
        -- Defined in ?GHC.Arr?
      ...plus 28 others
    In the expression: (Open [1, 2, 3]) <: (Open ([1, 2, 4]))
    In an equation for ?it?:
        it = (Open [1, 2, 3]) <: (Open ([1, 2, 4]))

If I remove the Ord constraint on the Poset (Crust a) instance, It changes
from ambiguous Ord to ambiguous Eq.

On Wed, Jan 27, 2016 at 3:44 AM, martin <martin.drautzb...@web.de> wrote:

> Hello all,
>
> here is something where I don't understand the second error:
>
> *Main> (Open [1,2,3]) <: (Open ([1,2,4]))
>
> <interactive>:94:8:
>     No instance for (Num a0) arising from the literal ?1?
>     The type variable ?a0? is ambiguous
>     Note: there are several potential instances:
>       instance Num Double -- Defined in ?GHC.Float?
>       instance Num Float -- Defined in ?GHC.Float?
>       instance Integral a => Num (GHC.Real.Ratio a)
>         -- Defined in ?GHC.Real?
>       ...plus 46 others
>     In the expression: 1
>     In the first argument of ?Open?, namely ?[1, 2, 3]?
>     In the first argument of ?(<:)?, namely ?(Open [1, 2, 3])?
>
> Okay, I understand this one, but why this:
>
> <interactive>:94:16:
>     No instance for (Poset a0) arising from a use of ?<:?
>     The type variable ?a0? is ambiguous
>     Note: there are several potential instances:
>       instance (Eq a, Ord a, Poset a) => Poset (Crust a)    -- <== yes,
> yes, yes, take this one
>         -- Defined at
> /home/martin/projects/haskell/currychicken/opal/Poset.hs:83:10
>       instance (Eq a, Ord a, Poset a) => Poset (PsSet a)
>         -- Defined at
> /home/martin/projects/haskell/currychicken/opal/Poset.hs:50:10
>       instance (Eq a, Ord a, Poset a) => Poset (PsList a)
>         -- Defined at
> /home/martin/projects/haskell/currychicken/opal/Poset.hs:46:10
>       ...plus one other
>     In the expression: (Open [1, 2, 3]) <: (Open ([1, 2, 4]))
>     In an equation for ?it?:
>         it = (Open [1, 2, 3]) <: (Open ([1, 2, 4]))
>
> The operands of (<:) are clearly Crusts, so (PsSet a) or (PsList a)
> shouldn't be options
>
> *Main> :t Open [1,2,3]
> Open [1,2,3] :: Num a => Crust a
> *Main>
>
> The problem goes away, when I make sure my list elements are Ints
>
> *Main> (Open [1::Int,2,3]) <: (Open ([1,2,4]))
> False
>
> But why do I see the second error at all?
>
>
> Here is the complete code:
>
> {-# Language FlexibleInstances #-}
> {-# Language UndecidableInstances #-}
>
> import qualified Data.List as L
> import qualified Data.Set as S
> import Debug.Trace
> import Test.QuickCheck hiding ((==>))
>
> ------------------------------------------------------------
> class Poset p where
> ------------------------------------------------------------
>         (<:) :: p -> p -> Bool
>
> instance Poset Int where (<:) = (==)
>
> ------------------------------------------------------------
> -- Alternatives
> ------------------------------------------------------------
> newtype PsList a = PsList [a]
> newtype PsSet  a = PsSet (S.Set a)
>
> isSubPolist :: (Poset a) => [a] -> [a] ->Bool
> isSubPolist as bs = all includedInBs as
>         where
>             includedInBs a = any (a <:) bs
>
> instance (Eq a, Ord a, Poset a) => Poset (PsList a)
>         where
>             (PsList as) <: (PsList bs) = isSubPolist as bs
>
> instance (Eq a, Ord a, Poset a) => Poset (PsSet a)
>         where
>             (PsSet as) <: (PsSet bs) = isSubPolist (S.toList as) (S.toList
> bs)
>
>
> ------------------------------------------------------------
> data Crust a = Open [a] | Closed [a]
> ------------------------------------------------------------
>              deriving (Eq, Ord, Show)
>
> instance (Eq a, Ord a, Poset a) => Poset (Crust a)
>         where
>             (<:) (Open as) (Closed bs)   = False
>             (<:) (Closed as) (Closed bs) = as == bs
>
>             (<:) (Open _) (Open [])         =  True
>             (<:) (Open []) (Open _)         =  False
>             (<:) (Open (x:xs)) (Open (y:ys)) = x <: y &&
>                                                (Open xs) <: (Open ys)
>
>             (<:) (Closed _) (Open [])   = True
>             (<:) (Closed []) (Open _)   = False
>             (<:) (Closed (x:xs)) (Open (y:ys))  = x <: y &&
>                                                   (Closed xs) <: (Open ys)
>
>
> _______________________________________________
> 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/20160127/f613e287/attachment-0001.html>

------------------------------

Message: 5
Date: Wed, 27 Jan 2016 16:11:23 +0100
From: Ulrik Rasmussen <hask...@utr.dk>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Parsing 'A's and then ('A's or 'B's)
Message-ID: <56a8de1b.1010...@utr.dk>
Content-Type: text/plain; charset=utf-8; format=flowed

On 2016-01-27 13:48, Francesco Ariis wrote:
> On Wed, Jan 27, 2016 at 01:34:29PM +0100, Ulrik Rasmussen wrote:
> > The language is recognized by a relatively simple DFA (attached), so the
> > simplest solution (I think) is to just encode that:
> >
> >      module Main where
> >
> >      import Text.Parsec
> >      import Text.Parsec.String
> >
> >      p :: Parser ()
> >      p = char 'A' >> ((char 'A' >> sA) <|> (char 'B' >> sB))
> >        where
> >          sA = (char 'A' >> sA) <|> (char 'B' >> sB) <|> return ()
> >          sB = (char 'B' >> sB) <|> return ()
>
> I am probably missing something: say we have an "AAB" string, how does
> this check that it is `compatible` with [x,y] or [x,x,y] or [x,y,y]
> (or not compatible with [x,x,x], etc.)?
>

Oh, I read Simon's question as being constrained to the specific problem 
[x, y] (i.e. recognizing AA*(AA* + BB*)).
If the problem is to run any list of parsers such as [x,y,x,x], then 
this won't work.


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 91, Issue 34
*****************************************

Reply via email to