Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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.  Named fields in data types (legajid)
   2. Re:  Named fields in data types (Chadda? Fouch?)
   3. Re:  Question on data/type (Phillip Pirrip)
   4. Re:  Question on data/type (Daniel Fischer)
   5. Re:  Named fields in data types (legajid)
   6. Re:  Named fields in data types (Edward Z. Yang)
   7.  Windows API and FFI (i?fai)
   8. Re:  Windows API and FFI (Jeff Zaroyko)


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

Message: 1
Date: Tue, 17 Nov 2009 22:24:26 +0100
From: legajid <lega...@free.fr>
Subject: [Haskell-beginners] Named fields in data types
To: beginners@haskell.org
Message-ID: <4b03148a.10...@free.fr>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello,
i've some trouble with named fields in data types.

data Carnet = Adresse  { nom :: String, cp :: Integer, ville :: String  }
        |
       Telephone {nom::String, telnum::String}
    deriving Show

contact01 = Adresse "Didier" 51100 "Reims"
contact02 = Adresse {nom="Laure", cp=0} -- line 1
--contact02 Adresse { ville="Nogent" }       -- line 2
--contact02 { ville="Nogent" }                     -- line 3
contact03=Telephone "Didier" "0326..."       -- line 4

When loading this source :
line 1 says "warning : Fields not initialized :ville
line 2 and 3 when uncommented give parse error (possibly indentation)

I'm ok with line 1.
Is it possible to write such things as line2 or 3 ? Which syntax ?

Thanks for help.
Didier.



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

Message: 2
Date: Tue, 17 Nov 2009 22:55:05 +0100
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Named fields in data types
To: legajid <lega...@free.fr>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0911171355o5dc7f19y5f19563bca298...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Tue, Nov 17, 2009 at 10:24 PM, legajid <lega...@free.fr> wrote:
> Hello,
> i've some trouble with named fields in data types.
>
> data Carnet = Adresse  { nom :: String, cp :: Integer, ville :: String  }
>       |
>      Telephone {nom::String, telnum::String}
>   deriving Show
>
> contact01 = Adresse "Didier" 51100 "Reims"
> contact02 = Adresse {nom="Laure", cp=0} -- line 1
> --contact02 Adresse { ville="Nogent" }       -- line 2
> --contact02 { ville="Nogent" }                     -- line 3
> contact03=Telephone "Didier" "0326..."       -- line 4
>
> When loading this source :
> line 1 says "warning : Fields not initialized :ville
> line 2 and 3 when uncommented give parse error (possibly indentation)
>
> I'm ok with line 1.
> Is it possible to write such things as line2 or 3 ? Which syntax ?

line 2 appears correct except you forgot the "="... Of course some
fields aren't initialized so you may have a problem if you try to
access them later on.
(La ligne 2 est correcte sauf que tu as oublié le égal "="... Bien sûr
certains des champs ne sont pas initialisés et ça pourrait poser
problème si tu essaies d'y accéder plus tard)

Note that you can also create a new value with some fields in common
with an old value, for instance :
(Note que tu peux aussi créer une nouvelle valeur partageant un
certain nombre de champs avec une autre valeur déjà déclarée)

> contact01 = Adresse "Didier" 51100 "Reims"
> contact02 = contact01 { nom = "Charles" }

Which leads to the practice of using records to create a "default
setting" value where you just modify the field that concern you.
(Ce qui a donné lieu à l'idiome qui consiste à utiliser un type
enregistrement (avec des champs nommés) pour les configuration avec
une valeur "réglage par défaut" dont on ne modifie que les champs qui
nous intéresse)

> main = xmonad defaultConfig {terminal = "konsole"}

-- 
Jedaï


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

Message: 3
Date: Tue, 17 Nov 2009 21:46:45 -0500
From: Phillip Pirrip <ppir...@gmail.com>
Subject: Re: [Haskell-beginners] Question on data/type
To: beginners@haskell.org
Message-ID: <de32292c-b1fb-4bc4-a0c5-42a5d16d7...@gmail.com>
Content-Type: text/plain; charset=us-ascii

Hi,

Thanks everyone for their patience on my question and took the time to write 
back.  I was thinking to re-phrase my question (to correct some typo etc), but 
many of you have already guessed my intent. I am trying to write a simple 
Matrix library, as my little learning exercise, so 

TypeConA : Scalar
TypeConB : 1D array
TypeConC : 2D array /matrix.

So I would like to have one typeclass for operations like Scalar +/* Matrix etc.

Felipe: you are way ahead of me (like showing me the answer before I do my 
exam), and I really appreciate your example code, since that is the level of 
understanding of Haskell I am looking forward to.  I don't think I really 
understand the code yet, but I will give it a try and let you know. As this 
moment my level of understanding is basic Haskell syntax, basic Monad (going to 
try Monad/IArray for in-place non-destruction update) and just started to read 
up on Control.Applicative (and arrows) and Existential types.  I have never 
even heard of phantom types until now.

BTW, how do I generate "literate" Haskell code?  I keep reading it but I still 
don't know how to make one (I am assuming it is more complicated then just type 
the code in with ">" in emacs).

//pip


On 2009-11-17, at 6:40 AM, Felipe Lessa wrote:

> (This e-mail is literate Haskell)
> 
> Not that this is the right solution to your problems, but...
> 
>> {-# LANGUAGE GADTs, EmptyDataDecls,
>>             FlexibleInstances, FlexibleContexts #-}
>> 
>> import Control.Applicative
> 
> This requires EmptyDataDecls:
> 
>> data TypeConA
>> data TypeConB
>> data TypeConC
> 
> We're gonna use those empty data types as phantom types in our
> data type below.  This requires GADTs:
> 
>> data TypeCon t a where
>>  ValConA :: a                    -> TypeCon TypeConA a
>>  ValConB :: [TypeCon TypeConA a] -> TypeCon TypeConB a
>>  ValConC :: [TypeCon TypeConB a] -> TypeCon TypeConC a
> 
> Using the phantom types we tell the type system what kind of
> value we want.  Now, some useful instances because we can't
> derive them:
> 
>> instance Show a => Show (TypeCon t a) where
>>  showsPrec n x = showParen (n > 10) $
>>    case x of
>>      ValConA a -> showString "ValConA " . showsPrec 11 a
>>      ValConB a -> showString "ValConB " . showsPrec 11 a
>>      ValConC a -> showString "ValConC " . showsPrec 11 a
>> 
>> instance Eq a => Eq (TypeCon t a) where
>>  (ValConA a) == (ValConA b) = (a == b)
>>  (ValConB a) == (ValConB b) = (a == b)
>>  (ValConC a) == (ValConC b) = (a == b)
>>  _           == _           = error "never here"
> 
> The 't' phantom type guarantees that we'll never reach that
> last definition, e.g.
> 
>   *Main> (ValConA True) == (ValConB [])
> 
>   <interactive>:1:19:
>       Couldn't match expected type `TypeConA'
>              against inferred type `TypeConB'
>         Expected type: TypeCon TypeConA Bool
>         Inferred type: TypeCon TypeConB a
>       In the second argument of `(==)', namely `(ValConB [])'
>       In the expression: (ValConA True) == (ValConB [])
> 
>> instance Functor (TypeCon t) where
>>  fmap f (ValConA a) = ValConA (f a)
>>  fmap f (ValConB a) = ValConB (fmap (fmap f) a)
>>  fmap f (ValConC a) = ValConC (fmap (fmap f) a)
> 
> Now, if you want applicative then you'll need FlexibleInstances
> because we can't write 'pure :: a -> TypeCon t a'; this signature
> means that the user of the function may choose any 't' he wants,
> but we can give him only one of the 't's that appear in the
> constructors above.
> 
>> instance Applicative (TypeCon TypeConA) where
>>  pure x = ValConA x
>>  (ValConA f) <*> (ValConA x) = ValConA (f x)
>>  _           <*> _           = error "never here"
>> 
>> instance Applicative (TypeCon TypeConB) where
>>  pure x = ValConB [pure x]
>>  (ValConB fs) <*> (ValConB xs) = ValConB (fmap (<*>) fs <*> xs)
>>  _            <*> _            = error "never here"
>> 
>> instance Applicative (TypeCon TypeConC) where
>>  pure x = ValConC [pure x]
>>  (ValConC fs) <*> (ValConC xs) = ValConC (fmap (<*>) fs <*> xs)
>>  _            <*> _            = error "never here"
> 
> Now that we have applicative we can also write, using
> FlexibleContexts,
> 
>> liftBinOp :: Applicative (TypeCon t) => (a->b->c)
>>          -> TypeCon t a -> TypeCon t b -> TypeCon t c
>> liftBinOp = liftA2
> 
> We need that 'Applicative' constraint because the type system
> doesn't know that we have already defined all possible
> 'Applicative' instances, so we have to live with that :).
> 
> And then we can simply write
> 
>> instance (Applicative (TypeCon t), Num a) =>
>>         Num (TypeCon t a) where
>>  (+) = liftA2 (+)
>>  (-) = liftA2 (-)
>>  (*) = liftA2 (*)
>>  negate = fmap negate
>>  abs    = fmap abs
>>  signum = fmap signum
>>  fromInteger = pure . fromInteger
> 
> Finally,
> 
>   *Main> let x1 = ValConB [ValConA 10, ValConA 7]
>   *Main> let x2 = ValConB [ValConA 5, ValConA 13]
>   *Main> x1 * x2
>   ValConB [ValConA 50,ValConA 130,ValConA 35,ValConA 91]
> 
> HTH,
> 
> --
> Felipe.



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

Message: 4
Date: Wed, 18 Nov 2009 04:59:41 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Question on data/type
To: beginners@haskell.org
Message-ID: <200911180459.42866.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Mittwoch 18 November 2009 03:46:45 schrieb Phillip Pirrip:
> BTW, how do I generate "literate" Haskell code?  I keep reading it but I
> still don't know how to make one (I am assuming it is more complicated then
> just type the code in with ">" in emacs).
>
> //pip

No, it isn't. The hardest part is writing good code and comments (regardless of 
whether 
you write literate code or 'normal').

There are two ways of writing literal Haskell code, explained at 
http://haskell.org/onlinereport/syntax-iso.html#sect9.4 .

a) 'Bird tack', start code lines with '>', write as normal (you can include -- 
and {- -} 
comments). *Separate '>'-lines from non-code lines by at least one blank line*.

b) 'LaTeX' literate Haskell, code is begun by a line starting with 
"\begin{code}" and 
ended by "\end{code}". You can create really pretty stuff with that style.


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

Message: 5
Date: Wed, 18 Nov 2009 21:11:01 +0100
From: legajid <lega...@free.fr>
Subject: Re: [Haskell-beginners] Named fields in data types
To: Chadda? Fouch? <chaddai.fou...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4b0454d5.2030...@free.fr>
Content-Type: text/plain; charset=UTF-8; format=flowed

Chaddaï Fouché a écrit :
> On Tue, Nov 17, 2009 at 10:24 PM, legajid <lega...@free.fr> wrote:
>   
>> Hello,
>> i've some trouble with named fields in data types.
>>
>> data Carnet = Adresse  { nom :: String, cp :: Integer, ville :: String  }
>>       |
>>      Telephone {nom::String, telnum::String}
>>   deriving Show
>>
>> contact01 = Adresse "Didier" 51100 "Reims"
>> contact02 = Adresse {nom="Laure", cp=0} -- line 1
>> --contact02 Adresse { ville="Nogent" }       -- line 2
>> --contact02 { ville="Nogent" }                     -- line 3
>> contact03=Telephone "Didier" "0326..."       -- line 4
>>
>> When loading this source :
>> line 1 says "warning : Fields not initialized :ville
>> line 2 and 3 when uncommented give parse error (possibly indentation)
>>
>> I'm ok with line 1.
>> Is it possible to write such things as line2 or 3 ? Which syntax ?
>>     
>
> line 2 appears correct except you forgot the "="... Of course some
> fields aren't initialized so you may have a problem if you try to
> access them later on.
> (La ligne 2 est correcte sauf que tu as oublié le égal "="... Bien sûr
> certains des champs ne sont pas initialisés et ça pourrait poser
> problème si tu essaies d'y accéder plus tard)
>
> Note that you can also create a new value with some fields in common
> with an old value, for instance :
> (Note que tu peux aussi créer une nouvelle valeur partageant un
> certain nombre de champs avec une autre valeur déjà déclarée)
>
>   
>> contact01 = Adresse "Didier" 51100 "Reims"
>> contact02 = contact01 { nom = "Charles" }
>>     
>
> Which leads to the practice of using records to create a "default
> setting" value where you just modify the field that concern you.
> (Ce qui a donné lieu à l'idiome qui consiste à utiliser un type
> enregistrement (avec des champs nommés) pour les configuration avec
> une valeur "réglage par défaut" dont on ne modifie que les champs qui
> nous intéresse)
>
>   
>> main = xmonad defaultConfig {terminal = "konsole"}
>>     
>
>   
I've tried these lines :
contact01 = Adresse "Didier" 51100 "Reims"
contact02 = Adresse {nom="Laure", cp=0}
contact02 = contact02 { ville="Nogent" }

but i get an error : multiple declarations of Main.contact02
So, does it mean i can't add values to contact02. Instead, i must create 
a contact03 based on contact02 ?

Didier.



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

Message: 6
Date: Wed, 18 Nov 2009 15:38:33 -0500
From: "Edward Z. Yang" <ezy...@mit.edu>
Subject: Re: [Haskell-beginners] Named fields in data types
To: legajid <lega...@free.fr>
Cc: beginners <beginners@haskell.org>
Message-ID: <1258576646-sup-8...@ezyang>
Content-Type: text/plain; charset=UTF-8

Excerpts from legajid's message of Wed Nov 18 15:11:01 -0500 2009:
> I've tried these lines :
> contact01 = Adresse "Didier" 51100 "Reims"
> contact02 = Adresse {nom="Laure", cp=0}
> contact02 = contact02 { ville="Nogent" }
> 
> but i get an error : multiple declarations of Main.contact02
> So, does it mean i can't add values to contact02. Instead, i must create 
> a contact03 based on contact02 ?

Yep; part of the point behind a pure functional language is to not
allow mutation by default.

Cheers,
Edward


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

Message: 7
Date: Fri, 20 Nov 2009 02:58:30 -0500
From: i?fai <iae...@me.com>
Subject: [Haskell-beginners] Windows API and FFI
To: Beginners@haskell.org
Message-ID: <c0330a3e-389f-43ce-b956-c1c237a91...@me.com>
Content-Type: text/plain; charset=iso-8859-1

I have a specific function that I would like to get info to allow me to accept 
clicks into the cmd.exe window.

The function seems to be here:

http://msdn.microsoft.com/en-us/library/ms684961(VS.85).aspx

One of the parameters is this: A pointer to an array of INPUT_RECORD structures 
that receives the input buffer data. The total size of the array required will 
be less than 64K.

There are in and out parameters for this function. I have never done anything 
like this before, and was hoping this is done somewhere, or it is fairly easy 
to do.

Any help would be appreciated.

- iæfai.

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

Message: 8
Date: Fri, 20 Nov 2009 19:11:01 +1100
From: Jeff Zaroyko <jeffzaro...@gmail.com>
Subject: Re: [Haskell-beginners] Windows API and FFI
To: i?fai <iae...@me.com>
Cc: Beginners@haskell.org
Message-ID:
        <f5d9424f0911200011n41a995aeq6759e4319b6a2...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Fri, Nov 20, 2009 at 6:58 PM, iæfai <iae...@me.com> wrote:
> I have a specific function that I would like to get info to allow me to 
> accept clicks into the cmd.exe window.
>
> The function seems to be here:
>
> http://msdn.microsoft.com/en-us/library/ms684961(VS.85).aspx
>
> One of the parameters is this: A pointer to an array of INPUT_RECORD 
> structures that receives the input buffer data. The total size of the array 
> required will be less than 64K.
>
> There are in and out parameters for this function. I have never done anything 
> like this before, and was hoping this is done somewhere, or it is fairly easy 
> to do.

If you have not already, start by looking at the Win32 package which
has bindings to some Win32 functions, which includes helper functions
and types which you should find useful.  As to the specific structure
required, I'm not sure if it's covered, but it's a reasonable starting
point.


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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 17, Issue 18
*****************************************

Reply via email to